OSDN Git Service

2010-03-08 Janus Weil <janus@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010
3    Free Software Foundation, Inc.
4    Contributed by Andy Vaught
5
6 This file is part of GCC.
7
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 3, or (at your option) any later
11 version.
12
13 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
14 WARRANTY; without even the implied warranty of MERCHANTABILITY or
15 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
16 for more details.
17
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING3.  If not see
20 <http://www.gnu.org/licenses/>.  */
21
22 #include "config.h"
23 #include "system.h"
24 #include "flags.h"
25 #include "gfortran.h"
26 #include "obstack.h"
27 #include "bitmap.h"
28 #include "arith.h"  /* For gfc_compare_expr().  */
29 #include "dependency.h"
30 #include "data.h"
31 #include "target-memory.h" /* for gfc_simplify_transfer */
32
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.esym will be set.  */
2560   if (sym && sym->attr.abstract && !expr->value.function.esym)
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       gfc_clear_ts (&ts);
3962       ts.type = BT_INTEGER;
3963       ts.kind = gfc_index_integer_kind;
3964
3965       gfc_convert_type_warn (dim, &ts, 2, 0);
3966     }
3967
3968   return SUCCESS;
3969 }
3970
3971 /* Given an expression that contains array references, update those array
3972    references to point to the right array specifications.  While this is
3973    filled in during matching, this information is difficult to save and load
3974    in a module, so we take care of it here.
3975
3976    The idea here is that the original array reference comes from the
3977    base symbol.  We traverse the list of reference structures, setting
3978    the stored reference to references.  Component references can
3979    provide an additional array specification.  */
3980
3981 static void
3982 find_array_spec (gfc_expr *e)
3983 {
3984   gfc_array_spec *as;
3985   gfc_component *c;
3986   gfc_symbol *derived;
3987   gfc_ref *ref;
3988
3989   if (e->symtree->n.sym->ts.type == BT_CLASS)
3990     as = e->symtree->n.sym->ts.u.derived->components->as;
3991   else
3992     as = e->symtree->n.sym->as;
3993   derived = NULL;
3994
3995   for (ref = e->ref; ref; ref = ref->next)
3996     switch (ref->type)
3997       {
3998       case REF_ARRAY:
3999         if (as == NULL)
4000           gfc_internal_error ("find_array_spec(): Missing spec");
4001
4002         ref->u.ar.as = as;
4003         as = NULL;
4004         break;
4005
4006       case REF_COMPONENT:
4007         if (derived == NULL)
4008           derived = e->symtree->n.sym->ts.u.derived;
4009
4010         if (derived->attr.is_class)
4011           derived = derived->components->ts.u.derived;
4012
4013         c = derived->components;
4014
4015         for (; c; c = c->next)
4016           if (c == ref->u.c.component)
4017             {
4018               /* Track the sequence of component references.  */
4019               if (c->ts.type == BT_DERIVED)
4020                 derived = c->ts.u.derived;
4021               break;
4022             }
4023
4024         if (c == NULL)
4025           gfc_internal_error ("find_array_spec(): Component not found");
4026
4027         if (c->attr.dimension)
4028           {
4029             if (as != NULL)
4030               gfc_internal_error ("find_array_spec(): unused as(1)");
4031             as = c->as;
4032           }
4033
4034         break;
4035
4036       case REF_SUBSTRING:
4037         break;
4038       }
4039
4040   if (as != NULL)
4041     gfc_internal_error ("find_array_spec(): unused as(2)");
4042 }
4043
4044
4045 /* Resolve an array reference.  */
4046
4047 static gfc_try
4048 resolve_array_ref (gfc_array_ref *ar)
4049 {
4050   int i, check_scalar;
4051   gfc_expr *e;
4052
4053   for (i = 0; i < ar->dimen; i++)
4054     {
4055       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4056
4057       if (gfc_resolve_index (ar->start[i], check_scalar) == FAILURE)
4058         return FAILURE;
4059       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4060         return FAILURE;
4061       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4062         return FAILURE;
4063
4064       e = ar->start[i];
4065
4066       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4067         switch (e->rank)
4068           {
4069           case 0:
4070             ar->dimen_type[i] = DIMEN_ELEMENT;
4071             break;
4072
4073           case 1:
4074             ar->dimen_type[i] = DIMEN_VECTOR;
4075             if (e->expr_type == EXPR_VARIABLE
4076                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4077               ar->start[i] = gfc_get_parentheses (e);
4078             break;
4079
4080           default:
4081             gfc_error ("Array index at %L is an array of rank %d",
4082                        &ar->c_where[i], e->rank);
4083             return FAILURE;
4084           }
4085     }
4086
4087   /* If the reference type is unknown, figure out what kind it is.  */
4088
4089   if (ar->type == AR_UNKNOWN)
4090     {
4091       ar->type = AR_ELEMENT;
4092       for (i = 0; i < ar->dimen; i++)
4093         if (ar->dimen_type[i] == DIMEN_RANGE
4094             || ar->dimen_type[i] == DIMEN_VECTOR)
4095           {
4096             ar->type = AR_SECTION;
4097             break;
4098           }
4099     }
4100
4101   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4102     return FAILURE;
4103
4104   return SUCCESS;
4105 }
4106
4107
4108 static gfc_try
4109 resolve_substring (gfc_ref *ref)
4110 {
4111   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4112
4113   if (ref->u.ss.start != NULL)
4114     {
4115       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4116         return FAILURE;
4117
4118       if (ref->u.ss.start->ts.type != BT_INTEGER)
4119         {
4120           gfc_error ("Substring start index at %L must be of type INTEGER",
4121                      &ref->u.ss.start->where);
4122           return FAILURE;
4123         }
4124
4125       if (ref->u.ss.start->rank != 0)
4126         {
4127           gfc_error ("Substring start index at %L must be scalar",
4128                      &ref->u.ss.start->where);
4129           return FAILURE;
4130         }
4131
4132       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4133           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4134               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4135         {
4136           gfc_error ("Substring start index at %L is less than one",
4137                      &ref->u.ss.start->where);
4138           return FAILURE;
4139         }
4140     }
4141
4142   if (ref->u.ss.end != NULL)
4143     {
4144       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4145         return FAILURE;
4146
4147       if (ref->u.ss.end->ts.type != BT_INTEGER)
4148         {
4149           gfc_error ("Substring end index at %L must be of type INTEGER",
4150                      &ref->u.ss.end->where);
4151           return FAILURE;
4152         }
4153
4154       if (ref->u.ss.end->rank != 0)
4155         {
4156           gfc_error ("Substring end index at %L must be scalar",
4157                      &ref->u.ss.end->where);
4158           return FAILURE;
4159         }
4160
4161       if (ref->u.ss.length != NULL
4162           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4163           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4164               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4165         {
4166           gfc_error ("Substring end index at %L exceeds the string length",
4167                      &ref->u.ss.start->where);
4168           return FAILURE;
4169         }
4170
4171       if (compare_bound_mpz_t (ref->u.ss.end,
4172                                gfc_integer_kinds[k].huge) == CMP_GT
4173           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4174               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4175         {
4176           gfc_error ("Substring end index at %L is too large",
4177                      &ref->u.ss.end->where);
4178           return FAILURE;
4179         }
4180     }
4181
4182   return SUCCESS;
4183 }
4184
4185
4186 /* This function supplies missing substring charlens.  */
4187
4188 void
4189 gfc_resolve_substring_charlen (gfc_expr *e)
4190 {
4191   gfc_ref *char_ref;
4192   gfc_expr *start, *end;
4193
4194   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4195     if (char_ref->type == REF_SUBSTRING)
4196       break;
4197
4198   if (!char_ref)
4199     return;
4200
4201   gcc_assert (char_ref->next == NULL);
4202
4203   if (e->ts.u.cl)
4204     {
4205       if (e->ts.u.cl->length)
4206         gfc_free_expr (e->ts.u.cl->length);
4207       else if (e->expr_type == EXPR_VARIABLE
4208                  && e->symtree->n.sym->attr.dummy)
4209         return;
4210     }
4211
4212   e->ts.type = BT_CHARACTER;
4213   e->ts.kind = gfc_default_character_kind;
4214
4215   if (!e->ts.u.cl)
4216     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4217
4218   if (char_ref->u.ss.start)
4219     start = gfc_copy_expr (char_ref->u.ss.start);
4220   else
4221     start = gfc_int_expr (1);
4222
4223   if (char_ref->u.ss.end)
4224     end = gfc_copy_expr (char_ref->u.ss.end);
4225   else if (e->expr_type == EXPR_VARIABLE)
4226     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4227   else
4228     end = NULL;
4229
4230   if (!start || !end)
4231     return;
4232
4233   /* Length = (end - start +1).  */
4234   e->ts.u.cl->length = gfc_subtract (end, start);
4235   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length, gfc_int_expr (1));
4236
4237   e->ts.u.cl->length->ts.type = BT_INTEGER;
4238   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4239
4240   /* Make sure that the length is simplified.  */
4241   gfc_simplify_expr (e->ts.u.cl->length, 1);
4242   gfc_resolve_expr (e->ts.u.cl->length);
4243 }
4244
4245
4246 /* Resolve subtype references.  */
4247
4248 static gfc_try
4249 resolve_ref (gfc_expr *expr)
4250 {
4251   int current_part_dimension, n_components, seen_part_dimension;
4252   gfc_ref *ref;
4253
4254   for (ref = expr->ref; ref; ref = ref->next)
4255     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4256       {
4257         find_array_spec (expr);
4258         break;
4259       }
4260
4261   for (ref = expr->ref; ref; ref = ref->next)
4262     switch (ref->type)
4263       {
4264       case REF_ARRAY:
4265         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4266           return FAILURE;
4267         break;
4268
4269       case REF_COMPONENT:
4270         break;
4271
4272       case REF_SUBSTRING:
4273         resolve_substring (ref);
4274         break;
4275       }
4276
4277   /* Check constraints on part references.  */
4278
4279   current_part_dimension = 0;
4280   seen_part_dimension = 0;
4281   n_components = 0;
4282
4283   for (ref = expr->ref; ref; ref = ref->next)
4284     {
4285       switch (ref->type)
4286         {
4287         case REF_ARRAY:
4288           switch (ref->u.ar.type)
4289             {
4290             case AR_FULL:
4291             case AR_SECTION:
4292               current_part_dimension = 1;
4293               break;
4294
4295             case AR_ELEMENT:
4296               current_part_dimension = 0;
4297               break;
4298
4299             case AR_UNKNOWN:
4300               gfc_internal_error ("resolve_ref(): Bad array reference");
4301             }
4302
4303           break;
4304
4305         case REF_COMPONENT:
4306           if (current_part_dimension || seen_part_dimension)
4307             {
4308               /* F03:C614.  */
4309               if (ref->u.c.component->attr.pointer
4310                   || ref->u.c.component->attr.proc_pointer)
4311                 {
4312                   gfc_error ("Component to the right of a part reference "
4313                              "with nonzero rank must not have the POINTER "
4314                              "attribute at %L", &expr->where);
4315                   return FAILURE;
4316                 }
4317               else if (ref->u.c.component->attr.allocatable)
4318                 {
4319                   gfc_error ("Component to the right of a part reference "
4320                              "with nonzero rank must not have the ALLOCATABLE "
4321                              "attribute at %L", &expr->where);
4322                   return FAILURE;
4323                 }
4324             }
4325
4326           n_components++;
4327           break;
4328
4329         case REF_SUBSTRING:
4330           break;
4331         }
4332
4333       if (((ref->type == REF_COMPONENT && n_components > 1)
4334            || ref->next == NULL)
4335           && current_part_dimension
4336           && seen_part_dimension)
4337         {
4338           gfc_error ("Two or more part references with nonzero rank must "
4339                      "not be specified at %L", &expr->where);
4340           return FAILURE;
4341         }
4342
4343       if (ref->type == REF_COMPONENT)
4344         {
4345           if (current_part_dimension)
4346             seen_part_dimension = 1;
4347
4348           /* reset to make sure */
4349           current_part_dimension = 0;
4350         }
4351     }
4352
4353   return SUCCESS;
4354 }
4355
4356
4357 /* Given an expression, determine its shape.  This is easier than it sounds.
4358    Leaves the shape array NULL if it is not possible to determine the shape.  */
4359
4360 static void
4361 expression_shape (gfc_expr *e)
4362 {
4363   mpz_t array[GFC_MAX_DIMENSIONS];
4364   int i;
4365
4366   if (e->rank == 0 || e->shape != NULL)
4367     return;
4368
4369   for (i = 0; i < e->rank; i++)
4370     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4371       goto fail;
4372
4373   e->shape = gfc_get_shape (e->rank);
4374
4375   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4376
4377   return;
4378
4379 fail:
4380   for (i--; i >= 0; i--)
4381     mpz_clear (array[i]);
4382 }
4383
4384
4385 /* Given a variable expression node, compute the rank of the expression by
4386    examining the base symbol and any reference structures it may have.  */
4387
4388 static void
4389 expression_rank (gfc_expr *e)
4390 {
4391   gfc_ref *ref;
4392   int i, rank;
4393
4394   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4395      could lead to serious confusion...  */
4396   gcc_assert (e->expr_type != EXPR_COMPCALL);
4397
4398   if (e->ref == NULL)
4399     {
4400       if (e->expr_type == EXPR_ARRAY)
4401         goto done;
4402       /* Constructors can have a rank different from one via RESHAPE().  */
4403
4404       if (e->symtree == NULL)
4405         {
4406           e->rank = 0;
4407           goto done;
4408         }
4409
4410       e->rank = (e->symtree->n.sym->as == NULL)
4411                 ? 0 : e->symtree->n.sym->as->rank;
4412       goto done;
4413     }
4414
4415   rank = 0;
4416
4417   for (ref = e->ref; ref; ref = ref->next)
4418     {
4419       if (ref->type != REF_ARRAY)
4420         continue;
4421
4422       if (ref->u.ar.type == AR_FULL)
4423         {
4424           rank = ref->u.ar.as->rank;
4425           break;
4426         }
4427
4428       if (ref->u.ar.type == AR_SECTION)
4429         {
4430           /* Figure out the rank of the section.  */
4431           if (rank != 0)
4432             gfc_internal_error ("expression_rank(): Two array specs");
4433
4434           for (i = 0; i < ref->u.ar.dimen; i++)
4435             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4436                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4437               rank++;
4438
4439           break;
4440         }
4441     }
4442
4443   e->rank = rank;
4444
4445 done:
4446   expression_shape (e);
4447 }
4448
4449
4450 /* Resolve a variable expression.  */
4451
4452 static gfc_try
4453 resolve_variable (gfc_expr *e)
4454 {
4455   gfc_symbol *sym;
4456   gfc_try t;
4457
4458   t = SUCCESS;
4459
4460   if (e->symtree == NULL)
4461     return FAILURE;
4462
4463   if (e->ref && resolve_ref (e) == FAILURE)
4464     return FAILURE;
4465
4466   sym = e->symtree->n.sym;
4467   if (sym->attr.flavor == FL_PROCEDURE
4468       && (!sym->attr.function
4469           || (sym->attr.function && sym->result
4470               && sym->result->attr.proc_pointer
4471               && !sym->result->attr.function)))
4472     {
4473       e->ts.type = BT_PROCEDURE;
4474       goto resolve_procedure;
4475     }
4476
4477   if (sym->ts.type != BT_UNKNOWN)
4478     gfc_variable_attr (e, &e->ts);
4479   else
4480     {
4481       /* Must be a simple variable reference.  */
4482       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
4483         return FAILURE;
4484       e->ts = sym->ts;
4485     }
4486
4487   if (check_assumed_size_reference (sym, e))
4488     return FAILURE;
4489
4490   /* Deal with forward references to entries during resolve_code, to
4491      satisfy, at least partially, 12.5.2.5.  */
4492   if (gfc_current_ns->entries
4493       && current_entry_id == sym->entry_id
4494       && cs_base
4495       && cs_base->current
4496       && cs_base->current->op != EXEC_ENTRY)
4497     {
4498       gfc_entry_list *entry;
4499       gfc_formal_arglist *formal;
4500       int n;
4501       bool seen;
4502
4503       /* If the symbol is a dummy...  */
4504       if (sym->attr.dummy && sym->ns == gfc_current_ns)
4505         {
4506           entry = gfc_current_ns->entries;
4507           seen = false;
4508
4509           /* ...test if the symbol is a parameter of previous entries.  */
4510           for (; entry && entry->id <= current_entry_id; entry = entry->next)
4511             for (formal = entry->sym->formal; formal; formal = formal->next)
4512               {
4513                 if (formal->sym && sym->name == formal->sym->name)
4514                   seen = true;
4515               }
4516
4517           /*  If it has not been seen as a dummy, this is an error.  */
4518           if (!seen)
4519             {
4520               if (specification_expr)
4521                 gfc_error ("Variable '%s', used in a specification expression"
4522                            ", is referenced at %L before the ENTRY statement "
4523                            "in which it is a parameter",
4524                            sym->name, &cs_base->current->loc);
4525               else
4526                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
4527                            "statement in which it is a parameter",
4528                            sym->name, &cs_base->current->loc);
4529               t = FAILURE;
4530             }
4531         }
4532
4533       /* Now do the same check on the specification expressions.  */
4534       specification_expr = 1;
4535       if (sym->ts.type == BT_CHARACTER
4536           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
4537         t = FAILURE;
4538
4539       if (sym->as)
4540         for (n = 0; n < sym->as->rank; n++)
4541           {
4542              specification_expr = 1;
4543              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
4544                t = FAILURE;
4545              specification_expr = 1;
4546              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
4547                t = FAILURE;
4548           }
4549       specification_expr = 0;
4550
4551       if (t == SUCCESS)
4552         /* Update the symbol's entry level.  */
4553         sym->entry_id = current_entry_id + 1;
4554     }
4555
4556 resolve_procedure:
4557   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
4558     t = FAILURE;
4559
4560   return t;
4561 }
4562
4563
4564 /* Checks to see that the correct symbol has been host associated.
4565    The only situation where this arises is that in which a twice
4566    contained function is parsed after the host association is made.
4567    Therefore, on detecting this, change the symbol in the expression
4568    and convert the array reference into an actual arglist if the old
4569    symbol is a variable.  */
4570 static bool
4571 check_host_association (gfc_expr *e)
4572 {
4573   gfc_symbol *sym, *old_sym;
4574   gfc_symtree *st;
4575   int n;
4576   gfc_ref *ref;
4577   gfc_actual_arglist *arg, *tail = NULL;
4578   bool retval = e->expr_type == EXPR_FUNCTION;
4579
4580   /*  If the expression is the result of substitution in
4581       interface.c(gfc_extend_expr) because there is no way in
4582       which the host association can be wrong.  */
4583   if (e->symtree == NULL
4584         || e->symtree->n.sym == NULL
4585         || e->user_operator)
4586     return retval;
4587
4588   old_sym = e->symtree->n.sym;
4589
4590   if (gfc_current_ns->parent
4591         && old_sym->ns != gfc_current_ns)
4592     {
4593       /* Use the 'USE' name so that renamed module symbols are
4594          correctly handled.  */
4595       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
4596
4597       if (sym && old_sym != sym
4598               && sym->ts.type == old_sym->ts.type
4599               && sym->attr.flavor == FL_PROCEDURE
4600               && sym->attr.contained)
4601         {
4602           /* Clear the shape, since it might not be valid.  */
4603           if (e->shape != NULL)
4604             {
4605               for (n = 0; n < e->rank; n++)
4606                 mpz_clear (e->shape[n]);
4607
4608               gfc_free (e->shape);
4609             }
4610
4611           /* Give the expression the right symtree!  */
4612           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
4613           gcc_assert (st != NULL);
4614
4615           if (old_sym->attr.flavor == FL_PROCEDURE
4616                 || e->expr_type == EXPR_FUNCTION)
4617             {
4618               /* Original was function so point to the new symbol, since
4619                  the actual argument list is already attached to the
4620                  expression. */
4621               e->value.function.esym = NULL;
4622               e->symtree = st;
4623             }
4624           else
4625             {
4626               /* Original was variable so convert array references into
4627                  an actual arglist. This does not need any checking now
4628                  since gfc_resolve_function will take care of it.  */
4629               e->value.function.actual = NULL;
4630               e->expr_type = EXPR_FUNCTION;
4631               e->symtree = st;
4632
4633               /* Ambiguity will not arise if the array reference is not
4634                  the last reference.  */
4635               for (ref = e->ref; ref; ref = ref->next)
4636                 if (ref->type == REF_ARRAY && ref->next == NULL)
4637                   break;
4638
4639               gcc_assert (ref->type == REF_ARRAY);
4640
4641               /* Grab the start expressions from the array ref and
4642                  copy them into actual arguments.  */
4643               for (n = 0; n < ref->u.ar.dimen; n++)
4644                 {
4645                   arg = gfc_get_actual_arglist ();
4646                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
4647                   if (e->value.function.actual == NULL)
4648                     tail = e->value.function.actual = arg;
4649                   else
4650                     {
4651                       tail->next = arg;
4652                       tail = arg;
4653                     }
4654                 }
4655
4656               /* Dump the reference list and set the rank.  */
4657               gfc_free_ref_list (e->ref);
4658               e->ref = NULL;
4659               e->rank = sym->as ? sym->as->rank : 0;
4660             }
4661
4662           gfc_resolve_expr (e);
4663           sym->refs++;
4664         }
4665     }
4666   /* This might have changed!  */
4667   return e->expr_type == EXPR_FUNCTION;
4668 }
4669
4670
4671 static void
4672 gfc_resolve_character_operator (gfc_expr *e)
4673 {
4674   gfc_expr *op1 = e->value.op.op1;
4675   gfc_expr *op2 = e->value.op.op2;
4676   gfc_expr *e1 = NULL;
4677   gfc_expr *e2 = NULL;
4678
4679   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
4680
4681   if (op1->ts.u.cl && op1->ts.u.cl->length)
4682     e1 = gfc_copy_expr (op1->ts.u.cl->length);
4683   else if (op1->expr_type == EXPR_CONSTANT)
4684     e1 = gfc_int_expr (op1->value.character.length);
4685
4686   if (op2->ts.u.cl && op2->ts.u.cl->length)
4687     e2 = gfc_copy_expr (op2->ts.u.cl->length);
4688   else if (op2->expr_type == EXPR_CONSTANT)
4689     e2 = gfc_int_expr (op2->value.character.length);
4690
4691   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4692
4693   if (!e1 || !e2)
4694     return;
4695
4696   e->ts.u.cl->length = gfc_add (e1, e2);
4697   e->ts.u.cl->length->ts.type = BT_INTEGER;
4698   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4699   gfc_simplify_expr (e->ts.u.cl->length, 0);
4700   gfc_resolve_expr (e->ts.u.cl->length);
4701
4702   return;
4703 }
4704
4705
4706 /*  Ensure that an character expression has a charlen and, if possible, a
4707     length expression.  */
4708
4709 static void
4710 fixup_charlen (gfc_expr *e)
4711 {
4712   /* The cases fall through so that changes in expression type and the need
4713      for multiple fixes are picked up.  In all circumstances, a charlen should
4714      be available for the middle end to hang a backend_decl on.  */
4715   switch (e->expr_type)
4716     {
4717     case EXPR_OP:
4718       gfc_resolve_character_operator (e);
4719
4720     case EXPR_ARRAY:
4721       if (e->expr_type == EXPR_ARRAY)
4722         gfc_resolve_character_array_constructor (e);
4723
4724     case EXPR_SUBSTRING:
4725       if (!e->ts.u.cl && e->ref)
4726         gfc_resolve_substring_charlen (e);
4727
4728     default:
4729       if (!e->ts.u.cl)
4730         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4731
4732       break;
4733     }
4734 }
4735
4736
4737 /* Update an actual argument to include the passed-object for type-bound
4738    procedures at the right position.  */
4739
4740 static gfc_actual_arglist*
4741 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
4742                      const char *name)
4743 {
4744   gcc_assert (argpos > 0);
4745
4746   if (argpos == 1)
4747     {
4748       gfc_actual_arglist* result;
4749
4750       result = gfc_get_actual_arglist ();
4751       result->expr = po;
4752       result->next = lst;
4753       if (name)
4754         result->name = name;
4755
4756       return result;
4757     }
4758
4759   if (lst)
4760     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
4761   else
4762     lst = update_arglist_pass (NULL, po, argpos - 1, name);
4763   return lst;
4764 }
4765
4766
4767 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
4768
4769 static gfc_expr*
4770 extract_compcall_passed_object (gfc_expr* e)
4771 {
4772   gfc_expr* po;
4773
4774   gcc_assert (e->expr_type == EXPR_COMPCALL);
4775
4776   if (e->value.compcall.base_object)
4777     po = gfc_copy_expr (e->value.compcall.base_object);
4778   else
4779     {
4780       po = gfc_get_expr ();
4781       po->expr_type = EXPR_VARIABLE;
4782       po->symtree = e->symtree;
4783       po->ref = gfc_copy_ref (e->ref);
4784       po->where = e->where;
4785     }
4786
4787   if (gfc_resolve_expr (po) == FAILURE)
4788     return NULL;
4789
4790   return po;
4791 }
4792
4793
4794 /* Update the arglist of an EXPR_COMPCALL expression to include the
4795    passed-object.  */
4796
4797 static gfc_try
4798 update_compcall_arglist (gfc_expr* e)
4799 {
4800   gfc_expr* po;
4801   gfc_typebound_proc* tbp;
4802
4803   tbp = e->value.compcall.tbp;
4804
4805   if (tbp->error)
4806     return FAILURE;
4807
4808   po = extract_compcall_passed_object (e);
4809   if (!po)
4810     return FAILURE;
4811
4812   if (tbp->nopass || e->value.compcall.ignore_pass)
4813     {
4814       gfc_free_expr (po);
4815       return SUCCESS;
4816     }
4817
4818   gcc_assert (tbp->pass_arg_num > 0);
4819   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
4820                                                   tbp->pass_arg_num,
4821                                                   tbp->pass_arg);
4822
4823   return SUCCESS;
4824 }
4825
4826
4827 /* Extract the passed object from a PPC call (a copy of it).  */
4828
4829 static gfc_expr*
4830 extract_ppc_passed_object (gfc_expr *e)
4831 {
4832   gfc_expr *po;
4833   gfc_ref **ref;
4834
4835   po = gfc_get_expr ();
4836   po->expr_type = EXPR_VARIABLE;
4837   po->symtree = e->symtree;
4838   po->ref = gfc_copy_ref (e->ref);
4839   po->where = e->where;
4840
4841   /* Remove PPC reference.  */
4842   ref = &po->ref;
4843   while ((*ref)->next)
4844     ref = &(*ref)->next;
4845   gfc_free_ref_list (*ref);
4846   *ref = NULL;
4847
4848   if (gfc_resolve_expr (po) == FAILURE)
4849     return NULL;
4850
4851   return po;
4852 }
4853
4854
4855 /* Update the actual arglist of a procedure pointer component to include the
4856    passed-object.  */
4857
4858 static gfc_try
4859 update_ppc_arglist (gfc_expr* e)
4860 {
4861   gfc_expr* po;
4862   gfc_component *ppc;
4863   gfc_typebound_proc* tb;
4864
4865   if (!gfc_is_proc_ptr_comp (e, &ppc))
4866     return FAILURE;
4867
4868   tb = ppc->tb;
4869
4870   if (tb->error)
4871     return FAILURE;
4872   else if (tb->nopass)
4873     return SUCCESS;
4874
4875   po = extract_ppc_passed_object (e);
4876   if (!po)
4877     return FAILURE;
4878
4879   if (po->rank > 0)
4880     {
4881       gfc_error ("Passed-object at %L must be scalar", &e->where);
4882       return FAILURE;
4883     }
4884
4885   gcc_assert (tb->pass_arg_num > 0);
4886   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
4887                                                   tb->pass_arg_num,
4888                                                   tb->pass_arg);
4889
4890   return SUCCESS;
4891 }
4892
4893
4894 /* Check that the object a TBP is called on is valid, i.e. it must not be
4895    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
4896
4897 static gfc_try
4898 check_typebound_baseobject (gfc_expr* e)
4899 {
4900   gfc_expr* base;
4901
4902   base = extract_compcall_passed_object (e);
4903   if (!base)
4904     return FAILURE;
4905
4906   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
4907
4908   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
4909     {
4910       gfc_error ("Base object for type-bound procedure call at %L is of"
4911                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
4912       return FAILURE;
4913     }
4914
4915   /* If the procedure called is NOPASS, the base object must be scalar.  */
4916   if (e->value.compcall.tbp->nopass && base->rank > 0)
4917     {
4918       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
4919                  " be scalar", &e->where);
4920       return FAILURE;
4921     }
4922
4923   /* FIXME: Remove once PR 41177 (this problem) is fixed completely.  */
4924   if (base->rank > 0)
4925     {
4926       gfc_error ("Non-scalar base object at %L currently not implemented",
4927                  &e->where);
4928       return FAILURE;
4929     }
4930
4931   return SUCCESS;
4932 }
4933
4934
4935 /* Resolve a call to a type-bound procedure, either function or subroutine,
4936    statically from the data in an EXPR_COMPCALL expression.  The adapted
4937    arglist and the target-procedure symtree are returned.  */
4938
4939 static gfc_try
4940 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
4941                           gfc_actual_arglist** actual)
4942 {
4943   gcc_assert (e->expr_type == EXPR_COMPCALL);
4944   gcc_assert (!e->value.compcall.tbp->is_generic);
4945
4946   /* Update the actual arglist for PASS.  */
4947   if (update_compcall_arglist (e) == FAILURE)
4948     return FAILURE;
4949
4950   *actual = e->value.compcall.actual;
4951   *target = e->value.compcall.tbp->u.specific;
4952
4953   gfc_free_ref_list (e->ref);
4954   e->ref = NULL;
4955   e->value.compcall.actual = NULL;
4956
4957   return SUCCESS;
4958 }
4959
4960
4961 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
4962    which of the specific bindings (if any) matches the arglist and transform
4963    the expression into a call of that binding.  */
4964
4965 static gfc_try
4966 resolve_typebound_generic_call (gfc_expr* e)
4967 {
4968   gfc_typebound_proc* genproc;
4969   const char* genname;
4970
4971   gcc_assert (e->expr_type == EXPR_COMPCALL);
4972   genname = e->value.compcall.name;
4973   genproc = e->value.compcall.tbp;
4974
4975   if (!genproc->is_generic)
4976     return SUCCESS;
4977
4978   /* Try the bindings on this type and in the inheritance hierarchy.  */
4979   for (; genproc; genproc = genproc->overridden)
4980     {
4981       gfc_tbp_generic* g;
4982
4983       gcc_assert (genproc->is_generic);
4984       for (g = genproc->u.generic; g; g = g->next)
4985         {
4986           gfc_symbol* target;
4987           gfc_actual_arglist* args;
4988           bool matches;
4989
4990           gcc_assert (g->specific);
4991
4992           if (g->specific->error)
4993             continue;
4994
4995           target = g->specific->u.specific->n.sym;
4996
4997           /* Get the right arglist by handling PASS/NOPASS.  */
4998           args = gfc_copy_actual_arglist (e->value.compcall.actual);
4999           if (!g->specific->nopass)
5000             {
5001               gfc_expr* po;
5002               po = extract_compcall_passed_object (e);
5003               if (!po)
5004                 return FAILURE;
5005
5006               gcc_assert (g->specific->pass_arg_num > 0);
5007               gcc_assert (!g->specific->error);
5008               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5009                                           g->specific->pass_arg);
5010             }
5011           resolve_actual_arglist (args, target->attr.proc,
5012                                   is_external_proc (target) && !target->formal);
5013
5014           /* Check if this arglist matches the formal.  */
5015           matches = gfc_arglist_matches_symbol (&args, target);
5016
5017           /* Clean up and break out of the loop if we've found it.  */
5018           gfc_free_actual_arglist (args);
5019           if (matches)
5020             {
5021               e->value.compcall.tbp = g->specific;
5022               goto success;
5023             }
5024         }
5025     }
5026
5027   /* Nothing matching found!  */
5028   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5029              " '%s' at %L", genname, &e->where);
5030   return FAILURE;
5031
5032 success:
5033   return SUCCESS;
5034 }
5035
5036
5037 /* Resolve a call to a type-bound subroutine.  */
5038
5039 static gfc_try
5040 resolve_typebound_call (gfc_code* c)
5041 {
5042   gfc_actual_arglist* newactual;
5043   gfc_symtree* target;
5044
5045   /* Check that's really a SUBROUTINE.  */
5046   if (!c->expr1->value.compcall.tbp->subroutine)
5047     {
5048       gfc_error ("'%s' at %L should be a SUBROUTINE",
5049                  c->expr1->value.compcall.name, &c->loc);
5050       return FAILURE;
5051     }
5052
5053   if (check_typebound_baseobject (c->expr1) == FAILURE)
5054     return FAILURE;
5055
5056   if (resolve_typebound_generic_call (c->expr1) == FAILURE)
5057     return FAILURE;
5058
5059   /* Transform into an ordinary EXEC_CALL for now.  */
5060
5061   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5062     return FAILURE;
5063
5064   c->ext.actual = newactual;
5065   c->symtree = target;
5066   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5067
5068   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5069
5070   gfc_free_expr (c->expr1);
5071   c->expr1 = gfc_get_expr ();
5072   c->expr1->expr_type = EXPR_FUNCTION;
5073   c->expr1->symtree = target;
5074   c->expr1->where = c->loc;
5075
5076   return resolve_call (c);
5077 }
5078
5079
5080 /* Resolve a component-call expression.  This originally was intended
5081    only to see functions.  However, it is convenient to use it in 
5082    resolving subroutine class methods, since we do not have to add a
5083    gfc_code each time. */
5084 static gfc_try
5085 resolve_compcall (gfc_expr* e, bool fcn)
5086 {
5087   gfc_actual_arglist* newactual;
5088   gfc_symtree* target;
5089
5090   /* Check that's really a FUNCTION.  */
5091   if (fcn && !e->value.compcall.tbp->function)
5092     {
5093       gfc_error ("'%s' at %L should be a FUNCTION",
5094                  e->value.compcall.name, &e->where);
5095       return FAILURE;
5096     }
5097   else if (!fcn && !e->value.compcall.tbp->subroutine)
5098     {
5099       /* To resolve class member calls, we borrow this bit
5100          of code to select the specific procedures.  */
5101       gfc_error ("'%s' at %L should be a SUBROUTINE",
5102                  e->value.compcall.name, &e->where);
5103       return FAILURE;
5104     }
5105
5106   /* These must not be assign-calls!  */
5107   gcc_assert (!e->value.compcall.assign);
5108
5109   if (check_typebound_baseobject (e) == FAILURE)
5110     return FAILURE;
5111
5112   if (resolve_typebound_generic_call (e) == FAILURE)
5113     return FAILURE;
5114   gcc_assert (!e->value.compcall.tbp->is_generic);
5115
5116   /* Take the rank from the function's symbol.  */
5117   if (e->value.compcall.tbp->u.specific->n.sym->as)
5118     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5119
5120   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5121      arglist to the TBP's binding target.  */
5122
5123   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5124     return FAILURE;
5125
5126   e->value.function.actual = newactual;
5127   e->value.function.name = NULL;
5128   e->value.function.esym = target->n.sym;
5129   e->value.function.class_esym = NULL;
5130   e->value.function.isym = NULL;
5131   e->symtree = target;
5132   e->ts = target->n.sym->ts;
5133   e->expr_type = EXPR_FUNCTION;
5134
5135   /* Resolution is not necessary if this is a class subroutine; this
5136      function only has to identify the specific proc. Resolution of
5137      the call will be done next in resolve_typebound_call.  */
5138   return fcn ? gfc_resolve_expr (e) : SUCCESS;
5139 }
5140
5141
5142 /* Resolve a typebound call for the members in a class.  This group of
5143    functions implements dynamic dispatch in the provisional version
5144    of f03 OOP.  As soon as vtables are in place and contain pointers
5145    to methods, this will no longer be necessary.  */
5146 static gfc_expr *list_e;
5147 static void check_class_members (gfc_symbol *);
5148 static gfc_try class_try;
5149 static bool fcn_flag;
5150 static gfc_symbol *class_object;
5151
5152
5153 static void
5154 check_members (gfc_symbol *derived)
5155 {
5156   if (derived->attr.flavor == FL_DERIVED)
5157     check_class_members (derived);
5158 }
5159
5160
5161 static void 
5162 check_class_members (gfc_symbol *derived)
5163 {
5164   gfc_expr *e;
5165   gfc_symtree *tbp;
5166   gfc_class_esym_list *etmp;
5167
5168   e = gfc_copy_expr (list_e);
5169
5170   tbp = gfc_find_typebound_proc (derived, &class_try,
5171                                  e->value.compcall.name,
5172                                  false, &e->where);
5173
5174   if (tbp == NULL)
5175     {
5176       gfc_error ("no typebound available procedure named '%s' at %L",
5177                  e->value.compcall.name, &e->where);
5178       return;
5179     }
5180
5181   /* If we have to match a passed class member, force the actual
5182       expression to have the correct type.  */
5183   if (!tbp->n.tb->nopass)
5184     {
5185       if (e->value.compcall.base_object == NULL)
5186         e->value.compcall.base_object = extract_compcall_passed_object (e);
5187
5188       if (!derived->attr.abstract)
5189         {
5190           e->value.compcall.base_object->ts.type = BT_DERIVED;
5191           e->value.compcall.base_object->ts.u.derived = derived;
5192         }
5193     }
5194
5195   e->value.compcall.tbp = tbp->n.tb;
5196   e->value.compcall.name = tbp->name;
5197
5198   /* Let the original expresssion catch the assertion in
5199      resolve_compcall, since this flag does not appear to be reset or
5200      copied in some systems.  */
5201   e->value.compcall.assign = 0;
5202
5203   /* Do the renaming, PASSing, generic => specific and other
5204      good things for each class member.  */
5205   class_try = (resolve_compcall (e, fcn_flag) == SUCCESS)
5206                                 ? class_try : FAILURE;
5207
5208   /* Now transfer the found symbol to the esym list.  */
5209   if (class_try == SUCCESS)
5210     {
5211       etmp = list_e->value.function.class_esym;
5212       list_e->value.function.class_esym
5213                 = gfc_get_class_esym_list();
5214       list_e->value.function.class_esym->next = etmp;
5215       list_e->value.function.class_esym->derived = derived;
5216       list_e->value.function.class_esym->esym
5217                 = e->value.function.esym;
5218     }
5219
5220   gfc_free_expr (e);
5221   
5222   /* Burrow down into grandchildren types.  */
5223   if (derived->f2k_derived)
5224     gfc_traverse_ns (derived->f2k_derived, check_members);
5225 }
5226
5227
5228 /* Eliminate esym_lists where all the members point to the
5229    typebound procedure of the declared type; ie. one where
5230    type selection has no effect..  */
5231 static void
5232 resolve_class_esym (gfc_expr *e)
5233 {
5234   gfc_class_esym_list *p, *q;
5235   bool empty = true;
5236
5237   gcc_assert (e && e->expr_type == EXPR_FUNCTION);
5238
5239   p = e->value.function.class_esym;
5240   if (p == NULL)
5241     return;
5242
5243   for (; p; p = p->next)
5244     empty = empty && (e->value.function.esym == p->esym);
5245
5246   if (empty)
5247     {
5248       p = e->value.function.class_esym;
5249       for (; p; p = q)
5250         {
5251           q = p->next;
5252           gfc_free (p);
5253         }
5254       e->value.function.class_esym = NULL;
5255    }
5256 }
5257
5258
5259 /* Generate an expression for the hash value, given the reference to
5260    the class of the final expression (class_ref), the base of the
5261    full reference list (new_ref), the declared type and the class
5262    object (st).  */
5263 static gfc_expr*
5264 hash_value_expr (gfc_ref *class_ref, gfc_ref *new_ref, gfc_symtree *st)
5265 {
5266   gfc_expr *hash_value;
5267
5268   /* Build an expression for the correct hash_value; ie. that of the last
5269      CLASS reference.  */
5270   if (class_ref)
5271     {
5272       class_ref->next = NULL;
5273     }
5274   else
5275     {
5276       gfc_free_ref_list (new_ref);
5277       new_ref = NULL;
5278     }
5279   hash_value = gfc_get_expr ();
5280   hash_value->expr_type = EXPR_VARIABLE;
5281   hash_value->symtree = st;
5282   hash_value->symtree->n.sym->refs++;
5283   hash_value->ref = new_ref;
5284   gfc_add_component_ref (hash_value, "$vptr");
5285   gfc_add_component_ref (hash_value, "$hash");
5286
5287   return hash_value;
5288 }
5289
5290
5291 /* Get the ultimate declared type from an expression.  In addition,
5292    return the last class/derived type reference and the copy of the
5293    reference list.  */
5294 static gfc_symbol*
5295 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5296                         gfc_expr *e)
5297 {
5298   gfc_symbol *declared;
5299   gfc_ref *ref;
5300
5301   declared = NULL;
5302   *class_ref = NULL;
5303   *new_ref = gfc_copy_ref (e->ref);
5304   for (ref = *new_ref; ref; ref = ref->next)
5305     {
5306       if (ref->type != REF_COMPONENT)
5307         continue;
5308
5309       if (ref->u.c.component->ts.type == BT_CLASS
5310             || ref->u.c.component->ts.type == BT_DERIVED)
5311         {
5312           declared = ref->u.c.component->ts.u.derived;
5313           *class_ref = ref;
5314         }
5315     }
5316
5317   if (declared == NULL)
5318     declared = e->symtree->n.sym->ts.u.derived;
5319
5320   return declared;
5321 }
5322
5323
5324 /* Resolve the argument expressions so that any arguments expressions
5325    that include class methods are resolved before the current call.
5326    This is necessary because of the static variables used in CLASS
5327    method resolution.  */
5328 static void
5329 resolve_arg_exprs (gfc_actual_arglist *arg)
5330
5331   /* Resolve the actual arglist expressions.  */
5332   for (; arg; arg = arg->next)
5333     {
5334       if (arg->expr)
5335         gfc_resolve_expr (arg->expr);
5336     }
5337 }
5338
5339
5340 /* Resolve a CLASS typebound function, or 'method'.  */
5341 static gfc_try
5342 resolve_class_compcall (gfc_expr* e)
5343 {
5344   gfc_symbol *derived, *declared;
5345   gfc_ref *new_ref;
5346   gfc_ref *class_ref;
5347   gfc_symtree *st;
5348
5349   st = e->symtree;
5350   class_object = st->n.sym;
5351
5352   /* Get the CLASS declared type.  */
5353   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5354
5355   /* Weed out cases of the ultimate component being a derived type.  */
5356   if (class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5357     {
5358       gfc_free_ref_list (new_ref);
5359       return resolve_compcall (e, true);
5360     }
5361
5362   /* Resolve the argument expressions,  */
5363   resolve_arg_exprs (e->value.function.actual); 
5364
5365   /* Get the data component, which is of the declared type.  */
5366   derived = declared->components->ts.u.derived;
5367
5368   /* Resolve the function call for each member of the class.  */
5369   class_try = SUCCESS;
5370   fcn_flag = true;
5371   list_e = gfc_copy_expr (e);
5372   check_class_members (derived);
5373
5374   class_try = (resolve_compcall (e, true) == SUCCESS)
5375                  ? class_try : FAILURE;
5376
5377   /* Transfer the class list to the original expression.  Note that
5378      the class_esym list is cleaned up in trans-expr.c, as the calls
5379      are translated.  */
5380   e->value.function.class_esym = list_e->value.function.class_esym;
5381   list_e->value.function.class_esym = NULL;
5382   gfc_free_expr (list_e);
5383
5384   resolve_class_esym (e);
5385
5386   /* More than one typebound procedure so transmit an expression for
5387      the hash_value as the selector.  */
5388   if (e->value.function.class_esym != NULL)
5389     e->value.function.class_esym->hash_value
5390                 = hash_value_expr (class_ref, new_ref, st);
5391
5392   return class_try;
5393 }
5394
5395 /* Resolve a CLASS typebound subroutine, or 'method'.  */
5396 static gfc_try
5397 resolve_class_typebound_call (gfc_code *code)
5398 {
5399   gfc_symbol *derived, *declared;
5400   gfc_ref *new_ref;
5401   gfc_ref *class_ref;
5402   gfc_symtree *st;
5403
5404   st = code->expr1->symtree;
5405   class_object = st->n.sym;
5406
5407   /* Get the CLASS declared type.  */
5408   declared = get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5409
5410   /* Weed out cases of the ultimate component being a derived type.  */
5411   if (class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5412     {
5413       gfc_free_ref_list (new_ref);
5414       return resolve_typebound_call (code);
5415     } 
5416
5417   /* Resolve the argument expressions,  */
5418   resolve_arg_exprs (code->expr1->value.compcall.actual); 
5419
5420   /* Get the data component, which is of the declared type.  */
5421   derived = declared->components->ts.u.derived;
5422
5423   class_try = SUCCESS;
5424   fcn_flag = false;
5425   list_e = gfc_copy_expr (code->expr1);
5426   check_class_members (derived);
5427
5428   class_try = (resolve_typebound_call (code) == SUCCESS)
5429                  ? class_try : FAILURE;
5430
5431   /* Transfer the class list to the original expression.  Note that
5432      the class_esym list is cleaned up in trans-expr.c, as the calls
5433      are translated.  */
5434   code->expr1->value.function.class_esym
5435                         = list_e->value.function.class_esym;
5436   list_e->value.function.class_esym = NULL;
5437   gfc_free_expr (list_e);
5438
5439   resolve_class_esym (code->expr1);
5440
5441   /* More than one typebound procedure so transmit an expression for
5442      the hash_value as the selector.  */
5443   if (code->expr1->value.function.class_esym != NULL)
5444     code->expr1->value.function.class_esym->hash_value
5445                 = hash_value_expr (class_ref, new_ref, st);
5446
5447   return class_try;
5448 }
5449
5450
5451 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5452
5453 static gfc_try
5454 resolve_ppc_call (gfc_code* c)
5455 {
5456   gfc_component *comp;
5457   bool b;
5458
5459   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5460   gcc_assert (b);
5461
5462   c->resolved_sym = c->expr1->symtree->n.sym;
5463   c->expr1->expr_type = EXPR_VARIABLE;
5464
5465   if (!comp->attr.subroutine)
5466     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5467
5468   if (resolve_ref (c->expr1) == FAILURE)
5469     return FAILURE;
5470
5471   if (update_ppc_arglist (c->expr1) == FAILURE)
5472     return FAILURE;
5473
5474   c->ext.actual = c->expr1->value.compcall.actual;
5475
5476   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5477                               comp->formal == NULL) == FAILURE)
5478     return FAILURE;
5479
5480   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
5481
5482   return SUCCESS;
5483 }
5484
5485
5486 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
5487
5488 static gfc_try
5489 resolve_expr_ppc (gfc_expr* e)
5490 {
5491   gfc_component *comp;
5492   bool b;
5493
5494   b = gfc_is_proc_ptr_comp (e, &comp);
5495   gcc_assert (b);
5496
5497   /* Convert to EXPR_FUNCTION.  */
5498   e->expr_type = EXPR_FUNCTION;
5499   e->value.function.isym = NULL;
5500   e->value.function.actual = e->value.compcall.actual;
5501   e->ts = comp->ts;
5502   if (comp->as != NULL)
5503     e->rank = comp->as->rank;
5504
5505   if (!comp->attr.function)
5506     gfc_add_function (&comp->attr, comp->name, &e->where);
5507
5508   if (resolve_ref (e) == FAILURE)
5509     return FAILURE;
5510
5511   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
5512                               comp->formal == NULL) == FAILURE)
5513     return FAILURE;
5514
5515   if (update_ppc_arglist (e) == FAILURE)
5516     return FAILURE;
5517
5518   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
5519
5520   return SUCCESS;
5521 }
5522
5523
5524 static bool
5525 gfc_is_expandable_expr (gfc_expr *e)
5526 {
5527   gfc_constructor *con;
5528
5529   if (e->expr_type == EXPR_ARRAY)
5530     {
5531       /* Traverse the constructor looking for variables that are flavor
5532          parameter.  Parameters must be expanded since they are fully used at
5533          compile time.  */
5534       for (con = e->value.constructor; con; con = con->next)
5535         {
5536           if (con->expr->expr_type == EXPR_VARIABLE
5537           && con->expr->symtree
5538           && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
5539               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
5540             return true;
5541           if (con->expr->expr_type == EXPR_ARRAY
5542             && gfc_is_expandable_expr (con->expr))
5543             return true;
5544         }
5545     }
5546
5547   return false;
5548 }
5549
5550 /* Resolve an expression.  That is, make sure that types of operands agree
5551    with their operators, intrinsic operators are converted to function calls
5552    for overloaded types and unresolved function references are resolved.  */
5553
5554 gfc_try
5555 gfc_resolve_expr (gfc_expr *e)
5556 {
5557   gfc_try t;
5558
5559   if (e == NULL)
5560     return SUCCESS;
5561
5562   switch (e->expr_type)
5563     {
5564     case EXPR_OP:
5565       t = resolve_operator (e);
5566       break;
5567
5568     case EXPR_FUNCTION:
5569     case EXPR_VARIABLE:
5570
5571       if (check_host_association (e))
5572         t = resolve_function (e);
5573       else
5574         {
5575           t = resolve_variable (e);
5576           if (t == SUCCESS)
5577             expression_rank (e);
5578         }
5579
5580       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
5581           && e->ref->type != REF_SUBSTRING)
5582         gfc_resolve_substring_charlen (e);
5583
5584       break;
5585
5586     case EXPR_COMPCALL:
5587       if (e->symtree && e->symtree->n.sym->ts.type == BT_CLASS)
5588         t = resolve_class_compcall (e);
5589       else
5590         t = resolve_compcall (e, true);
5591       break;
5592
5593     case EXPR_SUBSTRING:
5594       t = resolve_ref (e);
5595       break;
5596
5597     case EXPR_CONSTANT:
5598     case EXPR_NULL:
5599       t = SUCCESS;
5600       break;
5601
5602     case EXPR_PPC:
5603       t = resolve_expr_ppc (e);
5604       break;
5605
5606     case EXPR_ARRAY:
5607       t = FAILURE;
5608       if (resolve_ref (e) == FAILURE)
5609         break;
5610
5611       t = gfc_resolve_array_constructor (e);
5612       /* Also try to expand a constructor.  */
5613       if (t == SUCCESS)
5614         {
5615           expression_rank (e);
5616           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
5617             gfc_expand_constructor (e);
5618         }
5619
5620       /* This provides the opportunity for the length of constructors with
5621          character valued function elements to propagate the string length
5622          to the expression.  */
5623       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
5624         {
5625           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
5626              here rather then add a duplicate test for it above.  */ 
5627           gfc_expand_constructor (e);
5628           t = gfc_resolve_character_array_constructor (e);
5629         }
5630
5631       break;
5632
5633     case EXPR_STRUCTURE:
5634       t = resolve_ref (e);
5635       if (t == FAILURE)
5636         break;
5637
5638       t = resolve_structure_cons (e);
5639       if (t == FAILURE)
5640         break;
5641
5642       t = gfc_simplify_expr (e, 0);
5643       break;
5644
5645     default:
5646       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
5647     }
5648
5649   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
5650     fixup_charlen (e);
5651
5652   return t;
5653 }
5654
5655
5656 /* Resolve an expression from an iterator.  They must be scalar and have
5657    INTEGER or (optionally) REAL type.  */
5658
5659 static gfc_try
5660 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
5661                            const char *name_msgid)
5662 {
5663   if (gfc_resolve_expr (expr) == FAILURE)
5664     return FAILURE;
5665
5666   if (expr->rank != 0)
5667     {
5668       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
5669       return FAILURE;
5670     }
5671
5672   if (expr->ts.type != BT_INTEGER)
5673     {
5674       if (expr->ts.type == BT_REAL)
5675         {
5676           if (real_ok)
5677             return gfc_notify_std (GFC_STD_F95_DEL,
5678                                    "Deleted feature: %s at %L must be integer",
5679                                    _(name_msgid), &expr->where);
5680           else
5681             {
5682               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
5683                          &expr->where);
5684               return FAILURE;
5685             }
5686         }
5687       else
5688         {
5689           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
5690           return FAILURE;
5691         }
5692     }
5693   return SUCCESS;
5694 }
5695
5696
5697 /* Resolve the expressions in an iterator structure.  If REAL_OK is
5698    false allow only INTEGER type iterators, otherwise allow REAL types.  */
5699
5700 gfc_try
5701 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
5702 {
5703   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
5704       == FAILURE)
5705     return FAILURE;
5706
5707   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
5708     {
5709       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
5710                  &iter->var->where);
5711       return FAILURE;
5712     }
5713
5714   if (gfc_resolve_iterator_expr (iter->start, real_ok,
5715                                  "Start expression in DO loop") == FAILURE)
5716     return FAILURE;
5717
5718   if (gfc_resolve_iterator_expr (iter->end, real_ok,
5719                                  "End expression in DO loop") == FAILURE)
5720     return FAILURE;
5721
5722   if (gfc_resolve_iterator_expr (iter->step, real_ok,
5723                                  "Step expression in DO loop") == FAILURE)
5724     return FAILURE;
5725
5726   if (iter->step->expr_type == EXPR_CONSTANT)
5727     {
5728       if ((iter->step->ts.type == BT_INTEGER
5729            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
5730           || (iter->step->ts.type == BT_REAL
5731               && mpfr_sgn (iter->step->value.real) == 0))
5732         {
5733           gfc_error ("Step expression in DO loop at %L cannot be zero",
5734                      &iter->step->where);
5735           return FAILURE;
5736         }
5737     }
5738
5739   /* Convert start, end, and step to the same type as var.  */
5740   if (iter->start->ts.kind != iter->var->ts.kind
5741       || iter->start->ts.type != iter->var->ts.type)
5742     gfc_convert_type (iter->start, &iter->var->ts, 2);
5743
5744   if (iter->end->ts.kind != iter->var->ts.kind
5745       || iter->end->ts.type != iter->var->ts.type)
5746     gfc_convert_type (iter->end, &iter->var->ts, 2);
5747
5748   if (iter->step->ts.kind != iter->var->ts.kind
5749       || iter->step->ts.type != iter->var->ts.type)
5750     gfc_convert_type (iter->step, &iter->var->ts, 2);
5751
5752   if (iter->start->expr_type == EXPR_CONSTANT
5753       && iter->end->expr_type == EXPR_CONSTANT
5754       && iter->step->expr_type == EXPR_CONSTANT)
5755     {
5756       int sgn, cmp;
5757       if (iter->start->ts.type == BT_INTEGER)
5758         {
5759           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
5760           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
5761         }
5762       else
5763         {
5764           sgn = mpfr_sgn (iter->step->value.real);
5765           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
5766         }
5767       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
5768         gfc_warning ("DO loop at %L will be executed zero times",
5769                      &iter->step->where);
5770     }
5771
5772   return SUCCESS;
5773 }
5774
5775
5776 /* Traversal function for find_forall_index.  f == 2 signals that
5777    that variable itself is not to be checked - only the references.  */
5778
5779 static bool
5780 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
5781 {
5782   if (expr->expr_type != EXPR_VARIABLE)
5783     return false;
5784   
5785   /* A scalar assignment  */
5786   if (!expr->ref || *f == 1)
5787     {
5788       if (expr->symtree->n.sym == sym)
5789         return true;
5790       else
5791         return false;
5792     }
5793
5794   if (*f == 2)
5795     *f = 1;
5796   return false;
5797 }
5798
5799
5800 /* Check whether the FORALL index appears in the expression or not.
5801    Returns SUCCESS if SYM is found in EXPR.  */
5802
5803 gfc_try
5804 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
5805 {
5806   if (gfc_traverse_expr (expr, sym, forall_index, f))
5807     return SUCCESS;
5808   else
5809     return FAILURE;
5810 }
5811
5812
5813 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
5814    to be a scalar INTEGER variable.  The subscripts and stride are scalar
5815    INTEGERs, and if stride is a constant it must be nonzero.
5816    Furthermore "A subscript or stride in a forall-triplet-spec shall
5817    not contain a reference to any index-name in the
5818    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
5819
5820 static void
5821 resolve_forall_iterators (gfc_forall_iterator *it)
5822 {
5823   gfc_forall_iterator *iter, *iter2;
5824
5825   for (iter = it; iter; iter = iter->next)
5826     {
5827       if (gfc_resolve_expr (iter->var) == SUCCESS
5828           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
5829         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
5830                    &iter->var->where);
5831
5832       if (gfc_resolve_expr (iter->start) == SUCCESS
5833           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
5834         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
5835                    &iter->start->where);
5836       if (iter->var->ts.kind != iter->start->ts.kind)
5837         gfc_convert_type (iter->start, &iter->var->ts, 2);
5838
5839       if (gfc_resolve_expr (iter->end) == SUCCESS
5840           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
5841         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
5842                    &iter->end->where);
5843       if (iter->var->ts.kind != iter->end->ts.kind)
5844         gfc_convert_type (iter->end, &iter->var->ts, 2);
5845
5846       if (gfc_resolve_expr (iter->stride) == SUCCESS)
5847         {
5848           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
5849             gfc_error ("FORALL stride expression at %L must be a scalar %s",
5850                        &iter->stride->where, "INTEGER");
5851
5852           if (iter->stride->expr_type == EXPR_CONSTANT
5853               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
5854             gfc_error ("FORALL stride expression at %L cannot be zero",
5855                        &iter->stride->where);
5856         }
5857       if (iter->var->ts.kind != iter->stride->ts.kind)
5858         gfc_convert_type (iter->stride, &iter->var->ts, 2);
5859     }
5860
5861   for (iter = it; iter; iter = iter->next)
5862     for (iter2 = iter; iter2; iter2 = iter2->next)
5863       {
5864         if (find_forall_index (iter2->start,
5865                                iter->var->symtree->n.sym, 0) == SUCCESS
5866             || find_forall_index (iter2->end,
5867                                   iter->var->symtree->n.sym, 0) == SUCCESS
5868             || find_forall_index (iter2->stride,
5869                                   iter->var->symtree->n.sym, 0) == SUCCESS)
5870           gfc_error ("FORALL index '%s' may not appear in triplet "
5871                      "specification at %L", iter->var->symtree->name,
5872                      &iter2->start->where);
5873       }
5874 }
5875
5876
5877 /* Given a pointer to a symbol that is a derived type, see if it's
5878    inaccessible, i.e. if it's defined in another module and the components are
5879    PRIVATE.  The search is recursive if necessary.  Returns zero if no
5880    inaccessible components are found, nonzero otherwise.  */
5881
5882 static int
5883 derived_inaccessible (gfc_symbol *sym)
5884 {
5885   gfc_component *c;
5886
5887   if (sym->attr.use_assoc && sym->attr.private_comp)
5888     return 1;
5889
5890   for (c = sym->components; c; c = c->next)
5891     {
5892         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
5893           return 1;
5894     }
5895
5896   return 0;
5897 }
5898
5899
5900 /* Resolve the argument of a deallocate expression.  The expression must be
5901    a pointer or a full array.  */
5902
5903 static gfc_try
5904 resolve_deallocate_expr (gfc_expr *e)
5905 {
5906   symbol_attribute attr;
5907   int allocatable, pointer, check_intent_in;
5908   gfc_ref *ref;
5909   gfc_symbol *sym;
5910   gfc_component *c;
5911
5912   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
5913   check_intent_in = 1;
5914
5915   if (gfc_resolve_expr (e) == FAILURE)
5916     return FAILURE;
5917
5918   if (e->expr_type != EXPR_VARIABLE)
5919     goto bad;
5920
5921   sym = e->symtree->n.sym;
5922
5923   if (sym->ts.type == BT_CLASS)
5924     {
5925       allocatable = sym->ts.u.derived->components->attr.allocatable;
5926       pointer = sym->ts.u.derived->components->attr.pointer;
5927     }
5928   else
5929     {
5930       allocatable = sym->attr.allocatable;
5931       pointer = sym->attr.pointer;
5932     }
5933   for (ref = e->ref; ref; ref = ref->next)
5934     {
5935       if (pointer)
5936         check_intent_in = 0;
5937
5938       switch (ref->type)
5939         {
5940         case REF_ARRAY:
5941           if (ref->u.ar.type != AR_FULL)
5942             allocatable = 0;
5943           break;
5944
5945         case REF_COMPONENT:
5946           c = ref->u.c.component;
5947           if (c->ts.type == BT_CLASS)
5948             {
5949               allocatable = c->ts.u.derived->components->attr.allocatable;
5950               pointer = c->ts.u.derived->components->attr.pointer;
5951             }
5952           else
5953             {
5954               allocatable = c->attr.allocatable;
5955               pointer = c->attr.pointer;
5956             }
5957           break;
5958
5959         case REF_SUBSTRING:
5960           allocatable = 0;
5961           break;
5962         }
5963     }
5964
5965   attr = gfc_expr_attr (e);
5966
5967   if (allocatable == 0 && attr.pointer == 0)
5968     {
5969     bad:
5970       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
5971                  &e->where);
5972     }
5973
5974   if (check_intent_in && sym->attr.intent == INTENT_IN)
5975     {
5976       gfc_error ("Cannot deallocate INTENT(IN) variable '%s' at %L",
5977                  sym->name, &e->where);
5978       return FAILURE;
5979     }
5980
5981   if (e->ts.type == BT_CLASS)
5982     {
5983       /* Only deallocate the DATA component.  */
5984       gfc_add_component_ref (e, "$data");
5985     }
5986
5987   return SUCCESS;
5988 }
5989
5990
5991 /* Returns true if the expression e contains a reference to the symbol sym.  */
5992 static bool
5993 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
5994 {
5995   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
5996     return true;
5997
5998   return false;
5999 }
6000
6001 bool
6002 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6003 {
6004   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6005 }
6006
6007
6008 /* Given the expression node e for an allocatable/pointer of derived type to be
6009    allocated, get the expression node to be initialized afterwards (needed for
6010    derived types with default initializers, and derived types with allocatable
6011    components that need nullification.)  */
6012
6013 gfc_expr *
6014 gfc_expr_to_initialize (gfc_expr *e)
6015 {
6016   gfc_expr *result;
6017   gfc_ref *ref;
6018   int i;
6019
6020   result = gfc_copy_expr (e);
6021
6022   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6023   for (ref = result->ref; ref; ref = ref->next)
6024     if (ref->type == REF_ARRAY && ref->next == NULL)
6025       {
6026         ref->u.ar.type = AR_FULL;
6027
6028         for (i = 0; i < ref->u.ar.dimen; i++)
6029           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6030
6031         result->rank = ref->u.ar.dimen;
6032         break;
6033       }
6034
6035   return result;
6036 }
6037
6038
6039 /* Used in resolve_allocate_expr to check that a allocation-object and
6040    a source-expr are conformable.  This does not catch all possible 
6041    cases; in particular a runtime checking is needed.  */
6042
6043 static gfc_try
6044 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6045 {
6046   /* First compare rank.  */
6047   if (e2->ref && e1->rank != e2->ref->u.ar.as->rank)
6048     {
6049       gfc_error ("Source-expr at %L must be scalar or have the "
6050                  "same rank as the allocate-object at %L",
6051                  &e1->where, &e2->where);
6052       return FAILURE;
6053     }
6054
6055   if (e1->shape)
6056     {
6057       int i;
6058       mpz_t s;
6059
6060       mpz_init (s);
6061
6062       for (i = 0; i < e1->rank; i++)
6063         {
6064           if (e2->ref->u.ar.end[i])
6065             {
6066               mpz_set (s, e2->ref->u.ar.end[i]->value.integer);
6067               mpz_sub (s, s, e2->ref->u.ar.start[i]->value.integer);
6068               mpz_add_ui (s, s, 1);
6069             }
6070           else
6071             {
6072               mpz_set (s, e2->ref->u.ar.start[i]->value.integer);
6073             }
6074
6075           if (mpz_cmp (e1->shape[i], s) != 0)
6076             {
6077               gfc_error ("Source-expr at %L and allocate-object at %L must "
6078                          "have the same shape", &e1->where, &e2->where);
6079               mpz_clear (s);
6080               return FAILURE;
6081             }
6082         }
6083
6084       mpz_clear (s);
6085     }
6086
6087   return SUCCESS;
6088 }
6089
6090
6091 /* Resolve the expression in an ALLOCATE statement, doing the additional
6092    checks to see whether the expression is OK or not.  The expression must
6093    have a trailing array reference that gives the size of the array.  */
6094
6095 static gfc_try
6096 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6097 {
6098   int i, pointer, allocatable, dimension, check_intent_in, is_abstract;
6099   symbol_attribute attr;
6100   gfc_ref *ref, *ref2;
6101   gfc_array_ref *ar;
6102   gfc_symbol *sym;
6103   gfc_alloc *a;
6104   gfc_component *c;
6105   gfc_expr *init_e;
6106
6107   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
6108   check_intent_in = 1;
6109
6110   if (gfc_resolve_expr (e) == FAILURE)
6111     return FAILURE;
6112
6113   /* Make sure the expression is allocatable or a pointer.  If it is
6114      pointer, the next-to-last reference must be a pointer.  */
6115
6116   ref2 = NULL;
6117   if (e->symtree)
6118     sym = e->symtree->n.sym;
6119
6120   /* Check whether ultimate component is abstract and CLASS.  */
6121   is_abstract = 0;
6122
6123   if (e->expr_type != EXPR_VARIABLE)
6124     {
6125       allocatable = 0;
6126       attr = gfc_expr_attr (e);
6127       pointer = attr.pointer;
6128       dimension = attr.dimension;
6129     }
6130   else
6131     {
6132       if (sym->ts.type == BT_CLASS)
6133         {
6134           allocatable = sym->ts.u.derived->components->attr.allocatable;
6135           pointer = sym->ts.u.derived->components->attr.pointer;
6136           dimension = sym->ts.u.derived->components->attr.dimension;
6137           is_abstract = sym->ts.u.derived->components->attr.abstract;
6138         }
6139       else
6140         {
6141           allocatable = sym->attr.allocatable;
6142           pointer = sym->attr.pointer;
6143           dimension = sym->attr.dimension;
6144         }
6145
6146       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6147         {
6148           if (pointer)
6149             check_intent_in = 0;
6150
6151           switch (ref->type)
6152             {
6153               case REF_ARRAY:
6154                 if (ref->next != NULL)
6155                   pointer = 0;
6156                 break;
6157
6158               case REF_COMPONENT:
6159                 c = ref->u.c.component;
6160                 if (c->ts.type == BT_CLASS)
6161                   {
6162                     allocatable = c->ts.u.derived->components->attr.allocatable;
6163                     pointer = c->ts.u.derived->components->attr.pointer;
6164                     dimension = c->ts.u.derived->components->attr.dimension;
6165                     is_abstract = c->ts.u.derived->components->attr.abstract;
6166                   }
6167                 else
6168                   {
6169                     allocatable = c->attr.allocatable;
6170                     pointer = c->attr.pointer;
6171                     dimension = c->attr.dimension;
6172                     is_abstract = c->attr.abstract;
6173                   }
6174                 break;
6175
6176               case REF_SUBSTRING:
6177                 allocatable = 0;
6178                 pointer = 0;
6179                 break;
6180             }
6181         }
6182     }
6183
6184   if (allocatable == 0 && pointer == 0)
6185     {
6186       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6187                  &e->where);
6188       return FAILURE;
6189     }
6190
6191   /* Some checks for the SOURCE tag.  */
6192   if (code->expr3)
6193     {
6194       /* Check F03:C631.  */
6195       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6196         {
6197           gfc_error ("Type of entity at %L is type incompatible with "
6198                       "source-expr at %L", &e->where, &code->expr3->where);
6199           return FAILURE;
6200         }
6201
6202       /* Check F03:C632 and restriction following Note 6.18.  */
6203       if (code->expr3->rank > 0
6204           && conformable_arrays (code->expr3, e) == FAILURE)
6205         return FAILURE;
6206
6207       /* Check F03:C633.  */
6208       if (code->expr3->ts.kind != e->ts.kind)
6209         {
6210           gfc_error ("The allocate-object at %L and the source-expr at %L "
6211                       "shall have the same kind type parameter",
6212                       &e->where, &code->expr3->where);
6213           return FAILURE;
6214         }
6215     }
6216   else if (is_abstract&& code->ext.alloc.ts.type == BT_UNKNOWN)
6217     {
6218       gcc_assert (e->ts.type == BT_CLASS);
6219       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6220                  "type-spec or SOURCE=", sym->name, &e->where);
6221       return FAILURE;
6222     }
6223
6224   if (check_intent_in && sym->attr.intent == INTENT_IN)
6225     {
6226       gfc_error ("Cannot allocate INTENT(IN) variable '%s' at %L",
6227                  sym->name, &e->where);
6228       return FAILURE;
6229     }
6230     
6231   if (!code->expr3)
6232     {
6233       /* Add default initializer for those derived types that need them.  */
6234       if (e->ts.type == BT_DERIVED
6235           && (init_e = gfc_default_initializer (&e->ts)))
6236         {
6237           gfc_code *init_st = gfc_get_code ();
6238           init_st->loc = code->loc;
6239           init_st->op = EXEC_INIT_ASSIGN;
6240           init_st->expr1 = gfc_expr_to_initialize (e);
6241           init_st->expr2 = init_e;
6242           init_st->next = code->next;
6243           code->next = init_st;
6244         }
6245       else if (e->ts.type == BT_CLASS
6246                && ((code->ext.alloc.ts.type == BT_UNKNOWN
6247                     && (init_e = gfc_default_initializer (&e->ts.u.derived->components->ts)))
6248                    || (code->ext.alloc.ts.type == BT_DERIVED
6249                        && (init_e = gfc_default_initializer (&code->ext.alloc.ts)))))
6250         {
6251           gfc_code *init_st = gfc_get_code ();
6252           init_st->loc = code->loc;
6253           init_st->op = EXEC_INIT_ASSIGN;
6254           init_st->expr1 = gfc_expr_to_initialize (e);
6255           init_st->expr2 = init_e;
6256           init_st->next = code->next;
6257           code->next = init_st;
6258         }
6259     }
6260
6261   if (pointer || dimension == 0)
6262     return SUCCESS;
6263
6264   /* Make sure the next-to-last reference node is an array specification.  */
6265
6266   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL)
6267     {
6268       gfc_error ("Array specification required in ALLOCATE statement "
6269                  "at %L", &e->where);
6270       return FAILURE;
6271     }
6272
6273   /* Make sure that the array section reference makes sense in the
6274     context of an ALLOCATE specification.  */
6275
6276   ar = &ref2->u.ar;
6277
6278   for (i = 0; i < ar->dimen; i++)
6279     {
6280       if (ref2->u.ar.type == AR_ELEMENT)
6281         goto check_symbols;
6282
6283       switch (ar->dimen_type[i])
6284         {
6285         case DIMEN_ELEMENT:
6286           break;
6287
6288         case DIMEN_RANGE:
6289           if (ar->start[i] != NULL
6290               && ar->end[i] != NULL
6291               && ar->stride[i] == NULL)
6292             break;
6293
6294           /* Fall Through...  */
6295
6296         case DIMEN_UNKNOWN:
6297         case DIMEN_VECTOR:
6298           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6299                      &e->where);
6300           return FAILURE;
6301         }
6302
6303 check_symbols:
6304
6305       for (a = code->ext.alloc.list; a; a = a->next)
6306         {
6307           sym = a->expr->symtree->n.sym;
6308
6309           /* TODO - check derived type components.  */
6310           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6311             continue;
6312
6313           if ((ar->start[i] != NULL
6314                && gfc_find_sym_in_expr (sym, ar->start[i]))
6315               || (ar->end[i] != NULL
6316                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6317             {
6318               gfc_error ("'%s' must not appear in the array specification at "
6319                          "%L in the same ALLOCATE statement where it is "
6320                          "itself allocated", sym->name, &ar->where);
6321               return FAILURE;
6322             }
6323         }
6324     }
6325
6326   return SUCCESS;
6327 }
6328
6329 static void
6330 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6331 {
6332   gfc_expr *stat, *errmsg, *pe, *qe;
6333   gfc_alloc *a, *p, *q;
6334
6335   stat = code->expr1 ? code->expr1 : NULL;
6336
6337   errmsg = code->expr2 ? code->expr2 : NULL;
6338
6339   /* Check the stat variable.  */
6340   if (stat)
6341     {
6342       if (stat->symtree->n.sym->attr.intent == INTENT_IN)
6343         gfc_error ("Stat-variable '%s' at %L cannot be INTENT(IN)",
6344                    stat->symtree->n.sym->name, &stat->where);
6345
6346       if (gfc_pure (NULL) && gfc_impure_variable (stat->symtree->n.sym))
6347         gfc_error ("Illegal stat-variable at %L for a PURE procedure",
6348                    &stat->where);
6349
6350       if ((stat->ts.type != BT_INTEGER
6351            && !(stat->ref && (stat->ref->type == REF_ARRAY
6352                               || stat->ref->type == REF_COMPONENT)))
6353           || stat->rank > 0)
6354         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6355                    "variable", &stat->where);
6356
6357       for (p = code->ext.alloc.list; p; p = p->next)
6358         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6359           gfc_error ("Stat-variable at %L shall not be %sd within "
6360                      "the same %s statement", &stat->where, fcn, fcn);
6361     }
6362
6363   /* Check the errmsg variable.  */
6364   if (errmsg)
6365     {
6366       if (!stat)
6367         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
6368                      &errmsg->where);
6369
6370       if (errmsg->symtree->n.sym->attr.intent == INTENT_IN)
6371         gfc_error ("Errmsg-variable '%s' at %L cannot be INTENT(IN)",
6372                    errmsg->symtree->n.sym->name, &errmsg->where);
6373
6374       if (gfc_pure (NULL) && gfc_impure_variable (errmsg->symtree->n.sym))
6375         gfc_error ("Illegal errmsg-variable at %L for a PURE procedure",
6376                    &errmsg->where);
6377
6378       if ((errmsg->ts.type != BT_CHARACTER
6379            && !(errmsg->ref
6380                 && (errmsg->ref->type == REF_ARRAY
6381                     || errmsg->ref->type == REF_COMPONENT)))
6382           || errmsg->rank > 0 )
6383         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
6384                    "variable", &errmsg->where);
6385
6386       for (p = code->ext.alloc.list; p; p = p->next)
6387         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
6388           gfc_error ("Errmsg-variable at %L shall not be %sd within "
6389                      "the same %s statement", &errmsg->where, fcn, fcn);
6390     }
6391
6392   /* Check that an allocate-object appears only once in the statement.  
6393      FIXME: Checking derived types is disabled.  */
6394   for (p = code->ext.alloc.list; p; p = p->next)
6395     {
6396       pe = p->expr;
6397       if ((pe->ref && pe->ref->type != REF_COMPONENT)
6398            && (pe->symtree->n.sym->ts.type != BT_DERIVED))
6399         {
6400           for (q = p->next; q; q = q->next)
6401             {
6402               qe = q->expr;
6403               if ((qe->ref && qe->ref->type != REF_COMPONENT)
6404                   && (qe->symtree->n.sym->ts.type != BT_DERIVED)
6405                   && (pe->symtree->n.sym->name == qe->symtree->n.sym->name))
6406                 gfc_error ("Allocate-object at %L also appears at %L",
6407                            &pe->where, &qe->where);
6408             }
6409         }
6410     }
6411
6412   if (strcmp (fcn, "ALLOCATE") == 0)
6413     {
6414       for (a = code->ext.alloc.list; a; a = a->next)
6415         resolve_allocate_expr (a->expr, code);
6416     }
6417   else
6418     {
6419       for (a = code->ext.alloc.list; a; a = a->next)
6420         resolve_deallocate_expr (a->expr);
6421     }
6422 }
6423
6424
6425 /************ SELECT CASE resolution subroutines ************/
6426
6427 /* Callback function for our mergesort variant.  Determines interval
6428    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
6429    op1 > op2.  Assumes we're not dealing with the default case.  
6430    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
6431    There are nine situations to check.  */
6432
6433 static int
6434 compare_cases (const gfc_case *op1, const gfc_case *op2)
6435 {
6436   int retval;
6437
6438   if (op1->low == NULL) /* op1 = (:L)  */
6439     {
6440       /* op2 = (:N), so overlap.  */
6441       retval = 0;
6442       /* op2 = (M:) or (M:N),  L < M  */
6443       if (op2->low != NULL
6444           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6445         retval = -1;
6446     }
6447   else if (op1->high == NULL) /* op1 = (K:)  */
6448     {
6449       /* op2 = (M:), so overlap.  */
6450       retval = 0;
6451       /* op2 = (:N) or (M:N), K > N  */
6452       if (op2->high != NULL
6453           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6454         retval = 1;
6455     }
6456   else /* op1 = (K:L)  */
6457     {
6458       if (op2->low == NULL)       /* op2 = (:N), K > N  */
6459         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6460                  ? 1 : 0;
6461       else if (op2->high == NULL) /* op2 = (M:), L < M  */
6462         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6463                  ? -1 : 0;
6464       else                      /* op2 = (M:N)  */
6465         {
6466           retval =  0;
6467           /* L < M  */
6468           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6469             retval =  -1;
6470           /* K > N  */
6471           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6472             retval =  1;
6473         }
6474     }
6475
6476   return retval;
6477 }
6478
6479
6480 /* Merge-sort a double linked case list, detecting overlap in the
6481    process.  LIST is the head of the double linked case list before it
6482    is sorted.  Returns the head of the sorted list if we don't see any
6483    overlap, or NULL otherwise.  */
6484
6485 static gfc_case *
6486 check_case_overlap (gfc_case *list)
6487 {
6488   gfc_case *p, *q, *e, *tail;
6489   int insize, nmerges, psize, qsize, cmp, overlap_seen;
6490
6491   /* If the passed list was empty, return immediately.  */
6492   if (!list)
6493     return NULL;
6494
6495   overlap_seen = 0;
6496   insize = 1;
6497
6498   /* Loop unconditionally.  The only exit from this loop is a return
6499      statement, when we've finished sorting the case list.  */
6500   for (;;)
6501     {
6502       p = list;
6503       list = NULL;
6504       tail = NULL;
6505
6506       /* Count the number of merges we do in this pass.  */
6507       nmerges = 0;
6508
6509       /* Loop while there exists a merge to be done.  */
6510       while (p)
6511         {
6512           int i;
6513
6514           /* Count this merge.  */
6515           nmerges++;
6516
6517           /* Cut the list in two pieces by stepping INSIZE places
6518              forward in the list, starting from P.  */
6519           psize = 0;
6520           q = p;
6521           for (i = 0; i < insize; i++)
6522             {
6523               psize++;
6524               q = q->right;
6525               if (!q)
6526                 break;
6527             }
6528           qsize = insize;
6529
6530           /* Now we have two lists.  Merge them!  */
6531           while (psize > 0 || (qsize > 0 && q != NULL))
6532             {
6533               /* See from which the next case to merge comes from.  */
6534               if (psize == 0)
6535                 {
6536                   /* P is empty so the next case must come from Q.  */
6537                   e = q;
6538                   q = q->right;
6539                   qsize--;
6540                 }
6541               else if (qsize == 0 || q == NULL)
6542                 {
6543                   /* Q is empty.  */
6544                   e = p;
6545                   p = p->right;
6546                   psize--;
6547                 }
6548               else
6549                 {
6550                   cmp = compare_cases (p, q);
6551                   if (cmp < 0)
6552                     {
6553                       /* The whole case range for P is less than the
6554                          one for Q.  */
6555                       e = p;
6556                       p = p->right;
6557                       psize--;
6558                     }
6559                   else if (cmp > 0)
6560                     {
6561                       /* The whole case range for Q is greater than
6562                          the case range for P.  */
6563                       e = q;
6564                       q = q->right;
6565                       qsize--;
6566                     }
6567                   else
6568                     {
6569                       /* The cases overlap, or they are the same
6570                          element in the list.  Either way, we must
6571                          issue an error and get the next case from P.  */
6572                       /* FIXME: Sort P and Q by line number.  */
6573                       gfc_error ("CASE label at %L overlaps with CASE "
6574                                  "label at %L", &p->where, &q->where);
6575                       overlap_seen = 1;
6576                       e = p;
6577                       p = p->right;
6578                       psize--;
6579                     }
6580                 }
6581
6582                 /* Add the next element to the merged list.  */
6583               if (tail)
6584                 tail->right = e;
6585               else
6586                 list = e;
6587               e->left = tail;
6588               tail = e;
6589             }
6590
6591           /* P has now stepped INSIZE places along, and so has Q.  So
6592              they're the same.  */
6593           p = q;
6594         }
6595       tail->right = NULL;
6596
6597       /* If we have done only one merge or none at all, we've
6598          finished sorting the cases.  */
6599       if (nmerges <= 1)
6600         {
6601           if (!overlap_seen)
6602             return list;
6603           else
6604             return NULL;
6605         }
6606
6607       /* Otherwise repeat, merging lists twice the size.  */
6608       insize *= 2;
6609     }
6610 }
6611
6612
6613 /* Check to see if an expression is suitable for use in a CASE statement.
6614    Makes sure that all case expressions are scalar constants of the same
6615    type.  Return FAILURE if anything is wrong.  */
6616
6617 static gfc_try
6618 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
6619 {
6620   if (e == NULL) return SUCCESS;
6621
6622   if (e->ts.type != case_expr->ts.type)
6623     {
6624       gfc_error ("Expression in CASE statement at %L must be of type %s",
6625                  &e->where, gfc_basic_typename (case_expr->ts.type));
6626       return FAILURE;
6627     }
6628
6629   /* C805 (R808) For a given case-construct, each case-value shall be of
6630      the same type as case-expr.  For character type, length differences
6631      are allowed, but the kind type parameters shall be the same.  */
6632
6633   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
6634     {
6635       gfc_error ("Expression in CASE statement at %L must be of kind %d",
6636                  &e->where, case_expr->ts.kind);
6637       return FAILURE;
6638     }
6639
6640   /* Convert the case value kind to that of case expression kind, if needed.
6641      FIXME:  Should a warning be issued?  */
6642   if (e->ts.kind != case_expr->ts.kind)
6643     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
6644
6645   if (e->rank != 0)
6646     {
6647       gfc_error ("Expression in CASE statement at %L must be scalar",
6648                  &e->where);
6649       return FAILURE;
6650     }
6651
6652   return SUCCESS;
6653 }
6654
6655
6656 /* Given a completely parsed select statement, we:
6657
6658      - Validate all expressions and code within the SELECT.
6659      - Make sure that the selection expression is not of the wrong type.
6660      - Make sure that no case ranges overlap.
6661      - Eliminate unreachable cases and unreachable code resulting from
6662        removing case labels.
6663
6664    The standard does allow unreachable cases, e.g. CASE (5:3).  But
6665    they are a hassle for code generation, and to prevent that, we just
6666    cut them out here.  This is not necessary for overlapping cases
6667    because they are illegal and we never even try to generate code.
6668
6669    We have the additional caveat that a SELECT construct could have
6670    been a computed GOTO in the source code. Fortunately we can fairly
6671    easily work around that here: The case_expr for a "real" SELECT CASE
6672    is in code->expr1, but for a computed GOTO it is in code->expr2. All
6673    we have to do is make sure that the case_expr is a scalar integer
6674    expression.  */
6675
6676 static void
6677 resolve_select (gfc_code *code)
6678 {
6679   gfc_code *body;
6680   gfc_expr *case_expr;
6681   gfc_case *cp, *default_case, *tail, *head;
6682   int seen_unreachable;
6683   int seen_logical;
6684   int ncases;
6685   bt type;
6686   gfc_try t;
6687
6688   if (code->expr1 == NULL)
6689     {
6690       /* This was actually a computed GOTO statement.  */
6691       case_expr = code->expr2;
6692       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
6693         gfc_error ("Selection expression in computed GOTO statement "
6694                    "at %L must be a scalar integer expression",
6695                    &case_expr->where);
6696
6697       /* Further checking is not necessary because this SELECT was built
6698          by the compiler, so it should always be OK.  Just move the
6699          case_expr from expr2 to expr so that we can handle computed
6700          GOTOs as normal SELECTs from here on.  */
6701       code->expr1 = code->expr2;
6702       code->expr2 = NULL;
6703       return;
6704     }
6705
6706   case_expr = code->expr1;
6707
6708   type = case_expr->ts.type;
6709   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
6710     {
6711       gfc_error ("Argument of SELECT statement at %L cannot be %s",
6712                  &case_expr->where, gfc_typename (&case_expr->ts));
6713
6714       /* Punt. Going on here just produce more garbage error messages.  */
6715       return;
6716     }
6717
6718   if (case_expr->rank != 0)
6719     {
6720       gfc_error ("Argument of SELECT statement at %L must be a scalar "
6721                  "expression", &case_expr->where);
6722
6723       /* Punt.  */
6724       return;
6725     }
6726
6727   /* PR 19168 has a long discussion concerning a mismatch of the kinds
6728      of the SELECT CASE expression and its CASE values.  Walk the lists
6729      of case values, and if we find a mismatch, promote case_expr to
6730      the appropriate kind.  */
6731
6732   if (type == BT_LOGICAL || type == BT_INTEGER)
6733     {
6734       for (body = code->block; body; body = body->block)
6735         {
6736           /* Walk the case label list.  */
6737           for (cp = body->ext.case_list; cp; cp = cp->next)
6738             {
6739               /* Intercept the DEFAULT case.  It does not have a kind.  */
6740               if (cp->low == NULL && cp->high == NULL)
6741                 continue;
6742
6743               /* Unreachable case ranges are discarded, so ignore.  */
6744               if (cp->low != NULL && cp->high != NULL
6745                   && cp->low != cp->high
6746                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
6747                 continue;
6748
6749               /* FIXME: Should a warning be issued?  */
6750               if (cp->low != NULL
6751                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
6752                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
6753
6754               if (cp->high != NULL
6755                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
6756                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
6757             }
6758          }
6759     }
6760
6761   /* Assume there is no DEFAULT case.  */
6762   default_case = NULL;
6763   head = tail = NULL;
6764   ncases = 0;
6765   seen_logical = 0;
6766
6767   for (body = code->block; body; body = body->block)
6768     {
6769       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
6770       t = SUCCESS;
6771       seen_unreachable = 0;
6772
6773       /* Walk the case label list, making sure that all case labels
6774          are legal.  */
6775       for (cp = body->ext.case_list; cp; cp = cp->next)
6776         {
6777           /* Count the number of cases in the whole construct.  */
6778           ncases++;
6779
6780           /* Intercept the DEFAULT case.  */
6781           if (cp->low == NULL && cp->high == NULL)
6782             {
6783               if (default_case != NULL)
6784                 {
6785                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
6786                              "by a second DEFAULT CASE at %L",
6787                              &default_case->where, &cp->where);
6788                   t = FAILURE;
6789                   break;
6790                 }
6791               else
6792                 {
6793                   default_case = cp;
6794                   continue;
6795                 }
6796             }
6797
6798           /* Deal with single value cases and case ranges.  Errors are
6799              issued from the validation function.  */
6800           if(validate_case_label_expr (cp->low, case_expr) != SUCCESS
6801              || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
6802             {
6803               t = FAILURE;
6804               break;
6805             }
6806
6807           if (type == BT_LOGICAL
6808               && ((cp->low == NULL || cp->high == NULL)
6809                   || cp->low != cp->high))
6810             {
6811               gfc_error ("Logical range in CASE statement at %L is not "
6812                          "allowed", &cp->low->where);
6813               t = FAILURE;
6814               break;
6815             }
6816
6817           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
6818             {
6819               int value;
6820               value = cp->low->value.logical == 0 ? 2 : 1;
6821               if (value & seen_logical)
6822                 {
6823                   gfc_error ("constant logical value in CASE statement "
6824                              "is repeated at %L",
6825                              &cp->low->where);
6826                   t = FAILURE;
6827                   break;
6828                 }
6829               seen_logical |= value;
6830             }
6831
6832           if (cp->low != NULL && cp->high != NULL
6833               && cp->low != cp->high
6834               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
6835             {
6836               if (gfc_option.warn_surprising)
6837                 gfc_warning ("Range specification at %L can never "
6838                              "be matched", &cp->where);
6839
6840               cp->unreachable = 1;
6841               seen_unreachable = 1;
6842             }
6843           else
6844             {
6845               /* If the case range can be matched, it can also overlap with
6846                  other cases.  To make sure it does not, we put it in a
6847                  double linked list here.  We sort that with a merge sort
6848                  later on to detect any overlapping cases.  */
6849               if (!head)
6850                 {
6851                   head = tail = cp;
6852                   head->right = head->left = NULL;
6853                 }
6854               else
6855                 {
6856                   tail->right = cp;
6857                   tail->right->left = tail;
6858                   tail = tail->right;
6859                   tail->right = NULL;
6860                 }
6861             }
6862         }
6863
6864       /* It there was a failure in the previous case label, give up
6865          for this case label list.  Continue with the next block.  */
6866       if (t == FAILURE)
6867         continue;
6868
6869       /* See if any case labels that are unreachable have been seen.
6870          If so, we eliminate them.  This is a bit of a kludge because
6871          the case lists for a single case statement (label) is a
6872          single forward linked lists.  */
6873       if (seen_unreachable)
6874       {
6875         /* Advance until the first case in the list is reachable.  */
6876         while (body->ext.case_list != NULL
6877                && body->ext.case_list->unreachable)
6878           {
6879             gfc_case *n = body->ext.case_list;
6880             body->ext.case_list = body->ext.case_list->next;
6881             n->next = NULL;
6882             gfc_free_case_list (n);
6883           }
6884
6885         /* Strip all other unreachable cases.  */
6886         if (body->ext.case_list)
6887           {
6888             for (cp = body->ext.case_list; cp->next; cp = cp->next)
6889               {
6890                 if (cp->next->unreachable)
6891                   {
6892                     gfc_case *n = cp->next;
6893                     cp->next = cp->next->next;
6894                     n->next = NULL;
6895                     gfc_free_case_list (n);
6896                   }
6897               }
6898           }
6899       }
6900     }
6901
6902   /* See if there were overlapping cases.  If the check returns NULL,
6903      there was overlap.  In that case we don't do anything.  If head
6904      is non-NULL, we prepend the DEFAULT case.  The sorted list can
6905      then used during code generation for SELECT CASE constructs with
6906      a case expression of a CHARACTER type.  */
6907   if (head)
6908     {
6909       head = check_case_overlap (head);
6910
6911       /* Prepend the default_case if it is there.  */
6912       if (head != NULL && default_case)
6913         {
6914           default_case->left = NULL;
6915           default_case->right = head;
6916           head->left = default_case;
6917         }
6918     }
6919
6920   /* Eliminate dead blocks that may be the result if we've seen
6921      unreachable case labels for a block.  */
6922   for (body = code; body && body->block; body = body->block)
6923     {
6924       if (body->block->ext.case_list == NULL)
6925         {
6926           /* Cut the unreachable block from the code chain.  */
6927           gfc_code *c = body->block;
6928           body->block = c->block;
6929
6930           /* Kill the dead block, but not the blocks below it.  */
6931           c->block = NULL;
6932           gfc_free_statements (c);
6933         }
6934     }
6935
6936   /* More than two cases is legal but insane for logical selects.
6937      Issue a warning for it.  */
6938   if (gfc_option.warn_surprising && type == BT_LOGICAL
6939       && ncases > 2)
6940     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
6941                  &code->loc);
6942 }
6943
6944
6945 /* Check if a derived type is extensible.  */
6946
6947 bool
6948 gfc_type_is_extensible (gfc_symbol *sym)
6949 {
6950   return !(sym->attr.is_bind_c || sym->attr.sequence);
6951 }
6952
6953
6954 /* Resolve a SELECT TYPE statement.  */
6955
6956 static void
6957 resolve_select_type (gfc_code *code)
6958 {
6959   gfc_symbol *selector_type;
6960   gfc_code *body, *new_st, *if_st, *tail;
6961   gfc_code *class_is = NULL, *default_case = NULL;
6962   gfc_case *c;
6963   gfc_symtree *st;
6964   char name[GFC_MAX_SYMBOL_LEN];
6965   gfc_namespace *ns;
6966   int error = 0;
6967
6968   ns = code->ext.ns;
6969   gfc_resolve (ns);
6970
6971   if (code->expr2)
6972     selector_type = code->expr2->ts.u.derived->components->ts.u.derived;
6973   else
6974     selector_type = code->expr1->ts.u.derived->components->ts.u.derived;
6975
6976   /* Loop over TYPE IS / CLASS IS cases.  */
6977   for (body = code->block; body; body = body->block)
6978     {
6979       c = body->ext.case_list;
6980
6981       /* Check F03:C815.  */
6982       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
6983           && !gfc_type_is_extensible (c->ts.u.derived))
6984         {
6985           gfc_error ("Derived type '%s' at %L must be extensible",
6986                      c->ts.u.derived->name, &c->where);
6987           error++;
6988           continue;
6989         }
6990
6991       /* Check F03:C816.  */
6992       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
6993           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
6994         {
6995           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
6996                      c->ts.u.derived->name, &c->where, selector_type->name);
6997           error++;
6998           continue;
6999         }
7000
7001       /* Intercept the DEFAULT case.  */
7002       if (c->ts.type == BT_UNKNOWN)
7003         {
7004           /* Check F03:C818.  */
7005           if (default_case)
7006             {
7007               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7008                          "by a second DEFAULT CASE at %L",
7009                          &default_case->ext.case_list->where, &c->where);
7010               error++;
7011               continue;
7012             }
7013           else
7014             default_case = body;
7015         }
7016     }
7017     
7018   if (error>0)
7019     return;
7020
7021   if (code->expr2)
7022     {
7023       /* Insert assignment for selector variable.  */
7024       new_st = gfc_get_code ();
7025       new_st->op = EXEC_ASSIGN;
7026       new_st->expr1 = gfc_copy_expr (code->expr1);
7027       new_st->expr2 = gfc_copy_expr (code->expr2);
7028       ns->code = new_st;
7029     }
7030
7031   /* Put SELECT TYPE statement inside a BLOCK.  */
7032   new_st = gfc_get_code ();
7033   new_st->op = code->op;
7034   new_st->expr1 = code->expr1;
7035   new_st->expr2 = code->expr2;
7036   new_st->block = code->block;
7037   if (!ns->code)
7038     ns->code = new_st;
7039   else
7040     ns->code->next = new_st;
7041   code->op = EXEC_BLOCK;
7042   code->expr1 = code->expr2 =  NULL;
7043   code->block = NULL;
7044
7045   code = new_st;
7046
7047   /* Transform to EXEC_SELECT.  */
7048   code->op = EXEC_SELECT;
7049   gfc_add_component_ref (code->expr1, "$vptr");
7050   gfc_add_component_ref (code->expr1, "$hash");
7051
7052   /* Loop over TYPE IS / CLASS IS cases.  */
7053   for (body = code->block; body; body = body->block)
7054     {
7055       c = body->ext.case_list;
7056       
7057       if (c->ts.type == BT_DERIVED)
7058         c->low = c->high = gfc_int_expr (c->ts.u.derived->hash_value);
7059       else if (c->ts.type == BT_UNKNOWN)
7060         continue;
7061       
7062       /* Assign temporary to selector.  */
7063       if (c->ts.type == BT_CLASS)
7064         sprintf (name, "tmp$class$%s", c->ts.u.derived->name);
7065       else
7066         sprintf (name, "tmp$type$%s", c->ts.u.derived->name);
7067       st = gfc_find_symtree (ns->sym_root, name);
7068       new_st = gfc_get_code ();
7069       new_st->expr1 = gfc_get_variable_expr (st);
7070       new_st->expr2 = gfc_get_variable_expr (code->expr1->symtree);
7071       if (c->ts.type == BT_DERIVED)
7072         {
7073           new_st->op = EXEC_POINTER_ASSIGN;
7074           gfc_add_component_ref (new_st->expr2, "$data");
7075         }
7076       else
7077         new_st->op = EXEC_POINTER_ASSIGN;
7078       new_st->next = body->next;
7079       body->next = new_st;
7080     }
7081     
7082   /* Take out CLASS IS cases for separate treatment.  */
7083   body = code;
7084   while (body && body->block)
7085     {
7086       if (body->block->ext.case_list->ts.type == BT_CLASS)
7087         {
7088           /* Add to class_is list.  */
7089           if (class_is == NULL)
7090             { 
7091               class_is = body->block;
7092               tail = class_is;
7093             }
7094           else
7095             {
7096               for (tail = class_is; tail->block; tail = tail->block) ;
7097               tail->block = body->block;
7098               tail = tail->block;
7099             }
7100           /* Remove from EXEC_SELECT list.  */
7101           body->block = body->block->block;
7102           tail->block = NULL;
7103         }
7104       else
7105         body = body->block;
7106     }
7107
7108   if (class_is)
7109     {
7110       gfc_symbol *vtab;
7111       
7112       if (!default_case)
7113         {
7114           /* Add a default case to hold the CLASS IS cases.  */
7115           for (tail = code; tail->block; tail = tail->block) ;
7116           tail->block = gfc_get_code ();
7117           tail = tail->block;
7118           tail->op = EXEC_SELECT_TYPE;
7119           tail->ext.case_list = gfc_get_case ();
7120           tail->ext.case_list->ts.type = BT_UNKNOWN;
7121           tail->next = NULL;
7122           default_case = tail;
7123         }
7124       
7125       /* More than one CLASS IS block?  */
7126       if (class_is->block)
7127         {
7128           gfc_code **c1,*c2;
7129           bool swapped;
7130           /* Sort CLASS IS blocks by extension level.  */
7131           do
7132             {
7133               swapped = false;
7134               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
7135                 {
7136                   c2 = (*c1)->block;
7137                   /* F03:C817 (check for doubles).  */
7138                   if ((*c1)->ext.case_list->ts.u.derived->hash_value
7139                       == c2->ext.case_list->ts.u.derived->hash_value)
7140                     {
7141                       gfc_error ("Double CLASS IS block in SELECT TYPE "
7142                                  "statement at %L", &c2->ext.case_list->where);
7143                       return;
7144                     }
7145                   if ((*c1)->ext.case_list->ts.u.derived->attr.extension
7146                       < c2->ext.case_list->ts.u.derived->attr.extension)
7147                     {
7148                       /* Swap.  */
7149                       (*c1)->block = c2->block;
7150                       c2->block = *c1;
7151                       *c1 = c2;
7152                       swapped = true;
7153                     }
7154                 }
7155             }
7156           while (swapped);
7157         }
7158         
7159       /* Generate IF chain.  */
7160       if_st = gfc_get_code ();
7161       if_st->op = EXEC_IF;
7162       new_st = if_st;
7163       for (body = class_is; body; body = body->block)
7164         {
7165           new_st->block = gfc_get_code ();
7166           new_st = new_st->block;
7167           new_st->op = EXEC_IF;
7168           /* Set up IF condition: Call _gfortran_is_extension_of.  */
7169           new_st->expr1 = gfc_get_expr ();
7170           new_st->expr1->expr_type = EXPR_FUNCTION;
7171           new_st->expr1->ts.type = BT_LOGICAL;
7172           new_st->expr1->ts.kind = 4;
7173           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
7174           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
7175           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
7176           /* Set up arguments.  */
7177           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
7178           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
7179           gfc_add_component_ref (new_st->expr1->value.function.actual->expr, "$vptr");
7180           vtab = gfc_find_derived_vtab (body->ext.case_list->ts.u.derived);
7181           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
7182           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
7183           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
7184           new_st->next = body->next;
7185         }
7186         if (default_case->next)
7187           {
7188             new_st->block = gfc_get_code ();
7189             new_st = new_st->block;
7190             new_st->op = EXEC_IF;
7191             new_st->next = default_case->next;
7192           }
7193           
7194         /* Replace CLASS DEFAULT code by the IF chain.  */
7195         default_case->next = if_st;
7196     }
7197
7198   resolve_select (code);
7199
7200 }
7201
7202
7203 /* Resolve a transfer statement. This is making sure that:
7204    -- a derived type being transferred has only non-pointer components
7205    -- a derived type being transferred doesn't have private components, unless 
7206       it's being transferred from the module where the type was defined
7207    -- we're not trying to transfer a whole assumed size array.  */
7208
7209 static void
7210 resolve_transfer (gfc_code *code)
7211 {
7212   gfc_typespec *ts;
7213   gfc_symbol *sym;
7214   gfc_ref *ref;
7215   gfc_expr *exp;
7216
7217   exp = code->expr1;
7218
7219   if (exp->expr_type != EXPR_VARIABLE && exp->expr_type != EXPR_FUNCTION)
7220     return;
7221
7222   sym = exp->symtree->n.sym;
7223   ts = &sym->ts;
7224
7225   /* Go to actual component transferred.  */
7226   for (ref = code->expr1->ref; ref; ref = ref->next)
7227     if (ref->type == REF_COMPONENT)
7228       ts = &ref->u.c.component->ts;
7229
7230   if (ts->type == BT_DERIVED)
7231     {
7232       /* Check that transferred derived type doesn't contain POINTER
7233          components.  */
7234       if (ts->u.derived->attr.pointer_comp)
7235         {
7236           gfc_error ("Data transfer element at %L cannot have "
7237                      "POINTER components", &code->loc);
7238           return;
7239         }
7240
7241       if (ts->u.derived->attr.alloc_comp)
7242         {
7243           gfc_error ("Data transfer element at %L cannot have "
7244                      "ALLOCATABLE components", &code->loc);
7245           return;
7246         }
7247
7248       if (derived_inaccessible (ts->u.derived))
7249         {
7250           gfc_error ("Data transfer element at %L cannot have "
7251                      "PRIVATE components",&code->loc);
7252           return;
7253         }
7254     }
7255
7256   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
7257       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
7258     {
7259       gfc_error ("Data transfer element at %L cannot be a full reference to "
7260                  "an assumed-size array", &code->loc);
7261       return;
7262     }
7263 }
7264
7265
7266 /*********** Toplevel code resolution subroutines ***********/
7267
7268 /* Find the set of labels that are reachable from this block.  We also
7269    record the last statement in each block.  */
7270      
7271 static void
7272 find_reachable_labels (gfc_code *block)
7273 {
7274   gfc_code *c;
7275
7276   if (!block)
7277     return;
7278
7279   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
7280
7281   /* Collect labels in this block.  We don't keep those corresponding
7282      to END {IF|SELECT}, these are checked in resolve_branch by going
7283      up through the code_stack.  */
7284   for (c = block; c; c = c->next)
7285     {
7286       if (c->here && c->op != EXEC_END_BLOCK)
7287         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
7288     }
7289
7290   /* Merge with labels from parent block.  */
7291   if (cs_base->prev)
7292     {
7293       gcc_assert (cs_base->prev->reachable_labels);
7294       bitmap_ior_into (cs_base->reachable_labels,
7295                        cs_base->prev->reachable_labels);
7296     }
7297 }
7298
7299 /* Given a branch to a label, see if the branch is conforming.
7300    The code node describes where the branch is located.  */
7301
7302 static void
7303 resolve_branch (gfc_st_label *label, gfc_code *code)
7304 {
7305   code_stack *stack;
7306
7307   if (label == NULL)
7308     return;
7309
7310   /* Step one: is this a valid branching target?  */
7311
7312   if (label->defined == ST_LABEL_UNKNOWN)
7313     {
7314       gfc_error ("Label %d referenced at %L is never defined", label->value,
7315                  &label->where);
7316       return;
7317     }
7318
7319   if (label->defined != ST_LABEL_TARGET)
7320     {
7321       gfc_error ("Statement at %L is not a valid branch target statement "
7322                  "for the branch statement at %L", &label->where, &code->loc);
7323       return;
7324     }
7325
7326   /* Step two: make sure this branch is not a branch to itself ;-)  */
7327
7328   if (code->here == label)
7329     {
7330       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
7331       return;
7332     }
7333
7334   /* Step three:  See if the label is in the same block as the
7335      branching statement.  The hard work has been done by setting up
7336      the bitmap reachable_labels.  */
7337
7338   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
7339     return;
7340
7341   /* Step four:  If we haven't found the label in the bitmap, it may
7342     still be the label of the END of the enclosing block, in which
7343     case we find it by going up the code_stack.  */
7344
7345   for (stack = cs_base; stack; stack = stack->prev)
7346     if (stack->current->next && stack->current->next->here == label)
7347       break;
7348
7349   if (stack)
7350     {
7351       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
7352       return;
7353     }
7354
7355   /* The label is not in an enclosing block, so illegal.  This was
7356      allowed in Fortran 66, so we allow it as extension.  No
7357      further checks are necessary in this case.  */
7358   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
7359                   "as the GOTO statement at %L", &label->where,
7360                   &code->loc);
7361   return;
7362 }
7363
7364
7365 /* Check whether EXPR1 has the same shape as EXPR2.  */
7366
7367 static gfc_try
7368 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
7369 {
7370   mpz_t shape[GFC_MAX_DIMENSIONS];
7371   mpz_t shape2[GFC_MAX_DIMENSIONS];
7372   gfc_try result = FAILURE;
7373   int i;
7374
7375   /* Compare the rank.  */
7376   if (expr1->rank != expr2->rank)
7377     return result;
7378
7379   /* Compare the size of each dimension.  */
7380   for (i=0; i<expr1->rank; i++)
7381     {
7382       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
7383         goto ignore;
7384
7385       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
7386         goto ignore;
7387
7388       if (mpz_cmp (shape[i], shape2[i]))
7389         goto over;
7390     }
7391
7392   /* When either of the two expression is an assumed size array, we
7393      ignore the comparison of dimension sizes.  */
7394 ignore:
7395   result = SUCCESS;
7396
7397 over:
7398   for (i--; i >= 0; i--)
7399     {
7400       mpz_clear (shape[i]);
7401       mpz_clear (shape2[i]);
7402     }
7403   return result;
7404 }
7405
7406
7407 /* Check whether a WHERE assignment target or a WHERE mask expression
7408    has the same shape as the outmost WHERE mask expression.  */
7409
7410 static void
7411 resolve_where (gfc_code *code, gfc_expr *mask)
7412 {
7413   gfc_code *cblock;
7414   gfc_code *cnext;
7415   gfc_expr *e = NULL;
7416
7417   cblock = code->block;
7418
7419   /* Store the first WHERE mask-expr of the WHERE statement or construct.
7420      In case of nested WHERE, only the outmost one is stored.  */
7421   if (mask == NULL) /* outmost WHERE */
7422     e = cblock->expr1;
7423   else /* inner WHERE */
7424     e = mask;
7425
7426   while (cblock)
7427     {
7428       if (cblock->expr1)
7429         {
7430           /* Check if the mask-expr has a consistent shape with the
7431              outmost WHERE mask-expr.  */
7432           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
7433             gfc_error ("WHERE mask at %L has inconsistent shape",
7434                        &cblock->expr1->where);
7435          }
7436
7437       /* the assignment statement of a WHERE statement, or the first
7438          statement in where-body-construct of a WHERE construct */
7439       cnext = cblock->next;
7440       while (cnext)
7441         {
7442           switch (cnext->op)
7443             {
7444             /* WHERE assignment statement */
7445             case EXEC_ASSIGN:
7446
7447               /* Check shape consistent for WHERE assignment target.  */
7448               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
7449                gfc_error ("WHERE assignment target at %L has "
7450                           "inconsistent shape", &cnext->expr1->where);
7451               break;
7452
7453   
7454             case EXEC_ASSIGN_CALL:
7455               resolve_call (cnext);
7456               if (!cnext->resolved_sym->attr.elemental)
7457                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7458                           &cnext->ext.actual->expr->where);
7459               break;
7460
7461             /* WHERE or WHERE construct is part of a where-body-construct */
7462             case EXEC_WHERE:
7463               resolve_where (cnext, e);
7464               break;
7465
7466             default:
7467               gfc_error ("Unsupported statement inside WHERE at %L",
7468                          &cnext->loc);
7469             }
7470          /* the next statement within the same where-body-construct */
7471          cnext = cnext->next;
7472        }
7473     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7474     cblock = cblock->block;
7475   }
7476 }
7477
7478
7479 /* Resolve assignment in FORALL construct.
7480    NVAR is the number of FORALL index variables, and VAR_EXPR records the
7481    FORALL index variables.  */
7482
7483 static void
7484 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
7485 {
7486   int n;
7487
7488   for (n = 0; n < nvar; n++)
7489     {
7490       gfc_symbol *forall_index;
7491
7492       forall_index = var_expr[n]->symtree->n.sym;
7493
7494       /* Check whether the assignment target is one of the FORALL index
7495          variable.  */
7496       if ((code->expr1->expr_type == EXPR_VARIABLE)
7497           && (code->expr1->symtree->n.sym == forall_index))
7498         gfc_error ("Assignment to a FORALL index variable at %L",
7499                    &code->expr1->where);
7500       else
7501         {
7502           /* If one of the FORALL index variables doesn't appear in the
7503              assignment variable, then there could be a many-to-one
7504              assignment.  Emit a warning rather than an error because the
7505              mask could be resolving this problem.  */
7506           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
7507             gfc_warning ("The FORALL with index '%s' is not used on the "
7508                          "left side of the assignment at %L and so might "
7509                          "cause multiple assignment to this object",
7510                          var_expr[n]->symtree->name, &code->expr1->where);
7511         }
7512     }
7513 }
7514
7515
7516 /* Resolve WHERE statement in FORALL construct.  */
7517
7518 static void
7519 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
7520                                   gfc_expr **var_expr)
7521 {
7522   gfc_code *cblock;
7523   gfc_code *cnext;
7524
7525   cblock = code->block;
7526   while (cblock)
7527     {
7528       /* the assignment statement of a WHERE statement, or the first
7529          statement in where-body-construct of a WHERE construct */
7530       cnext = cblock->next;
7531       while (cnext)
7532         {
7533           switch (cnext->op)
7534             {
7535             /* WHERE assignment statement */
7536             case EXEC_ASSIGN:
7537               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
7538               break;
7539   
7540             /* WHERE operator assignment statement */
7541             case EXEC_ASSIGN_CALL:
7542               resolve_call (cnext);
7543               if (!cnext->resolved_sym->attr.elemental)
7544                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7545                           &cnext->ext.actual->expr->where);
7546               break;
7547
7548             /* WHERE or WHERE construct is part of a where-body-construct */
7549             case EXEC_WHERE:
7550               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
7551               break;
7552
7553             default:
7554               gfc_error ("Unsupported statement inside WHERE at %L",
7555                          &cnext->loc);
7556             }
7557           /* the next statement within the same where-body-construct */
7558           cnext = cnext->next;
7559         }
7560       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7561       cblock = cblock->block;
7562     }
7563 }
7564
7565
7566 /* Traverse the FORALL body to check whether the following errors exist:
7567    1. For assignment, check if a many-to-one assignment happens.
7568    2. For WHERE statement, check the WHERE body to see if there is any
7569       many-to-one assignment.  */
7570
7571 static void
7572 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
7573 {
7574   gfc_code *c;
7575
7576   c = code->block->next;
7577   while (c)
7578     {
7579       switch (c->op)
7580         {
7581         case EXEC_ASSIGN:
7582         case EXEC_POINTER_ASSIGN:
7583           gfc_resolve_assign_in_forall (c, nvar, var_expr);
7584           break;
7585
7586         case EXEC_ASSIGN_CALL:
7587           resolve_call (c);
7588           break;
7589
7590         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
7591            there is no need to handle it here.  */
7592         case EXEC_FORALL:
7593           break;
7594         case EXEC_WHERE:
7595           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
7596           break;
7597         default:
7598           break;
7599         }
7600       /* The next statement in the FORALL body.  */
7601       c = c->next;
7602     }
7603 }
7604
7605
7606 /* Counts the number of iterators needed inside a forall construct, including
7607    nested forall constructs. This is used to allocate the needed memory 
7608    in gfc_resolve_forall.  */
7609
7610 static int 
7611 gfc_count_forall_iterators (gfc_code *code)
7612 {
7613   int max_iters, sub_iters, current_iters;
7614   gfc_forall_iterator *fa;
7615
7616   gcc_assert(code->op == EXEC_FORALL);
7617   max_iters = 0;
7618   current_iters = 0;
7619
7620   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7621     current_iters ++;
7622   
7623   code = code->block->next;
7624
7625   while (code)
7626     {          
7627       if (code->op == EXEC_FORALL)
7628         {
7629           sub_iters = gfc_count_forall_iterators (code);
7630           if (sub_iters > max_iters)
7631             max_iters = sub_iters;
7632         }
7633       code = code->next;
7634     }
7635
7636   return current_iters + max_iters;
7637 }
7638
7639
7640 /* Given a FORALL construct, first resolve the FORALL iterator, then call
7641    gfc_resolve_forall_body to resolve the FORALL body.  */
7642
7643 static void
7644 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
7645 {
7646   static gfc_expr **var_expr;
7647   static int total_var = 0;
7648   static int nvar = 0;
7649   int old_nvar, tmp;
7650   gfc_forall_iterator *fa;
7651   int i;
7652
7653   old_nvar = nvar;
7654
7655   /* Start to resolve a FORALL construct   */
7656   if (forall_save == 0)
7657     {
7658       /* Count the total number of FORALL index in the nested FORALL
7659          construct in order to allocate the VAR_EXPR with proper size.  */
7660       total_var = gfc_count_forall_iterators (code);
7661
7662       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
7663       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
7664     }
7665
7666   /* The information about FORALL iterator, including FORALL index start, end
7667      and stride. The FORALL index can not appear in start, end or stride.  */
7668   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7669     {
7670       /* Check if any outer FORALL index name is the same as the current
7671          one.  */
7672       for (i = 0; i < nvar; i++)
7673         {
7674           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
7675             {
7676               gfc_error ("An outer FORALL construct already has an index "
7677                          "with this name %L", &fa->var->where);
7678             }
7679         }
7680
7681       /* Record the current FORALL index.  */
7682       var_expr[nvar] = gfc_copy_expr (fa->var);
7683
7684       nvar++;
7685
7686       /* No memory leak.  */
7687       gcc_assert (nvar <= total_var);
7688     }
7689
7690   /* Resolve the FORALL body.  */
7691   gfc_resolve_forall_body (code, nvar, var_expr);
7692
7693   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
7694   gfc_resolve_blocks (code->block, ns);
7695
7696   tmp = nvar;
7697   nvar = old_nvar;
7698   /* Free only the VAR_EXPRs allocated in this frame.  */
7699   for (i = nvar; i < tmp; i++)
7700      gfc_free_expr (var_expr[i]);
7701
7702   if (nvar == 0)
7703     {
7704       /* We are in the outermost FORALL construct.  */
7705       gcc_assert (forall_save == 0);
7706
7707       /* VAR_EXPR is not needed any more.  */
7708       gfc_free (var_expr);
7709       total_var = 0;
7710     }
7711 }
7712
7713
7714 /* Resolve a BLOCK construct statement.  */
7715
7716 static void
7717 resolve_block_construct (gfc_code* code)
7718 {
7719   /* Eventually, we may want to do some checks here or handle special stuff.
7720      But so far the only thing we can do is resolving the local namespace.  */
7721
7722   gfc_resolve (code->ext.ns);
7723 }
7724
7725
7726 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
7727    DO code nodes.  */
7728
7729 static void resolve_code (gfc_code *, gfc_namespace *);
7730
7731 void
7732 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
7733 {
7734   gfc_try t;
7735
7736   for (; b; b = b->block)
7737     {
7738       t = gfc_resolve_expr (b->expr1);
7739       if (gfc_resolve_expr (b->expr2) == FAILURE)
7740         t = FAILURE;
7741
7742       switch (b->op)
7743         {
7744         case EXEC_IF:
7745           if (t == SUCCESS && b->expr1 != NULL
7746               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
7747             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
7748                        &b->expr1->where);
7749           break;
7750
7751         case EXEC_WHERE:
7752           if (t == SUCCESS
7753               && b->expr1 != NULL
7754               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
7755             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
7756                        &b->expr1->where);
7757           break;
7758
7759         case EXEC_GOTO:
7760           resolve_branch (b->label1, b);
7761           break;
7762
7763         case EXEC_BLOCK:
7764           resolve_block_construct (b);
7765           break;
7766
7767         case EXEC_SELECT:
7768         case EXEC_SELECT_TYPE:
7769         case EXEC_FORALL:
7770         case EXEC_DO:
7771         case EXEC_DO_WHILE:
7772         case EXEC_READ:
7773         case EXEC_WRITE:
7774         case EXEC_IOLENGTH:
7775         case EXEC_WAIT:
7776           break;
7777
7778         case EXEC_OMP_ATOMIC:
7779         case EXEC_OMP_CRITICAL:
7780         case EXEC_OMP_DO:
7781         case EXEC_OMP_MASTER:
7782         case EXEC_OMP_ORDERED:
7783         case EXEC_OMP_PARALLEL:
7784         case EXEC_OMP_PARALLEL_DO:
7785         case EXEC_OMP_PARALLEL_SECTIONS:
7786         case EXEC_OMP_PARALLEL_WORKSHARE:
7787         case EXEC_OMP_SECTIONS:
7788         case EXEC_OMP_SINGLE:
7789         case EXEC_OMP_TASK:
7790         case EXEC_OMP_TASKWAIT:
7791         case EXEC_OMP_WORKSHARE:
7792           break;
7793
7794         default:
7795           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
7796         }
7797
7798       resolve_code (b->next, ns);
7799     }
7800 }
7801
7802
7803 /* Does everything to resolve an ordinary assignment.  Returns true
7804    if this is an interface assignment.  */
7805 static bool
7806 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
7807 {
7808   bool rval = false;
7809   gfc_expr *lhs;
7810   gfc_expr *rhs;
7811   int llen = 0;
7812   int rlen = 0;
7813   int n;
7814   gfc_ref *ref;
7815
7816   if (gfc_extend_assign (code, ns) == SUCCESS)
7817     {
7818       gfc_expr** rhsptr;
7819
7820       if (code->op == EXEC_ASSIGN_CALL)
7821         {
7822           lhs = code->ext.actual->expr;
7823           rhsptr = &code->ext.actual->next->expr;
7824         }
7825       else
7826         {
7827           gfc_actual_arglist* args;
7828           gfc_typebound_proc* tbp;
7829
7830           gcc_assert (code->op == EXEC_COMPCALL);
7831
7832           args = code->expr1->value.compcall.actual;
7833           lhs = args->expr;
7834           rhsptr = &args->next->expr;
7835
7836           tbp = code->expr1->value.compcall.tbp;
7837           gcc_assert (!tbp->is_generic);
7838         }
7839
7840       /* Make a temporary rhs when there is a default initializer
7841          and rhs is the same symbol as the lhs.  */
7842       if ((*rhsptr)->expr_type == EXPR_VARIABLE
7843             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
7844             && has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
7845             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
7846         *rhsptr = gfc_get_parentheses (*rhsptr);
7847
7848       return true;
7849     }
7850
7851   lhs = code->expr1;
7852   rhs = code->expr2;
7853
7854   if (rhs->is_boz
7855       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
7856                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
7857                          &code->loc) == FAILURE)
7858     return false;
7859
7860   /* Handle the case of a BOZ literal on the RHS.  */
7861   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
7862     {
7863       int rc;
7864       if (gfc_option.warn_surprising)
7865         gfc_warning ("BOZ literal at %L is bitwise transferred "
7866                      "non-integer symbol '%s'", &code->loc,
7867                      lhs->symtree->n.sym->name);
7868
7869       if (!gfc_convert_boz (rhs, &lhs->ts))
7870         return false;
7871       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
7872         {
7873           if (rc == ARITH_UNDERFLOW)
7874             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
7875                        ". This check can be disabled with the option "
7876                        "-fno-range-check", &rhs->where);
7877           else if (rc == ARITH_OVERFLOW)
7878             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
7879                        ". This check can be disabled with the option "
7880                        "-fno-range-check", &rhs->where);
7881           else if (rc == ARITH_NAN)
7882             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
7883                        ". This check can be disabled with the option "
7884                        "-fno-range-check", &rhs->where);
7885           return false;
7886         }
7887     }
7888
7889
7890   if (lhs->ts.type == BT_CHARACTER
7891         && gfc_option.warn_character_truncation)
7892     {
7893       if (lhs->ts.u.cl != NULL
7894             && lhs->ts.u.cl->length != NULL
7895             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
7896         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
7897
7898       if (rhs->expr_type == EXPR_CONSTANT)
7899         rlen = rhs->value.character.length;
7900
7901       else if (rhs->ts.u.cl != NULL
7902                  && rhs->ts.u.cl->length != NULL
7903                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
7904         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
7905
7906       if (rlen && llen && rlen > llen)
7907         gfc_warning_now ("CHARACTER expression will be truncated "
7908                          "in assignment (%d/%d) at %L",
7909                          llen, rlen, &code->loc);
7910     }
7911
7912   /* Ensure that a vector index expression for the lvalue is evaluated
7913      to a temporary if the lvalue symbol is referenced in it.  */
7914   if (lhs->rank)
7915     {
7916       for (ref = lhs->ref; ref; ref= ref->next)
7917         if (ref->type == REF_ARRAY)
7918           {
7919             for (n = 0; n < ref->u.ar.dimen; n++)
7920               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
7921                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
7922                                            ref->u.ar.start[n]))
7923                 ref->u.ar.start[n]
7924                         = gfc_get_parentheses (ref->u.ar.start[n]);
7925           }
7926     }
7927
7928   if (gfc_pure (NULL))
7929     {
7930       if (gfc_impure_variable (lhs->symtree->n.sym))
7931         {
7932           gfc_error ("Cannot assign to variable '%s' in PURE "
7933                      "procedure at %L",
7934                       lhs->symtree->n.sym->name,
7935                       &lhs->where);
7936           return rval;
7937         }
7938
7939       if (lhs->ts.type == BT_DERIVED
7940             && lhs->expr_type == EXPR_VARIABLE
7941             && lhs->ts.u.derived->attr.pointer_comp
7942             && gfc_impure_variable (rhs->symtree->n.sym))
7943         {
7944           gfc_error ("The impure variable at %L is assigned to "
7945                      "a derived type variable with a POINTER "
7946                      "component in a PURE procedure (12.6)",
7947                      &rhs->where);
7948           return rval;
7949         }
7950     }
7951
7952   /* F03:7.4.1.2.  */
7953   if (lhs->ts.type == BT_CLASS)
7954     {
7955       gfc_error ("Variable must not be polymorphic in assignment at %L",
7956                  &lhs->where);
7957       return false;
7958     }
7959
7960   gfc_check_assign (lhs, rhs, 1);
7961   return false;
7962 }
7963
7964
7965 /* Given a block of code, recursively resolve everything pointed to by this
7966    code block.  */
7967
7968 static void
7969 resolve_code (gfc_code *code, gfc_namespace *ns)
7970 {
7971   int omp_workshare_save;
7972   int forall_save;
7973   code_stack frame;
7974   gfc_try t;
7975
7976   frame.prev = cs_base;
7977   frame.head = code;
7978   cs_base = &frame;
7979
7980   find_reachable_labels (code);
7981
7982   for (; code; code = code->next)
7983     {
7984       frame.current = code;
7985       forall_save = forall_flag;
7986
7987       if (code->op == EXEC_FORALL)
7988         {
7989           forall_flag = 1;
7990           gfc_resolve_forall (code, ns, forall_save);
7991           forall_flag = 2;
7992         }
7993       else if (code->block)
7994         {
7995           omp_workshare_save = -1;
7996           switch (code->op)
7997             {
7998             case EXEC_OMP_PARALLEL_WORKSHARE:
7999               omp_workshare_save = omp_workshare_flag;
8000               omp_workshare_flag = 1;
8001               gfc_resolve_omp_parallel_blocks (code, ns);
8002               break;
8003             case EXEC_OMP_PARALLEL:
8004             case EXEC_OMP_PARALLEL_DO:
8005             case EXEC_OMP_PARALLEL_SECTIONS:
8006             case EXEC_OMP_TASK:
8007               omp_workshare_save = omp_workshare_flag;
8008               omp_workshare_flag = 0;
8009               gfc_resolve_omp_parallel_blocks (code, ns);
8010               break;
8011             case EXEC_OMP_DO:
8012               gfc_resolve_omp_do_blocks (code, ns);
8013               break;
8014             case EXEC_SELECT_TYPE:
8015               gfc_current_ns = code->ext.ns;
8016               gfc_resolve_blocks (code->block, gfc_current_ns);
8017               gfc_current_ns = ns;
8018               break;
8019             case EXEC_OMP_WORKSHARE:
8020               omp_workshare_save = omp_workshare_flag;
8021               omp_workshare_flag = 1;
8022               /* FALLTHROUGH */
8023             default:
8024               gfc_resolve_blocks (code->block, ns);
8025               break;
8026             }
8027
8028           if (omp_workshare_save != -1)
8029             omp_workshare_flag = omp_workshare_save;
8030         }
8031
8032       t = SUCCESS;
8033       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
8034         t = gfc_resolve_expr (code->expr1);
8035       forall_flag = forall_save;
8036
8037       if (gfc_resolve_expr (code->expr2) == FAILURE)
8038         t = FAILURE;
8039
8040       if (code->op == EXEC_ALLOCATE
8041           && gfc_resolve_expr (code->expr3) == FAILURE)
8042         t = FAILURE;
8043
8044       switch (code->op)
8045         {
8046         case EXEC_NOP:
8047         case EXEC_END_BLOCK:
8048         case EXEC_CYCLE:
8049         case EXEC_PAUSE:
8050         case EXEC_STOP:
8051         case EXEC_EXIT:
8052         case EXEC_CONTINUE:
8053         case EXEC_DT_END:
8054         case EXEC_ASSIGN_CALL:
8055           break;
8056
8057         case EXEC_ENTRY:
8058           /* Keep track of which entry we are up to.  */
8059           current_entry_id = code->ext.entry->id;
8060           break;
8061
8062         case EXEC_WHERE:
8063           resolve_where (code, NULL);
8064           break;
8065
8066         case EXEC_GOTO:
8067           if (code->expr1 != NULL)
8068             {
8069               if (code->expr1->ts.type != BT_INTEGER)
8070                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
8071                            "INTEGER variable", &code->expr1->where);
8072               else if (code->expr1->symtree->n.sym->attr.assign != 1)
8073                 gfc_error ("Variable '%s' has not been assigned a target "
8074                            "label at %L", code->expr1->symtree->n.sym->name,
8075                            &code->expr1->where);
8076             }
8077           else
8078             resolve_branch (code->label1, code);
8079           break;
8080
8081         case EXEC_RETURN:
8082           if (code->expr1 != NULL
8083                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
8084             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
8085                        "INTEGER return specifier", &code->expr1->where);
8086           break;
8087
8088         case EXEC_INIT_ASSIGN:
8089         case EXEC_END_PROCEDURE:
8090           break;
8091
8092         case EXEC_ASSIGN:
8093           if (t == FAILURE)
8094             break;
8095
8096           if (resolve_ordinary_assign (code, ns))
8097             {
8098               if (code->op == EXEC_COMPCALL)
8099                 goto compcall;
8100               else
8101                 goto call;
8102             }
8103           break;
8104
8105         case EXEC_LABEL_ASSIGN:
8106           if (code->label1->defined == ST_LABEL_UNKNOWN)
8107             gfc_error ("Label %d referenced at %L is never defined",
8108                        code->label1->value, &code->label1->where);
8109           if (t == SUCCESS
8110               && (code->expr1->expr_type != EXPR_VARIABLE
8111                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
8112                   || code->expr1->symtree->n.sym->ts.kind
8113                      != gfc_default_integer_kind
8114                   || code->expr1->symtree->n.sym->as != NULL))
8115             gfc_error ("ASSIGN statement at %L requires a scalar "
8116                        "default INTEGER variable", &code->expr1->where);
8117           break;
8118
8119         case EXEC_POINTER_ASSIGN:
8120           if (t == FAILURE)
8121             break;
8122
8123           gfc_check_pointer_assign (code->expr1, code->expr2);
8124           break;
8125
8126         case EXEC_ARITHMETIC_IF:
8127           if (t == SUCCESS
8128               && code->expr1->ts.type != BT_INTEGER
8129               && code->expr1->ts.type != BT_REAL)
8130             gfc_error ("Arithmetic IF statement at %L requires a numeric "
8131                        "expression", &code->expr1->where);
8132
8133           resolve_branch (code->label1, code);
8134           resolve_branch (code->label2, code);
8135           resolve_branch (code->label3, code);
8136           break;
8137
8138         case EXEC_IF:
8139           if (t == SUCCESS && code->expr1 != NULL
8140               && (code->expr1->ts.type != BT_LOGICAL
8141                   || code->expr1->rank != 0))
8142             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8143                        &code->expr1->where);
8144           break;
8145
8146         case EXEC_CALL:
8147         call:
8148           resolve_call (code);
8149           break;
8150
8151         case EXEC_COMPCALL:
8152         compcall:
8153           if (code->expr1->symtree
8154                 && code->expr1->symtree->n.sym->ts.type == BT_CLASS)
8155             resolve_class_typebound_call (code);
8156           else
8157             resolve_typebound_call (code);
8158           break;
8159
8160         case EXEC_CALL_PPC:
8161           resolve_ppc_call (code);
8162           break;
8163
8164         case EXEC_SELECT:
8165           /* Select is complicated. Also, a SELECT construct could be
8166              a transformed computed GOTO.  */
8167           resolve_select (code);
8168           break;
8169
8170         case EXEC_SELECT_TYPE:
8171           resolve_select_type (code);
8172           break;
8173
8174         case EXEC_BLOCK:
8175           gfc_resolve (code->ext.ns);
8176           break;
8177
8178         case EXEC_DO:
8179           if (code->ext.iterator != NULL)
8180             {
8181               gfc_iterator *iter = code->ext.iterator;
8182               if (gfc_resolve_iterator (iter, true) != FAILURE)
8183                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
8184             }
8185           break;
8186
8187         case EXEC_DO_WHILE:
8188           if (code->expr1 == NULL)
8189             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
8190           if (t == SUCCESS
8191               && (code->expr1->rank != 0
8192                   || code->expr1->ts.type != BT_LOGICAL))
8193             gfc_error ("Exit condition of DO WHILE loop at %L must be "
8194                        "a scalar LOGICAL expression", &code->expr1->where);
8195           break;
8196
8197         case EXEC_ALLOCATE:
8198           if (t == SUCCESS)
8199             resolve_allocate_deallocate (code, "ALLOCATE");
8200
8201           break;
8202
8203         case EXEC_DEALLOCATE:
8204           if (t == SUCCESS)
8205             resolve_allocate_deallocate (code, "DEALLOCATE");
8206
8207           break;
8208
8209         case EXEC_OPEN:
8210           if (gfc_resolve_open (code->ext.open) == FAILURE)
8211             break;
8212
8213           resolve_branch (code->ext.open->err, code);
8214           break;
8215
8216         case EXEC_CLOSE:
8217           if (gfc_resolve_close (code->ext.close) == FAILURE)
8218             break;
8219
8220           resolve_branch (code->ext.close->err, code);
8221           break;
8222
8223         case EXEC_BACKSPACE:
8224         case EXEC_ENDFILE:
8225         case EXEC_REWIND:
8226         case EXEC_FLUSH:
8227           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
8228             break;
8229
8230           resolve_branch (code->ext.filepos->err, code);
8231           break;
8232
8233         case EXEC_INQUIRE:
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_IOLENGTH:
8241           gcc_assert (code->ext.inquire != NULL);
8242           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8243             break;
8244
8245           resolve_branch (code->ext.inquire->err, code);
8246           break;
8247
8248         case EXEC_WAIT:
8249           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
8250             break;
8251
8252           resolve_branch (code->ext.wait->err, code);
8253           resolve_branch (code->ext.wait->end, code);
8254           resolve_branch (code->ext.wait->eor, code);
8255           break;
8256
8257         case EXEC_READ:
8258         case EXEC_WRITE:
8259           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
8260             break;
8261
8262           resolve_branch (code->ext.dt->err, code);
8263           resolve_branch (code->ext.dt->end, code);
8264           resolve_branch (code->ext.dt->eor, code);
8265           break;
8266
8267         case EXEC_TRANSFER:
8268           resolve_transfer (code);
8269           break;
8270
8271         case EXEC_FORALL:
8272           resolve_forall_iterators (code->ext.forall_iterator);
8273
8274           if (code->expr1 != NULL && code->expr1->ts.type != BT_LOGICAL)
8275             gfc_error ("FORALL mask clause at %L requires a LOGICAL "
8276                        "expression", &code->expr1->where);
8277           break;
8278
8279         case EXEC_OMP_ATOMIC:
8280         case EXEC_OMP_BARRIER:
8281         case EXEC_OMP_CRITICAL:
8282         case EXEC_OMP_FLUSH:
8283         case EXEC_OMP_DO:
8284         case EXEC_OMP_MASTER:
8285         case EXEC_OMP_ORDERED:
8286         case EXEC_OMP_SECTIONS:
8287         case EXEC_OMP_SINGLE:
8288         case EXEC_OMP_TASKWAIT:
8289         case EXEC_OMP_WORKSHARE:
8290           gfc_resolve_omp_directive (code, ns);
8291           break;
8292
8293         case EXEC_OMP_PARALLEL:
8294         case EXEC_OMP_PARALLEL_DO:
8295         case EXEC_OMP_PARALLEL_SECTIONS:
8296         case EXEC_OMP_PARALLEL_WORKSHARE:
8297         case EXEC_OMP_TASK:
8298           omp_workshare_save = omp_workshare_flag;
8299           omp_workshare_flag = 0;
8300           gfc_resolve_omp_directive (code, ns);
8301           omp_workshare_flag = omp_workshare_save;
8302           break;
8303
8304         default:
8305           gfc_internal_error ("resolve_code(): Bad statement code");
8306         }
8307     }
8308
8309   cs_base = frame.prev;
8310 }
8311
8312
8313 /* Resolve initial values and make sure they are compatible with
8314    the variable.  */
8315
8316 static void
8317 resolve_values (gfc_symbol *sym)
8318 {
8319   if (sym->value == NULL)
8320     return;
8321
8322   if (gfc_resolve_expr (sym->value) == FAILURE)
8323     return;
8324
8325   gfc_check_assign_symbol (sym, sym->value);
8326 }
8327
8328
8329 /* Verify the binding labels for common blocks that are BIND(C).  The label
8330    for a BIND(C) common block must be identical in all scoping units in which
8331    the common block is declared.  Further, the binding label can not collide
8332    with any other global entity in the program.  */
8333
8334 static void
8335 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
8336 {
8337   if (comm_block_tree->n.common->is_bind_c == 1)
8338     {
8339       gfc_gsymbol *binding_label_gsym;
8340       gfc_gsymbol *comm_name_gsym;
8341
8342       /* See if a global symbol exists by the common block's name.  It may
8343          be NULL if the common block is use-associated.  */
8344       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
8345                                          comm_block_tree->n.common->name);
8346       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
8347         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
8348                    "with the global entity '%s' at %L",
8349                    comm_block_tree->n.common->binding_label,
8350                    comm_block_tree->n.common->name,
8351                    &(comm_block_tree->n.common->where),
8352                    comm_name_gsym->name, &(comm_name_gsym->where));
8353       else if (comm_name_gsym != NULL
8354                && strcmp (comm_name_gsym->name,
8355                           comm_block_tree->n.common->name) == 0)
8356         {
8357           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
8358              as expected.  */
8359           if (comm_name_gsym->binding_label == NULL)
8360             /* No binding label for common block stored yet; save this one.  */
8361             comm_name_gsym->binding_label =
8362               comm_block_tree->n.common->binding_label;
8363           else
8364             if (strcmp (comm_name_gsym->binding_label,
8365                         comm_block_tree->n.common->binding_label) != 0)
8366               {
8367                 /* Common block names match but binding labels do not.  */
8368                 gfc_error ("Binding label '%s' for common block '%s' at %L "
8369                            "does not match the binding label '%s' for common "
8370                            "block '%s' at %L",
8371                            comm_block_tree->n.common->binding_label,
8372                            comm_block_tree->n.common->name,
8373                            &(comm_block_tree->n.common->where),
8374                            comm_name_gsym->binding_label,
8375                            comm_name_gsym->name,
8376                            &(comm_name_gsym->where));
8377                 return;
8378               }
8379         }
8380
8381       /* There is no binding label (NAME="") so we have nothing further to
8382          check and nothing to add as a global symbol for the label.  */
8383       if (comm_block_tree->n.common->binding_label[0] == '\0' )
8384         return;
8385       
8386       binding_label_gsym =
8387         gfc_find_gsymbol (gfc_gsym_root,
8388                           comm_block_tree->n.common->binding_label);
8389       if (binding_label_gsym == NULL)
8390         {
8391           /* Need to make a global symbol for the binding label to prevent
8392              it from colliding with another.  */
8393           binding_label_gsym =
8394             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
8395           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
8396           binding_label_gsym->type = GSYM_COMMON;
8397         }
8398       else
8399         {
8400           /* If comm_name_gsym is NULL, the name common block is use
8401              associated and the name could be colliding.  */
8402           if (binding_label_gsym->type != GSYM_COMMON)
8403             gfc_error ("Binding label '%s' for common block '%s' at %L "
8404                        "collides with the global entity '%s' at %L",
8405                        comm_block_tree->n.common->binding_label,
8406                        comm_block_tree->n.common->name,
8407                        &(comm_block_tree->n.common->where),
8408                        binding_label_gsym->name,
8409                        &(binding_label_gsym->where));
8410           else if (comm_name_gsym != NULL
8411                    && (strcmp (binding_label_gsym->name,
8412                                comm_name_gsym->binding_label) != 0)
8413                    && (strcmp (binding_label_gsym->sym_name,
8414                                comm_name_gsym->name) != 0))
8415             gfc_error ("Binding label '%s' for common block '%s' at %L "
8416                        "collides with global entity '%s' at %L",
8417                        binding_label_gsym->name, binding_label_gsym->sym_name,
8418                        &(comm_block_tree->n.common->where),
8419                        comm_name_gsym->name, &(comm_name_gsym->where));
8420         }
8421     }
8422   
8423   return;
8424 }
8425
8426
8427 /* Verify any BIND(C) derived types in the namespace so we can report errors
8428    for them once, rather than for each variable declared of that type.  */
8429
8430 static void
8431 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
8432 {
8433   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
8434       && derived_sym->attr.is_bind_c == 1)
8435     verify_bind_c_derived_type (derived_sym);
8436   
8437   return;
8438 }
8439
8440
8441 /* Verify that any binding labels used in a given namespace do not collide 
8442    with the names or binding labels of any global symbols.  */
8443
8444 static void
8445 gfc_verify_binding_labels (gfc_symbol *sym)
8446 {
8447   int has_error = 0;
8448   
8449   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
8450       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
8451     {
8452       gfc_gsymbol *bind_c_sym;
8453
8454       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
8455       if (bind_c_sym != NULL 
8456           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
8457         {
8458           if (sym->attr.if_source == IFSRC_DECL 
8459               && (bind_c_sym->type != GSYM_SUBROUTINE 
8460                   && bind_c_sym->type != GSYM_FUNCTION) 
8461               && ((sym->attr.contained == 1 
8462                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
8463                   || (sym->attr.use_assoc == 1 
8464                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
8465             {
8466               /* Make sure global procedures don't collide with anything.  */
8467               gfc_error ("Binding label '%s' at %L collides with the global "
8468                          "entity '%s' at %L", sym->binding_label,
8469                          &(sym->declared_at), bind_c_sym->name,
8470                          &(bind_c_sym->where));
8471               has_error = 1;
8472             }
8473           else if (sym->attr.contained == 0 
8474                    && (sym->attr.if_source == IFSRC_IFBODY 
8475                        && sym->attr.flavor == FL_PROCEDURE) 
8476                    && (bind_c_sym->sym_name != NULL 
8477                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
8478             {
8479               /* Make sure procedures in interface bodies don't collide.  */
8480               gfc_error ("Binding label '%s' in interface body at %L collides "
8481                          "with the global entity '%s' at %L",
8482                          sym->binding_label,
8483                          &(sym->declared_at), bind_c_sym->name,
8484                          &(bind_c_sym->where));
8485               has_error = 1;
8486             }
8487           else if (sym->attr.contained == 0 
8488                    && sym->attr.if_source == IFSRC_UNKNOWN)
8489             if ((sym->attr.use_assoc && bind_c_sym->mod_name
8490                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
8491                 || sym->attr.use_assoc == 0)
8492               {
8493                 gfc_error ("Binding label '%s' at %L collides with global "
8494                            "entity '%s' at %L", sym->binding_label,
8495                            &(sym->declared_at), bind_c_sym->name,
8496                            &(bind_c_sym->where));
8497                 has_error = 1;
8498               }
8499
8500           if (has_error != 0)
8501             /* Clear the binding label to prevent checking multiple times.  */
8502             sym->binding_label[0] = '\0';
8503         }
8504       else if (bind_c_sym == NULL)
8505         {
8506           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
8507           bind_c_sym->where = sym->declared_at;
8508           bind_c_sym->sym_name = sym->name;
8509
8510           if (sym->attr.use_assoc == 1)
8511             bind_c_sym->mod_name = sym->module;
8512           else
8513             if (sym->ns->proc_name != NULL)
8514               bind_c_sym->mod_name = sym->ns->proc_name->name;
8515
8516           if (sym->attr.contained == 0)
8517             {
8518               if (sym->attr.subroutine)
8519                 bind_c_sym->type = GSYM_SUBROUTINE;
8520               else if (sym->attr.function)
8521                 bind_c_sym->type = GSYM_FUNCTION;
8522             }
8523         }
8524     }
8525   return;
8526 }
8527
8528
8529 /* Resolve an index expression.  */
8530
8531 static gfc_try
8532 resolve_index_expr (gfc_expr *e)
8533 {
8534   if (gfc_resolve_expr (e) == FAILURE)
8535     return FAILURE;
8536
8537   if (gfc_simplify_expr (e, 0) == FAILURE)
8538     return FAILURE;
8539
8540   if (gfc_specification_expr (e) == FAILURE)
8541     return FAILURE;
8542
8543   return SUCCESS;
8544 }
8545
8546 /* Resolve a charlen structure.  */
8547
8548 static gfc_try
8549 resolve_charlen (gfc_charlen *cl)
8550 {
8551   int i, k;
8552
8553   if (cl->resolved)
8554     return SUCCESS;
8555
8556   cl->resolved = 1;
8557
8558   specification_expr = 1;
8559
8560   if (resolve_index_expr (cl->length) == FAILURE)
8561     {
8562       specification_expr = 0;
8563       return FAILURE;
8564     }
8565
8566   /* "If the character length parameter value evaluates to a negative
8567      value, the length of character entities declared is zero."  */
8568   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
8569     {
8570       if (gfc_option.warn_surprising)
8571         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
8572                          " the length has been set to zero",
8573                          &cl->length->where, i);
8574       gfc_replace_expr (cl->length, gfc_int_expr (0));
8575     }
8576
8577   /* Check that the character length is not too large.  */
8578   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
8579   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
8580       && cl->length->ts.type == BT_INTEGER
8581       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
8582     {
8583       gfc_error ("String length at %L is too large", &cl->length->where);
8584       return FAILURE;
8585     }
8586
8587   return SUCCESS;
8588 }
8589
8590
8591 /* Test for non-constant shape arrays.  */
8592
8593 static bool
8594 is_non_constant_shape_array (gfc_symbol *sym)
8595 {
8596   gfc_expr *e;
8597   int i;
8598   bool not_constant;
8599
8600   not_constant = false;
8601   if (sym->as != NULL)
8602     {
8603       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
8604          has not been simplified; parameter array references.  Do the
8605          simplification now.  */
8606       for (i = 0; i < sym->as->rank; i++)
8607         {
8608           e = sym->as->lower[i];
8609           if (e && (resolve_index_expr (e) == FAILURE
8610                     || !gfc_is_constant_expr (e)))
8611             not_constant = true;
8612
8613           e = sym->as->upper[i];
8614           if (e && (resolve_index_expr (e) == FAILURE
8615                     || !gfc_is_constant_expr (e)))
8616             not_constant = true;
8617         }
8618     }
8619   return not_constant;
8620 }
8621
8622 /* Given a symbol and an initialization expression, add code to initialize
8623    the symbol to the function entry.  */
8624 static void
8625 build_init_assign (gfc_symbol *sym, gfc_expr *init)
8626 {
8627   gfc_expr *lval;
8628   gfc_code *init_st;
8629   gfc_namespace *ns = sym->ns;
8630
8631   /* Search for the function namespace if this is a contained
8632      function without an explicit result.  */
8633   if (sym->attr.function && sym == sym->result
8634       && sym->name != sym->ns->proc_name->name)
8635     {
8636       ns = ns->contained;
8637       for (;ns; ns = ns->sibling)
8638         if (strcmp (ns->proc_name->name, sym->name) == 0)
8639           break;
8640     }
8641
8642   if (ns == NULL)
8643     {
8644       gfc_free_expr (init);
8645       return;
8646     }
8647
8648   /* Build an l-value expression for the result.  */
8649   lval = gfc_lval_expr_from_sym (sym);
8650
8651   /* Add the code at scope entry.  */
8652   init_st = gfc_get_code ();
8653   init_st->next = ns->code;
8654   ns->code = init_st;
8655
8656   /* Assign the default initializer to the l-value.  */
8657   init_st->loc = sym->declared_at;
8658   init_st->op = EXEC_INIT_ASSIGN;
8659   init_st->expr1 = lval;
8660   init_st->expr2 = init;
8661 }
8662
8663 /* Assign the default initializer to a derived type variable or result.  */
8664
8665 static void
8666 apply_default_init (gfc_symbol *sym)
8667 {
8668   gfc_expr *init = NULL;
8669
8670   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
8671     return;
8672
8673   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
8674     init = gfc_default_initializer (&sym->ts);
8675
8676   if (init == NULL)
8677     return;
8678
8679   build_init_assign (sym, init);
8680 }
8681
8682 /* Build an initializer for a local integer, real, complex, logical, or
8683    character variable, based on the command line flags finit-local-zero,
8684    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
8685    null if the symbol should not have a default initialization.  */
8686 static gfc_expr *
8687 build_default_init_expr (gfc_symbol *sym)
8688 {
8689   int char_len;
8690   gfc_expr *init_expr;
8691   int i;
8692
8693   /* These symbols should never have a default initialization.  */
8694   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
8695       || sym->attr.external
8696       || sym->attr.dummy
8697       || sym->attr.pointer
8698       || sym->attr.in_equivalence
8699       || sym->attr.in_common
8700       || sym->attr.data
8701       || sym->module
8702       || sym->attr.cray_pointee
8703       || sym->attr.cray_pointer)
8704     return NULL;
8705
8706   /* Now we'll try to build an initializer expression.  */
8707   init_expr = gfc_get_expr ();
8708   init_expr->expr_type = EXPR_CONSTANT;
8709   init_expr->ts.type = sym->ts.type;
8710   init_expr->ts.kind = sym->ts.kind;
8711   init_expr->where = sym->declared_at;
8712   
8713   /* We will only initialize integers, reals, complex, logicals, and
8714      characters, and only if the corresponding command-line flags
8715      were set.  Otherwise, we free init_expr and return null.  */
8716   switch (sym->ts.type)
8717     {    
8718     case BT_INTEGER:
8719       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
8720         mpz_init_set_si (init_expr->value.integer, 
8721                          gfc_option.flag_init_integer_value);
8722       else
8723         {
8724           gfc_free_expr (init_expr);
8725           init_expr = NULL;
8726         }
8727       break;
8728
8729     case BT_REAL:
8730       mpfr_init (init_expr->value.real);
8731       switch (gfc_option.flag_init_real)
8732         {
8733         case GFC_INIT_REAL_SNAN:
8734           init_expr->is_snan = 1;
8735           /* Fall through.  */
8736         case GFC_INIT_REAL_NAN:
8737           mpfr_set_nan (init_expr->value.real);
8738           break;
8739
8740         case GFC_INIT_REAL_INF:
8741           mpfr_set_inf (init_expr->value.real, 1);
8742           break;
8743
8744         case GFC_INIT_REAL_NEG_INF:
8745           mpfr_set_inf (init_expr->value.real, -1);
8746           break;
8747
8748         case GFC_INIT_REAL_ZERO:
8749           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
8750           break;
8751
8752         default:
8753           gfc_free_expr (init_expr);
8754           init_expr = NULL;
8755           break;
8756         }
8757       break;
8758           
8759     case BT_COMPLEX:
8760       mpc_init2 (init_expr->value.complex, mpfr_get_default_prec());
8761       switch (gfc_option.flag_init_real)
8762         {
8763         case GFC_INIT_REAL_SNAN:
8764           init_expr->is_snan = 1;
8765           /* Fall through.  */
8766         case GFC_INIT_REAL_NAN:
8767           mpfr_set_nan (mpc_realref (init_expr->value.complex));
8768           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
8769           break;
8770
8771         case GFC_INIT_REAL_INF:
8772           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
8773           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
8774           break;
8775
8776         case GFC_INIT_REAL_NEG_INF:
8777           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
8778           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
8779           break;
8780
8781         case GFC_INIT_REAL_ZERO:
8782           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
8783           break;
8784
8785         default:
8786           gfc_free_expr (init_expr);
8787           init_expr = NULL;
8788           break;
8789         }
8790       break;
8791           
8792     case BT_LOGICAL:
8793       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
8794         init_expr->value.logical = 0;
8795       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
8796         init_expr->value.logical = 1;
8797       else
8798         {
8799           gfc_free_expr (init_expr);
8800           init_expr = NULL;
8801         }
8802       break;
8803           
8804     case BT_CHARACTER:
8805       /* For characters, the length must be constant in order to 
8806          create a default initializer.  */
8807       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
8808           && sym->ts.u.cl->length
8809           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8810         {
8811           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
8812           init_expr->value.character.length = char_len;
8813           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
8814           for (i = 0; i < char_len; i++)
8815             init_expr->value.character.string[i]
8816               = (unsigned char) gfc_option.flag_init_character_value;
8817         }
8818       else
8819         {
8820           gfc_free_expr (init_expr);
8821           init_expr = NULL;
8822         }
8823       break;
8824           
8825     default:
8826      gfc_free_expr (init_expr);
8827      init_expr = NULL;
8828     }
8829   return init_expr;
8830 }
8831
8832 /* Add an initialization expression to a local variable.  */
8833 static void
8834 apply_default_init_local (gfc_symbol *sym)
8835 {
8836   gfc_expr *init = NULL;
8837
8838   /* The symbol should be a variable or a function return value.  */
8839   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
8840       || (sym->attr.function && sym->result != sym))
8841     return;
8842
8843   /* Try to build the initializer expression.  If we can't initialize
8844      this symbol, then init will be NULL.  */
8845   init = build_default_init_expr (sym);
8846   if (init == NULL)
8847     return;
8848
8849   /* For saved variables, we don't want to add an initializer at 
8850      function entry, so we just add a static initializer.  */
8851   if (sym->attr.save || sym->ns->save_all 
8852       || gfc_option.flag_max_stack_var_size == 0)
8853     {
8854       /* Don't clobber an existing initializer!  */
8855       gcc_assert (sym->value == NULL);
8856       sym->value = init;
8857       return;
8858     }
8859
8860   build_init_assign (sym, init);
8861 }
8862
8863 /* Resolution of common features of flavors variable and procedure.  */
8864
8865 static gfc_try
8866 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
8867 {
8868   /* Constraints on deferred shape variable.  */
8869   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
8870     {
8871       if (sym->attr.allocatable)
8872         {
8873           if (sym->attr.dimension)
8874             {
8875               gfc_error ("Allocatable array '%s' at %L must have "
8876                          "a deferred shape", sym->name, &sym->declared_at);
8877               return FAILURE;
8878             }
8879           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
8880                                    "may not be ALLOCATABLE", sym->name,
8881                                    &sym->declared_at) == FAILURE)
8882             return FAILURE;
8883         }
8884
8885       if (sym->attr.pointer && sym->attr.dimension)
8886         {
8887           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
8888                      sym->name, &sym->declared_at);
8889           return FAILURE;
8890         }
8891
8892     }
8893   else
8894     {
8895       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
8896           && !sym->attr.dummy && sym->ts.type != BT_CLASS)
8897         {
8898           gfc_error ("Array '%s' at %L cannot have a deferred shape",
8899                      sym->name, &sym->declared_at);
8900           return FAILURE;
8901          }
8902     }
8903   return SUCCESS;
8904 }
8905
8906
8907 /* Additional checks for symbols with flavor variable and derived
8908    type.  To be called from resolve_fl_variable.  */
8909
8910 static gfc_try
8911 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
8912 {
8913   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
8914
8915   /* Check to see if a derived type is blocked from being host
8916      associated by the presence of another class I symbol in the same
8917      namespace.  14.6.1.3 of the standard and the discussion on
8918      comp.lang.fortran.  */
8919   if (sym->ns != sym->ts.u.derived->ns
8920       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
8921     {
8922       gfc_symbol *s;
8923       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
8924       if (s && s->attr.flavor != FL_DERIVED)
8925         {
8926           gfc_error ("The type '%s' cannot be host associated at %L "
8927                      "because it is blocked by an incompatible object "
8928                      "of the same name declared at %L",
8929                      sym->ts.u.derived->name, &sym->declared_at,
8930                      &s->declared_at);
8931           return FAILURE;
8932         }
8933     }
8934
8935   /* 4th constraint in section 11.3: "If an object of a type for which
8936      component-initialization is specified (R429) appears in the
8937      specification-part of a module and does not have the ALLOCATABLE
8938      or POINTER attribute, the object shall have the SAVE attribute."
8939
8940      The check for initializers is performed with
8941      has_default_initializer because gfc_default_initializer generates
8942      a hidden default for allocatable components.  */
8943   if (!(sym->value || no_init_flag) && sym->ns->proc_name
8944       && sym->ns->proc_name->attr.flavor == FL_MODULE
8945       && !sym->ns->save_all && !sym->attr.save
8946       && !sym->attr.pointer && !sym->attr.allocatable
8947       && has_default_initializer (sym->ts.u.derived)
8948       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
8949                          "module variable '%s' at %L, needed due to "
8950                          "the default initialization", sym->name,
8951                          &sym->declared_at) == FAILURE)
8952     return FAILURE;
8953
8954   if (sym->ts.type == BT_CLASS)
8955     {
8956       /* C502.  */
8957       if (!gfc_type_is_extensible (sym->ts.u.derived->components->ts.u.derived))
8958         {
8959           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
8960                      sym->ts.u.derived->components->ts.u.derived->name,
8961                      sym->name, &sym->declared_at);
8962           return FAILURE;
8963         }
8964
8965       /* C509.  */
8966       /* Assume that use associated symbols were checked in the module ns.  */ 
8967       if (!sym->attr.class_ok && !sym->attr.use_assoc)
8968         {
8969           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
8970                      "or pointer", sym->name, &sym->declared_at);
8971           return FAILURE;
8972         }
8973     }
8974
8975   /* Assign default initializer.  */
8976   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
8977       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
8978     {
8979       sym->value = gfc_default_initializer (&sym->ts);
8980     }
8981
8982   return SUCCESS;
8983 }
8984
8985
8986 /* Resolve symbols with flavor variable.  */
8987
8988 static gfc_try
8989 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
8990 {
8991   int no_init_flag, automatic_flag;
8992   gfc_expr *e;
8993   const char *auto_save_msg;
8994
8995   auto_save_msg = "Automatic object '%s' at %L cannot have the "
8996                   "SAVE attribute";
8997
8998   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
8999     return FAILURE;
9000
9001   /* Set this flag to check that variables are parameters of all entries.
9002      This check is effected by the call to gfc_resolve_expr through
9003      is_non_constant_shape_array.  */
9004   specification_expr = 1;
9005
9006   if (sym->ns->proc_name
9007       && (sym->ns->proc_name->attr.flavor == FL_MODULE
9008           || sym->ns->proc_name->attr.is_main_program)
9009       && !sym->attr.use_assoc
9010       && !sym->attr.allocatable
9011       && !sym->attr.pointer
9012       && is_non_constant_shape_array (sym))
9013     {
9014       /* The shape of a main program or module array needs to be
9015          constant.  */
9016       gfc_error ("The module or main program array '%s' at %L must "
9017                  "have constant shape", sym->name, &sym->declared_at);
9018       specification_expr = 0;
9019       return FAILURE;
9020     }
9021
9022   if (sym->ts.type == BT_CHARACTER)
9023     {
9024       /* Make sure that character string variables with assumed length are
9025          dummy arguments.  */
9026       e = sym->ts.u.cl->length;
9027       if (e == NULL && !sym->attr.dummy && !sym->attr.result)
9028         {
9029           gfc_error ("Entity with assumed character length at %L must be a "
9030                      "dummy argument or a PARAMETER", &sym->declared_at);
9031           return FAILURE;
9032         }
9033
9034       if (e && sym->attr.save && !gfc_is_constant_expr (e))
9035         {
9036           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9037           return FAILURE;
9038         }
9039
9040       if (!gfc_is_constant_expr (e)
9041           && !(e->expr_type == EXPR_VARIABLE
9042                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
9043           && sym->ns->proc_name
9044           && (sym->ns->proc_name->attr.flavor == FL_MODULE
9045               || sym->ns->proc_name->attr.is_main_program)
9046           && !sym->attr.use_assoc)
9047         {
9048           gfc_error ("'%s' at %L must have constant character length "
9049                      "in this context", sym->name, &sym->declared_at);
9050           return FAILURE;
9051         }
9052     }
9053
9054   if (sym->value == NULL && sym->attr.referenced)
9055     apply_default_init_local (sym); /* Try to apply a default initialization.  */
9056
9057   /* Determine if the symbol may not have an initializer.  */
9058   no_init_flag = automatic_flag = 0;
9059   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
9060       || sym->attr.intrinsic || sym->attr.result)
9061     no_init_flag = 1;
9062   else if (sym->attr.dimension && !sym->attr.pointer
9063            && is_non_constant_shape_array (sym))
9064     {
9065       no_init_flag = automatic_flag = 1;
9066
9067       /* Also, they must not have the SAVE attribute.
9068          SAVE_IMPLICIT is checked below.  */
9069       if (sym->attr.save == SAVE_EXPLICIT)
9070         {
9071           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9072           return FAILURE;
9073         }
9074     }
9075
9076   /* Ensure that any initializer is simplified.  */
9077   if (sym->value)
9078     gfc_simplify_expr (sym->value, 1);
9079
9080   /* Reject illegal initializers.  */
9081   if (!sym->mark && sym->value)
9082     {
9083       if (sym->attr.allocatable)
9084         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
9085                    sym->name, &sym->declared_at);
9086       else if (sym->attr.external)
9087         gfc_error ("External '%s' at %L cannot have an initializer",
9088                    sym->name, &sym->declared_at);
9089       else if (sym->attr.dummy
9090         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
9091         gfc_error ("Dummy '%s' at %L cannot have an initializer",
9092                    sym->name, &sym->declared_at);
9093       else if (sym->attr.intrinsic)
9094         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
9095                    sym->name, &sym->declared_at);
9096       else if (sym->attr.result)
9097         gfc_error ("Function result '%s' at %L cannot have an initializer",
9098                    sym->name, &sym->declared_at);
9099       else if (automatic_flag)
9100         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
9101                    sym->name, &sym->declared_at);
9102       else
9103         goto no_init_error;
9104       return FAILURE;
9105     }
9106
9107 no_init_error:
9108   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
9109     return resolve_fl_variable_derived (sym, no_init_flag);
9110
9111   return SUCCESS;
9112 }
9113
9114
9115 /* Resolve a procedure.  */
9116
9117 static gfc_try
9118 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
9119 {
9120   gfc_formal_arglist *arg;
9121
9122   if (sym->attr.function
9123       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9124     return FAILURE;
9125
9126   if (sym->ts.type == BT_CHARACTER)
9127     {
9128       gfc_charlen *cl = sym->ts.u.cl;
9129
9130       if (cl && cl->length && gfc_is_constant_expr (cl->length)
9131              && resolve_charlen (cl) == FAILURE)
9132         return FAILURE;
9133
9134       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
9135           && sym->attr.proc == PROC_ST_FUNCTION)
9136         {
9137           gfc_error ("Character-valued statement function '%s' at %L must "
9138                      "have constant length", sym->name, &sym->declared_at);
9139           return FAILURE;
9140         }
9141     }
9142
9143   /* Ensure that derived type for are not of a private type.  Internal
9144      module procedures are excluded by 2.2.3.3 - i.e., they are not
9145      externally accessible and can access all the objects accessible in
9146      the host.  */
9147   if (!(sym->ns->parent
9148         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
9149       && gfc_check_access(sym->attr.access, sym->ns->default_access))
9150     {
9151       gfc_interface *iface;
9152
9153       for (arg = sym->formal; arg; arg = arg->next)
9154         {
9155           if (arg->sym
9156               && arg->sym->ts.type == BT_DERIVED
9157               && !arg->sym->ts.u.derived->attr.use_assoc
9158               && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9159                                     arg->sym->ts.u.derived->ns->default_access)
9160               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
9161                                  "PRIVATE type and cannot be a dummy argument"
9162                                  " of '%s', which is PUBLIC at %L",
9163                                  arg->sym->name, sym->name, &sym->declared_at)
9164                  == FAILURE)
9165             {
9166               /* Stop this message from recurring.  */
9167               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9168               return FAILURE;
9169             }
9170         }
9171
9172       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9173          PRIVATE to the containing module.  */
9174       for (iface = sym->generic; iface; iface = iface->next)
9175         {
9176           for (arg = iface->sym->formal; arg; arg = arg->next)
9177             {
9178               if (arg->sym
9179                   && arg->sym->ts.type == BT_DERIVED
9180                   && !arg->sym->ts.u.derived->attr.use_assoc
9181                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9182                                         arg->sym->ts.u.derived->ns->default_access)
9183                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9184                                      "'%s' in PUBLIC interface '%s' at %L "
9185                                      "takes dummy arguments of '%s' which is "
9186                                      "PRIVATE", iface->sym->name, sym->name,
9187                                      &iface->sym->declared_at,
9188                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9189                 {
9190                   /* Stop this message from recurring.  */
9191                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9192                   return FAILURE;
9193                 }
9194              }
9195         }
9196
9197       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9198          PRIVATE to the containing module.  */
9199       for (iface = sym->generic; iface; iface = iface->next)
9200         {
9201           for (arg = iface->sym->formal; arg; arg = arg->next)
9202             {
9203               if (arg->sym
9204                   && arg->sym->ts.type == BT_DERIVED
9205                   && !arg->sym->ts.u.derived->attr.use_assoc
9206                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9207                                         arg->sym->ts.u.derived->ns->default_access)
9208                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9209                                      "'%s' in PUBLIC interface '%s' at %L "
9210                                      "takes dummy arguments of '%s' which is "
9211                                      "PRIVATE", iface->sym->name, sym->name,
9212                                      &iface->sym->declared_at,
9213                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9214                 {
9215                   /* Stop this message from recurring.  */
9216                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9217                   return FAILURE;
9218                 }
9219              }
9220         }
9221     }
9222
9223   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
9224       && !sym->attr.proc_pointer)
9225     {
9226       gfc_error ("Function '%s' at %L cannot have an initializer",
9227                  sym->name, &sym->declared_at);
9228       return FAILURE;
9229     }
9230
9231   /* An external symbol may not have an initializer because it is taken to be
9232      a procedure. Exception: Procedure Pointers.  */
9233   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
9234     {
9235       gfc_error ("External object '%s' at %L may not have an initializer",
9236                  sym->name, &sym->declared_at);
9237       return FAILURE;
9238     }
9239
9240   /* An elemental function is required to return a scalar 12.7.1  */
9241   if (sym->attr.elemental && sym->attr.function && sym->as)
9242     {
9243       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
9244                  "result", sym->name, &sym->declared_at);
9245       /* Reset so that the error only occurs once.  */
9246       sym->attr.elemental = 0;
9247       return FAILURE;
9248     }
9249
9250   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
9251      char-len-param shall not be array-valued, pointer-valued, recursive
9252      or pure.  ....snip... A character value of * may only be used in the
9253      following ways: (i) Dummy arg of procedure - dummy associates with
9254      actual length; (ii) To declare a named constant; or (iii) External
9255      function - but length must be declared in calling scoping unit.  */
9256   if (sym->attr.function
9257       && sym->ts.type == BT_CHARACTER
9258       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
9259     {
9260       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
9261           || (sym->attr.recursive) || (sym->attr.pure))
9262         {
9263           if (sym->as && sym->as->rank)
9264             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9265                        "array-valued", sym->name, &sym->declared_at);
9266
9267           if (sym->attr.pointer)
9268             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9269                        "pointer-valued", sym->name, &sym->declared_at);
9270
9271           if (sym->attr.pure)
9272             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9273                        "pure", sym->name, &sym->declared_at);
9274
9275           if (sym->attr.recursive)
9276             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9277                        "recursive", sym->name, &sym->declared_at);
9278
9279           return FAILURE;
9280         }
9281
9282       /* Appendix B.2 of the standard.  Contained functions give an
9283          error anyway.  Fixed-form is likely to be F77/legacy.  */
9284       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
9285         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
9286                         "CHARACTER(*) function '%s' at %L",
9287                         sym->name, &sym->declared_at);
9288     }
9289
9290   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
9291     {
9292       gfc_formal_arglist *curr_arg;
9293       int has_non_interop_arg = 0;
9294
9295       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
9296                              sym->common_block) == FAILURE)
9297         {
9298           /* Clear these to prevent looking at them again if there was an
9299              error.  */
9300           sym->attr.is_bind_c = 0;
9301           sym->attr.is_c_interop = 0;
9302           sym->ts.is_c_interop = 0;
9303         }
9304       else
9305         {
9306           /* So far, no errors have been found.  */
9307           sym->attr.is_c_interop = 1;
9308           sym->ts.is_c_interop = 1;
9309         }
9310       
9311       curr_arg = sym->formal;
9312       while (curr_arg != NULL)
9313         {
9314           /* Skip implicitly typed dummy args here.  */
9315           if (curr_arg->sym->attr.implicit_type == 0)
9316             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
9317               /* If something is found to fail, record the fact so we
9318                  can mark the symbol for the procedure as not being
9319                  BIND(C) to try and prevent multiple errors being
9320                  reported.  */
9321               has_non_interop_arg = 1;
9322           
9323           curr_arg = curr_arg->next;
9324         }
9325
9326       /* See if any of the arguments were not interoperable and if so, clear
9327          the procedure symbol to prevent duplicate error messages.  */
9328       if (has_non_interop_arg != 0)
9329         {
9330           sym->attr.is_c_interop = 0;
9331           sym->ts.is_c_interop = 0;
9332           sym->attr.is_bind_c = 0;
9333         }
9334     }
9335   
9336   if (!sym->attr.proc_pointer)
9337     {
9338       if (sym->attr.save == SAVE_EXPLICIT)
9339         {
9340           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
9341                      "in '%s' at %L", sym->name, &sym->declared_at);
9342           return FAILURE;
9343         }
9344       if (sym->attr.intent)
9345         {
9346           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
9347                      "in '%s' at %L", sym->name, &sym->declared_at);
9348           return FAILURE;
9349         }
9350       if (sym->attr.subroutine && sym->attr.result)
9351         {
9352           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
9353                      "in '%s' at %L", sym->name, &sym->declared_at);
9354           return FAILURE;
9355         }
9356       if (sym->attr.external && sym->attr.function
9357           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
9358               || sym->attr.contained))
9359         {
9360           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
9361                      "in '%s' at %L", sym->name, &sym->declared_at);
9362           return FAILURE;
9363         }
9364       if (strcmp ("ppr@", sym->name) == 0)
9365         {
9366           gfc_error ("Procedure pointer result '%s' at %L "
9367                      "is missing the pointer attribute",
9368                      sym->ns->proc_name->name, &sym->declared_at);
9369           return FAILURE;
9370         }
9371     }
9372
9373   return SUCCESS;
9374 }
9375
9376
9377 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
9378    been defined and we now know their defined arguments, check that they fulfill
9379    the requirements of the standard for procedures used as finalizers.  */
9380
9381 static gfc_try
9382 gfc_resolve_finalizers (gfc_symbol* derived)
9383 {
9384   gfc_finalizer* list;
9385   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
9386   gfc_try result = SUCCESS;
9387   bool seen_scalar = false;
9388
9389   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
9390     return SUCCESS;
9391
9392   /* Walk over the list of finalizer-procedures, check them, and if any one
9393      does not fit in with the standard's definition, print an error and remove
9394      it from the list.  */
9395   prev_link = &derived->f2k_derived->finalizers;
9396   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
9397     {
9398       gfc_symbol* arg;
9399       gfc_finalizer* i;
9400       int my_rank;
9401
9402       /* Skip this finalizer if we already resolved it.  */
9403       if (list->proc_tree)
9404         {
9405           prev_link = &(list->next);
9406           continue;
9407         }
9408
9409       /* Check this exists and is a SUBROUTINE.  */
9410       if (!list->proc_sym->attr.subroutine)
9411         {
9412           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
9413                      list->proc_sym->name, &list->where);
9414           goto error;
9415         }
9416
9417       /* We should have exactly one argument.  */
9418       if (!list->proc_sym->formal || list->proc_sym->formal->next)
9419         {
9420           gfc_error ("FINAL procedure at %L must have exactly one argument",
9421                      &list->where);
9422           goto error;
9423         }
9424       arg = list->proc_sym->formal->sym;
9425
9426       /* This argument must be of our type.  */
9427       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
9428         {
9429           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
9430                      &arg->declared_at, derived->name);
9431           goto error;
9432         }
9433
9434       /* It must neither be a pointer nor allocatable nor optional.  */
9435       if (arg->attr.pointer)
9436         {
9437           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
9438                      &arg->declared_at);
9439           goto error;
9440         }
9441       if (arg->attr.allocatable)
9442         {
9443           gfc_error ("Argument of FINAL procedure at %L must not be"
9444                      " ALLOCATABLE", &arg->declared_at);
9445           goto error;
9446         }
9447       if (arg->attr.optional)
9448         {
9449           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
9450                      &arg->declared_at);
9451           goto error;
9452         }
9453
9454       /* It must not be INTENT(OUT).  */
9455       if (arg->attr.intent == INTENT_OUT)
9456         {
9457           gfc_error ("Argument of FINAL procedure at %L must not be"
9458                      " INTENT(OUT)", &arg->declared_at);
9459           goto error;
9460         }
9461
9462       /* Warn if the procedure is non-scalar and not assumed shape.  */
9463       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
9464           && arg->as->type != AS_ASSUMED_SHAPE)
9465         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
9466                      " shape argument", &arg->declared_at);
9467
9468       /* Check that it does not match in kind and rank with a FINAL procedure
9469          defined earlier.  To really loop over the *earlier* declarations,
9470          we need to walk the tail of the list as new ones were pushed at the
9471          front.  */
9472       /* TODO: Handle kind parameters once they are implemented.  */
9473       my_rank = (arg->as ? arg->as->rank : 0);
9474       for (i = list->next; i; i = i->next)
9475         {
9476           /* Argument list might be empty; that is an error signalled earlier,
9477              but we nevertheless continued resolving.  */
9478           if (i->proc_sym->formal)
9479             {
9480               gfc_symbol* i_arg = i->proc_sym->formal->sym;
9481               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
9482               if (i_rank == my_rank)
9483                 {
9484                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
9485                              " rank (%d) as '%s'",
9486                              list->proc_sym->name, &list->where, my_rank, 
9487                              i->proc_sym->name);
9488                   goto error;
9489                 }
9490             }
9491         }
9492
9493         /* Is this the/a scalar finalizer procedure?  */
9494         if (!arg->as || arg->as->rank == 0)
9495           seen_scalar = true;
9496
9497         /* Find the symtree for this procedure.  */
9498         gcc_assert (!list->proc_tree);
9499         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
9500
9501         prev_link = &list->next;
9502         continue;
9503
9504         /* Remove wrong nodes immediately from the list so we don't risk any
9505            troubles in the future when they might fail later expectations.  */
9506 error:
9507         result = FAILURE;
9508         i = list;
9509         *prev_link = list->next;
9510         gfc_free_finalizer (i);
9511     }
9512
9513   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
9514      were nodes in the list, must have been for arrays.  It is surely a good
9515      idea to have a scalar version there if there's something to finalize.  */
9516   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
9517     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
9518                  " defined at %L, suggest also scalar one",
9519                  derived->name, &derived->declared_at);
9520
9521   /* TODO:  Remove this error when finalization is finished.  */
9522   gfc_error ("Finalization at %L is not yet implemented",
9523              &derived->declared_at);
9524
9525   return result;
9526 }
9527
9528
9529 /* Check that it is ok for the typebound procedure proc to override the
9530    procedure old.  */
9531
9532 static gfc_try
9533 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
9534 {
9535   locus where;
9536   const gfc_symbol* proc_target;
9537   const gfc_symbol* old_target;
9538   unsigned proc_pass_arg, old_pass_arg, argpos;
9539   gfc_formal_arglist* proc_formal;
9540   gfc_formal_arglist* old_formal;
9541
9542   /* This procedure should only be called for non-GENERIC proc.  */
9543   gcc_assert (!proc->n.tb->is_generic);
9544
9545   /* If the overwritten procedure is GENERIC, this is an error.  */
9546   if (old->n.tb->is_generic)
9547     {
9548       gfc_error ("Can't overwrite GENERIC '%s' at %L",
9549                  old->name, &proc->n.tb->where);
9550       return FAILURE;
9551     }
9552
9553   where = proc->n.tb->where;
9554   proc_target = proc->n.tb->u.specific->n.sym;
9555   old_target = old->n.tb->u.specific->n.sym;
9556
9557   /* Check that overridden binding is not NON_OVERRIDABLE.  */
9558   if (old->n.tb->non_overridable)
9559     {
9560       gfc_error ("'%s' at %L overrides a procedure binding declared"
9561                  " NON_OVERRIDABLE", proc->name, &where);
9562       return FAILURE;
9563     }
9564
9565   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
9566   if (!old->n.tb->deferred && proc->n.tb->deferred)
9567     {
9568       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
9569                  " non-DEFERRED binding", proc->name, &where);
9570       return FAILURE;
9571     }
9572
9573   /* If the overridden binding is PURE, the overriding must be, too.  */
9574   if (old_target->attr.pure && !proc_target->attr.pure)
9575     {
9576       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
9577                  proc->name, &where);
9578       return FAILURE;
9579     }
9580
9581   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
9582      is not, the overriding must not be either.  */
9583   if (old_target->attr.elemental && !proc_target->attr.elemental)
9584     {
9585       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
9586                  " ELEMENTAL", proc->name, &where);
9587       return FAILURE;
9588     }
9589   if (!old_target->attr.elemental && proc_target->attr.elemental)
9590     {
9591       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
9592                  " be ELEMENTAL, either", proc->name, &where);
9593       return FAILURE;
9594     }
9595
9596   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
9597      SUBROUTINE.  */
9598   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
9599     {
9600       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
9601                  " SUBROUTINE", proc->name, &where);
9602       return FAILURE;
9603     }
9604
9605   /* If the overridden binding is a FUNCTION, the overriding must also be a
9606      FUNCTION and have the same characteristics.  */
9607   if (old_target->attr.function)
9608     {
9609       if (!proc_target->attr.function)
9610         {
9611           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
9612                      " FUNCTION", proc->name, &where);
9613           return FAILURE;
9614         }
9615
9616       /* FIXME:  Do more comprehensive checking (including, for instance, the
9617          rank and array-shape).  */
9618       gcc_assert (proc_target->result && old_target->result);
9619       if (!gfc_compare_types (&proc_target->result->ts,
9620                               &old_target->result->ts))
9621         {
9622           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
9623                      " matching result types", proc->name, &where);
9624           return FAILURE;
9625         }
9626     }
9627
9628   /* If the overridden binding is PUBLIC, the overriding one must not be
9629      PRIVATE.  */
9630   if (old->n.tb->access == ACCESS_PUBLIC
9631       && proc->n.tb->access == ACCESS_PRIVATE)
9632     {
9633       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
9634                  " PRIVATE", proc->name, &where);
9635       return FAILURE;
9636     }
9637
9638   /* Compare the formal argument lists of both procedures.  This is also abused
9639      to find the position of the passed-object dummy arguments of both
9640      bindings as at least the overridden one might not yet be resolved and we
9641      need those positions in the check below.  */
9642   proc_pass_arg = old_pass_arg = 0;
9643   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
9644     proc_pass_arg = 1;
9645   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
9646     old_pass_arg = 1;
9647   argpos = 1;
9648   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
9649        proc_formal && old_formal;
9650        proc_formal = proc_formal->next, old_formal = old_formal->next)
9651     {
9652       if (proc->n.tb->pass_arg
9653           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
9654         proc_pass_arg = argpos;
9655       if (old->n.tb->pass_arg
9656           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
9657         old_pass_arg = argpos;
9658
9659       /* Check that the names correspond.  */
9660       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
9661         {
9662           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
9663                      " to match the corresponding argument of the overridden"
9664                      " procedure", proc_formal->sym->name, proc->name, &where,
9665                      old_formal->sym->name);
9666           return FAILURE;
9667         }
9668
9669       /* Check that the types correspond if neither is the passed-object
9670          argument.  */
9671       /* FIXME:  Do more comprehensive testing here.  */
9672       if (proc_pass_arg != argpos && old_pass_arg != argpos
9673           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
9674         {
9675           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L "
9676                      "in respect to the overridden procedure",
9677                      proc_formal->sym->name, proc->name, &where);
9678           return FAILURE;
9679         }
9680
9681       ++argpos;
9682     }
9683   if (proc_formal || old_formal)
9684     {
9685       gfc_error ("'%s' at %L must have the same number of formal arguments as"
9686                  " the overridden procedure", proc->name, &where);
9687       return FAILURE;
9688     }
9689
9690   /* If the overridden binding is NOPASS, the overriding one must also be
9691      NOPASS.  */
9692   if (old->n.tb->nopass && !proc->n.tb->nopass)
9693     {
9694       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
9695                  " NOPASS", proc->name, &where);
9696       return FAILURE;
9697     }
9698
9699   /* If the overridden binding is PASS(x), the overriding one must also be
9700      PASS and the passed-object dummy arguments must correspond.  */
9701   if (!old->n.tb->nopass)
9702     {
9703       if (proc->n.tb->nopass)
9704         {
9705           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
9706                      " PASS", proc->name, &where);
9707           return FAILURE;
9708         }
9709
9710       if (proc_pass_arg != old_pass_arg)
9711         {
9712           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
9713                      " the same position as the passed-object dummy argument of"
9714                      " the overridden procedure", proc->name, &where);
9715           return FAILURE;
9716         }
9717     }
9718
9719   return SUCCESS;
9720 }
9721
9722
9723 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
9724
9725 static gfc_try
9726 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
9727                              const char* generic_name, locus where)
9728 {
9729   gfc_symbol* sym1;
9730   gfc_symbol* sym2;
9731
9732   gcc_assert (t1->specific && t2->specific);
9733   gcc_assert (!t1->specific->is_generic);
9734   gcc_assert (!t2->specific->is_generic);
9735
9736   sym1 = t1->specific->u.specific->n.sym;
9737   sym2 = t2->specific->u.specific->n.sym;
9738
9739   if (sym1 == sym2)
9740     return SUCCESS;
9741
9742   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
9743   if (sym1->attr.subroutine != sym2->attr.subroutine
9744       || sym1->attr.function != sym2->attr.function)
9745     {
9746       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
9747                  " GENERIC '%s' at %L",
9748                  sym1->name, sym2->name, generic_name, &where);
9749       return FAILURE;
9750     }
9751
9752   /* Compare the interfaces.  */
9753   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
9754     {
9755       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
9756                  sym1->name, sym2->name, generic_name, &where);
9757       return FAILURE;
9758     }
9759
9760   return SUCCESS;
9761 }
9762
9763
9764 /* Worker function for resolving a generic procedure binding; this is used to
9765    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
9766
9767    The difference between those cases is finding possible inherited bindings
9768    that are overridden, as one has to look for them in tb_sym_root,
9769    tb_uop_root or tb_op, respectively.  Thus the caller must already find
9770    the super-type and set p->overridden correctly.  */
9771
9772 static gfc_try
9773 resolve_tb_generic_targets (gfc_symbol* super_type,
9774                             gfc_typebound_proc* p, const char* name)
9775 {
9776   gfc_tbp_generic* target;
9777   gfc_symtree* first_target;
9778   gfc_symtree* inherited;
9779
9780   gcc_assert (p && p->is_generic);
9781
9782   /* Try to find the specific bindings for the symtrees in our target-list.  */
9783   gcc_assert (p->u.generic);
9784   for (target = p->u.generic; target; target = target->next)
9785     if (!target->specific)
9786       {
9787         gfc_typebound_proc* overridden_tbp;
9788         gfc_tbp_generic* g;
9789         const char* target_name;
9790
9791         target_name = target->specific_st->name;
9792
9793         /* Defined for this type directly.  */
9794         if (target->specific_st->n.tb)
9795           {
9796             target->specific = target->specific_st->n.tb;
9797             goto specific_found;
9798           }
9799
9800         /* Look for an inherited specific binding.  */
9801         if (super_type)
9802           {
9803             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
9804                                                  true, NULL);
9805
9806             if (inherited)
9807               {
9808                 gcc_assert (inherited->n.tb);
9809                 target->specific = inherited->n.tb;
9810                 goto specific_found;
9811               }
9812           }
9813
9814         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
9815                    " at %L", target_name, name, &p->where);
9816         return FAILURE;
9817
9818         /* Once we've found the specific binding, check it is not ambiguous with
9819            other specifics already found or inherited for the same GENERIC.  */
9820 specific_found:
9821         gcc_assert (target->specific);
9822
9823         /* This must really be a specific binding!  */
9824         if (target->specific->is_generic)
9825           {
9826             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
9827                        " '%s' is GENERIC, too", name, &p->where, target_name);
9828             return FAILURE;
9829           }
9830
9831         /* Check those already resolved on this type directly.  */
9832         for (g = p->u.generic; g; g = g->next)
9833           if (g != target && g->specific
9834               && check_generic_tbp_ambiguity (target, g, name, p->where)
9835                   == FAILURE)
9836             return FAILURE;
9837
9838         /* Check for ambiguity with inherited specific targets.  */
9839         for (overridden_tbp = p->overridden; overridden_tbp;
9840              overridden_tbp = overridden_tbp->overridden)
9841           if (overridden_tbp->is_generic)
9842             {
9843               for (g = overridden_tbp->u.generic; g; g = g->next)
9844                 {
9845                   gcc_assert (g->specific);
9846                   if (check_generic_tbp_ambiguity (target, g,
9847                                                    name, p->where) == FAILURE)
9848                     return FAILURE;
9849                 }
9850             }
9851       }
9852
9853   /* If we attempt to "overwrite" a specific binding, this is an error.  */
9854   if (p->overridden && !p->overridden->is_generic)
9855     {
9856       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
9857                  " the same name", name, &p->where);
9858       return FAILURE;
9859     }
9860
9861   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
9862      all must have the same attributes here.  */
9863   first_target = p->u.generic->specific->u.specific;
9864   gcc_assert (first_target);
9865   p->subroutine = first_target->n.sym->attr.subroutine;
9866   p->function = first_target->n.sym->attr.function;
9867
9868   return SUCCESS;
9869 }
9870
9871
9872 /* Resolve a GENERIC procedure binding for a derived type.  */
9873
9874 static gfc_try
9875 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
9876 {
9877   gfc_symbol* super_type;
9878
9879   /* Find the overridden binding if any.  */
9880   st->n.tb->overridden = NULL;
9881   super_type = gfc_get_derived_super_type (derived);
9882   if (super_type)
9883     {
9884       gfc_symtree* overridden;
9885       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
9886                                             true, NULL);
9887
9888       if (overridden && overridden->n.tb)
9889         st->n.tb->overridden = overridden->n.tb;
9890     }
9891
9892   /* Resolve using worker function.  */
9893   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
9894 }
9895
9896
9897 /* Retrieve the target-procedure of an operator binding and do some checks in
9898    common for intrinsic and user-defined type-bound operators.  */
9899
9900 static gfc_symbol*
9901 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
9902 {
9903   gfc_symbol* target_proc;
9904
9905   gcc_assert (target->specific && !target->specific->is_generic);
9906   target_proc = target->specific->u.specific->n.sym;
9907   gcc_assert (target_proc);
9908
9909   /* All operator bindings must have a passed-object dummy argument.  */
9910   if (target->specific->nopass)
9911     {
9912       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
9913       return NULL;
9914     }
9915
9916   return target_proc;
9917 }
9918
9919
9920 /* Resolve a type-bound intrinsic operator.  */
9921
9922 static gfc_try
9923 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
9924                                 gfc_typebound_proc* p)
9925 {
9926   gfc_symbol* super_type;
9927   gfc_tbp_generic* target;
9928   
9929   /* If there's already an error here, do nothing (but don't fail again).  */
9930   if (p->error)
9931     return SUCCESS;
9932
9933   /* Operators should always be GENERIC bindings.  */
9934   gcc_assert (p->is_generic);
9935
9936   /* Look for an overridden binding.  */
9937   super_type = gfc_get_derived_super_type (derived);
9938   if (super_type && super_type->f2k_derived)
9939     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
9940                                                      op, true, NULL);
9941   else
9942     p->overridden = NULL;
9943
9944   /* Resolve general GENERIC properties using worker function.  */
9945   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
9946     goto error;
9947
9948   /* Check the targets to be procedures of correct interface.  */
9949   for (target = p->u.generic; target; target = target->next)
9950     {
9951       gfc_symbol* target_proc;
9952
9953       target_proc = get_checked_tb_operator_target (target, p->where);
9954       if (!target_proc)
9955         goto error;
9956
9957       if (!gfc_check_operator_interface (target_proc, op, p->where))
9958         goto error;
9959     }
9960
9961   return SUCCESS;
9962
9963 error:
9964   p->error = 1;
9965   return FAILURE;
9966 }
9967
9968
9969 /* Resolve a type-bound user operator (tree-walker callback).  */
9970
9971 static gfc_symbol* resolve_bindings_derived;
9972 static gfc_try resolve_bindings_result;
9973
9974 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
9975
9976 static void
9977 resolve_typebound_user_op (gfc_symtree* stree)
9978 {
9979   gfc_symbol* super_type;
9980   gfc_tbp_generic* target;
9981
9982   gcc_assert (stree && stree->n.tb);
9983
9984   if (stree->n.tb->error)
9985     return;
9986
9987   /* Operators should always be GENERIC bindings.  */
9988   gcc_assert (stree->n.tb->is_generic);
9989
9990   /* Find overridden procedure, if any.  */
9991   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
9992   if (super_type && super_type->f2k_derived)
9993     {
9994       gfc_symtree* overridden;
9995       overridden = gfc_find_typebound_user_op (super_type, NULL,
9996                                                stree->name, true, NULL);
9997
9998       if (overridden && overridden->n.tb)
9999         stree->n.tb->overridden = overridden->n.tb;
10000     }
10001   else
10002     stree->n.tb->overridden = NULL;
10003
10004   /* Resolve basically using worker function.  */
10005   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
10006         == FAILURE)
10007     goto error;
10008
10009   /* Check the targets to be functions of correct interface.  */
10010   for (target = stree->n.tb->u.generic; target; target = target->next)
10011     {
10012       gfc_symbol* target_proc;
10013
10014       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
10015       if (!target_proc)
10016         goto error;
10017
10018       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
10019         goto error;
10020     }
10021
10022   return;
10023
10024 error:
10025   resolve_bindings_result = FAILURE;
10026   stree->n.tb->error = 1;
10027 }
10028
10029
10030 /* Resolve the type-bound procedures for a derived type.  */
10031
10032 static void
10033 resolve_typebound_procedure (gfc_symtree* stree)
10034 {
10035   gfc_symbol* proc;
10036   locus where;
10037   gfc_symbol* me_arg;
10038   gfc_symbol* super_type;
10039   gfc_component* comp;
10040
10041   gcc_assert (stree);
10042
10043   /* Undefined specific symbol from GENERIC target definition.  */
10044   if (!stree->n.tb)
10045     return;
10046
10047   if (stree->n.tb->error)
10048     return;
10049
10050   /* If this is a GENERIC binding, use that routine.  */
10051   if (stree->n.tb->is_generic)
10052     {
10053       if (resolve_typebound_generic (resolve_bindings_derived, stree)
10054             == FAILURE)
10055         goto error;
10056       return;
10057     }
10058
10059   /* Get the target-procedure to check it.  */
10060   gcc_assert (!stree->n.tb->is_generic);
10061   gcc_assert (stree->n.tb->u.specific);
10062   proc = stree->n.tb->u.specific->n.sym;
10063   where = stree->n.tb->where;
10064
10065   /* Default access should already be resolved from the parser.  */
10066   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
10067
10068   /* It should be a module procedure or an external procedure with explicit
10069      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
10070   if ((!proc->attr.subroutine && !proc->attr.function)
10071       || (proc->attr.proc != PROC_MODULE
10072           && proc->attr.if_source != IFSRC_IFBODY)
10073       || (proc->attr.abstract && !stree->n.tb->deferred))
10074     {
10075       gfc_error ("'%s' must be a module procedure or an external procedure with"
10076                  " an explicit interface at %L", proc->name, &where);
10077       goto error;
10078     }
10079   stree->n.tb->subroutine = proc->attr.subroutine;
10080   stree->n.tb->function = proc->attr.function;
10081
10082   /* Find the super-type of the current derived type.  We could do this once and
10083      store in a global if speed is needed, but as long as not I believe this is
10084      more readable and clearer.  */
10085   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10086
10087   /* If PASS, resolve and check arguments if not already resolved / loaded
10088      from a .mod file.  */
10089   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
10090     {
10091       if (stree->n.tb->pass_arg)
10092         {
10093           gfc_formal_arglist* i;
10094
10095           /* If an explicit passing argument name is given, walk the arg-list
10096              and look for it.  */
10097
10098           me_arg = NULL;
10099           stree->n.tb->pass_arg_num = 1;
10100           for (i = proc->formal; i; i = i->next)
10101             {
10102               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
10103                 {
10104                   me_arg = i->sym;
10105                   break;
10106                 }
10107               ++stree->n.tb->pass_arg_num;
10108             }
10109
10110           if (!me_arg)
10111             {
10112               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
10113                          " argument '%s'",
10114                          proc->name, stree->n.tb->pass_arg, &where,
10115                          stree->n.tb->pass_arg);
10116               goto error;
10117             }
10118         }
10119       else
10120         {
10121           /* Otherwise, take the first one; there should in fact be at least
10122              one.  */
10123           stree->n.tb->pass_arg_num = 1;
10124           if (!proc->formal)
10125             {
10126               gfc_error ("Procedure '%s' with PASS at %L must have at"
10127                          " least one argument", proc->name, &where);
10128               goto error;
10129             }
10130           me_arg = proc->formal->sym;
10131         }
10132
10133       /* Now check that the argument-type matches and the passed-object
10134          dummy argument is generally fine.  */
10135
10136       gcc_assert (me_arg);
10137
10138       if (me_arg->ts.type != BT_CLASS)
10139         {
10140           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10141                      " at %L", proc->name, &where);
10142           goto error;
10143         }
10144
10145       if (me_arg->ts.u.derived->components->ts.u.derived
10146           != resolve_bindings_derived)
10147         {
10148           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10149                      " the derived-type '%s'", me_arg->name, proc->name,
10150                      me_arg->name, &where, resolve_bindings_derived->name);
10151           goto error;
10152         }
10153   
10154       gcc_assert (me_arg->ts.type == BT_CLASS);
10155       if (me_arg->ts.u.derived->components->as
10156           && me_arg->ts.u.derived->components->as->rank > 0)
10157         {
10158           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
10159                      " scalar", proc->name, &where);
10160           goto error;
10161         }
10162       if (me_arg->ts.u.derived->components->attr.allocatable)
10163         {
10164           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10165                      " be ALLOCATABLE", proc->name, &where);
10166           goto error;
10167         }
10168       if (me_arg->ts.u.derived->components->attr.class_pointer)
10169         {
10170           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10171                      " be POINTER", proc->name, &where);
10172           goto error;
10173         }
10174     }
10175
10176   /* If we are extending some type, check that we don't override a procedure
10177      flagged NON_OVERRIDABLE.  */
10178   stree->n.tb->overridden = NULL;
10179   if (super_type)
10180     {
10181       gfc_symtree* overridden;
10182       overridden = gfc_find_typebound_proc (super_type, NULL,
10183                                             stree->name, true, NULL);
10184
10185       if (overridden && overridden->n.tb)
10186         stree->n.tb->overridden = overridden->n.tb;
10187
10188       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
10189         goto error;
10190     }
10191
10192   /* See if there's a name collision with a component directly in this type.  */
10193   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
10194     if (!strcmp (comp->name, stree->name))
10195       {
10196         gfc_error ("Procedure '%s' at %L has the same name as a component of"
10197                    " '%s'",
10198                    stree->name, &where, resolve_bindings_derived->name);
10199         goto error;
10200       }
10201
10202   /* Try to find a name collision with an inherited component.  */
10203   if (super_type && gfc_find_component (super_type, stree->name, true, true))
10204     {
10205       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
10206                  " component of '%s'",
10207                  stree->name, &where, resolve_bindings_derived->name);
10208       goto error;
10209     }
10210
10211   stree->n.tb->error = 0;
10212   return;
10213
10214 error:
10215   resolve_bindings_result = FAILURE;
10216   stree->n.tb->error = 1;
10217 }
10218
10219 static gfc_try
10220 resolve_typebound_procedures (gfc_symbol* derived)
10221 {
10222   int op;
10223
10224   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
10225     return SUCCESS;
10226
10227   resolve_bindings_derived = derived;
10228   resolve_bindings_result = SUCCESS;
10229
10230   if (derived->f2k_derived->tb_sym_root)
10231     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
10232                           &resolve_typebound_procedure);
10233
10234   if (derived->f2k_derived->tb_uop_root)
10235     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
10236                           &resolve_typebound_user_op);
10237
10238   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
10239     {
10240       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
10241       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
10242                                                p) == FAILURE)
10243         resolve_bindings_result = FAILURE;
10244     }
10245
10246   return resolve_bindings_result;
10247 }
10248
10249
10250 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
10251    to give all identical derived types the same backend_decl.  */
10252 static void
10253 add_dt_to_dt_list (gfc_symbol *derived)
10254 {
10255   gfc_dt_list *dt_list;
10256
10257   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
10258     if (derived == dt_list->derived)
10259       break;
10260
10261   if (dt_list == NULL)
10262     {
10263       dt_list = gfc_get_dt_list ();
10264       dt_list->next = gfc_derived_types;
10265       dt_list->derived = derived;
10266       gfc_derived_types = dt_list;
10267     }
10268 }
10269
10270
10271 /* Ensure that a derived-type is really not abstract, meaning that every
10272    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
10273
10274 static gfc_try
10275 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
10276 {
10277   if (!st)
10278     return SUCCESS;
10279
10280   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
10281     return FAILURE;
10282   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
10283     return FAILURE;
10284
10285   if (st->n.tb && st->n.tb->deferred)
10286     {
10287       gfc_symtree* overriding;
10288       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
10289       gcc_assert (overriding && overriding->n.tb);
10290       if (overriding->n.tb->deferred)
10291         {
10292           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
10293                      " '%s' is DEFERRED and not overridden",
10294                      sub->name, &sub->declared_at, st->name);
10295           return FAILURE;
10296         }
10297     }
10298
10299   return SUCCESS;
10300 }
10301
10302 static gfc_try
10303 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
10304 {
10305   /* The algorithm used here is to recursively travel up the ancestry of sub
10306      and for each ancestor-type, check all bindings.  If any of them is
10307      DEFERRED, look it up starting from sub and see if the found (overriding)
10308      binding is not DEFERRED.
10309      This is not the most efficient way to do this, but it should be ok and is
10310      clearer than something sophisticated.  */
10311
10312   gcc_assert (ancestor && ancestor->attr.abstract && !sub->attr.abstract);
10313
10314   /* Walk bindings of this ancestor.  */
10315   if (ancestor->f2k_derived)
10316     {
10317       gfc_try t;
10318       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
10319       if (t == FAILURE)
10320         return FAILURE;
10321     }
10322
10323   /* Find next ancestor type and recurse on it.  */
10324   ancestor = gfc_get_derived_super_type (ancestor);
10325   if (ancestor)
10326     return ensure_not_abstract (sub, ancestor);
10327
10328   return SUCCESS;
10329 }
10330
10331
10332 static void resolve_symbol (gfc_symbol *sym);
10333
10334
10335 /* Resolve the components of a derived type.  */
10336
10337 static gfc_try
10338 resolve_fl_derived (gfc_symbol *sym)
10339 {
10340   gfc_symbol* super_type;
10341   gfc_component *c;
10342   int i;
10343
10344   super_type = gfc_get_derived_super_type (sym);
10345
10346   /* Ensure the extended type gets resolved before we do.  */
10347   if (super_type && resolve_fl_derived (super_type) == FAILURE)
10348     return FAILURE;
10349
10350   /* An ABSTRACT type must be extensible.  */
10351   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
10352     {
10353       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
10354                  sym->name, &sym->declared_at);
10355       return FAILURE;
10356     }
10357
10358   for (c = sym->components; c != NULL; c = c->next)
10359     {
10360       if (c->attr.proc_pointer && c->ts.interface)
10361         {
10362           if (c->ts.interface->attr.procedure)
10363             gfc_error ("Interface '%s', used by procedure pointer component "
10364                        "'%s' at %L, is declared in a later PROCEDURE statement",
10365                        c->ts.interface->name, c->name, &c->loc);
10366
10367           /* Get the attributes from the interface (now resolved).  */
10368           if (c->ts.interface->attr.if_source
10369               || c->ts.interface->attr.intrinsic)
10370             {
10371               gfc_symbol *ifc = c->ts.interface;
10372
10373               if (ifc->formal && !ifc->formal_ns)
10374                 resolve_symbol (ifc);
10375
10376               if (ifc->attr.intrinsic)
10377                 resolve_intrinsic (ifc, &ifc->declared_at);
10378
10379               if (ifc->result)
10380                 {
10381                   c->ts = ifc->result->ts;
10382                   c->attr.allocatable = ifc->result->attr.allocatable;
10383                   c->attr.pointer = ifc->result->attr.pointer;
10384                   c->attr.dimension = ifc->result->attr.dimension;
10385                   c->as = gfc_copy_array_spec (ifc->result->as);
10386                 }
10387               else
10388                 {   
10389                   c->ts = ifc->ts;
10390                   c->attr.allocatable = ifc->attr.allocatable;
10391                   c->attr.pointer = ifc->attr.pointer;
10392                   c->attr.dimension = ifc->attr.dimension;
10393                   c->as = gfc_copy_array_spec (ifc->as);
10394                 }
10395               c->ts.interface = ifc;
10396               c->attr.function = ifc->attr.function;
10397               c->attr.subroutine = ifc->attr.subroutine;
10398               gfc_copy_formal_args_ppc (c, ifc);
10399
10400               c->attr.pure = ifc->attr.pure;
10401               c->attr.elemental = ifc->attr.elemental;
10402               c->attr.recursive = ifc->attr.recursive;
10403               c->attr.always_explicit = ifc->attr.always_explicit;
10404               c->attr.ext_attr |= ifc->attr.ext_attr;
10405               /* Replace symbols in array spec.  */
10406               if (c->as)
10407                 {
10408                   int i;
10409                   for (i = 0; i < c->as->rank; i++)
10410                     {
10411                       gfc_expr_replace_comp (c->as->lower[i], c);
10412                       gfc_expr_replace_comp (c->as->upper[i], c);
10413                     }
10414                 }
10415               /* Copy char length.  */
10416               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
10417                 {
10418                   c->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
10419                   gfc_expr_replace_comp (c->ts.u.cl->length, c);
10420                 }
10421             }
10422           else if (c->ts.interface->name[0] != '\0')
10423             {
10424               gfc_error ("Interface '%s' of procedure pointer component "
10425                          "'%s' at %L must be explicit", c->ts.interface->name,
10426                          c->name, &c->loc);
10427               return FAILURE;
10428             }
10429         }
10430       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
10431         {
10432           /* Since PPCs are not implicitly typed, a PPC without an explicit
10433              interface must be a subroutine.  */
10434           gfc_add_subroutine (&c->attr, c->name, &c->loc);
10435         }
10436
10437       /* Procedure pointer components: Check PASS arg.  */
10438       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0)
10439         {
10440           gfc_symbol* me_arg;
10441
10442           if (c->tb->pass_arg)
10443             {
10444               gfc_formal_arglist* i;
10445
10446               /* If an explicit passing argument name is given, walk the arg-list
10447                 and look for it.  */
10448
10449               me_arg = NULL;
10450               c->tb->pass_arg_num = 1;
10451               for (i = c->formal; i; i = i->next)
10452                 {
10453                   if (!strcmp (i->sym->name, c->tb->pass_arg))
10454                     {
10455                       me_arg = i->sym;
10456                       break;
10457                     }
10458                   c->tb->pass_arg_num++;
10459                 }
10460
10461               if (!me_arg)
10462                 {
10463                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
10464                              "at %L has no argument '%s'", c->name,
10465                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
10466                   c->tb->error = 1;
10467                   return FAILURE;
10468                 }
10469             }
10470           else
10471             {
10472               /* Otherwise, take the first one; there should in fact be at least
10473                 one.  */
10474               c->tb->pass_arg_num = 1;
10475               if (!c->formal)
10476                 {
10477                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
10478                              "must have at least one argument",
10479                              c->name, &c->loc);
10480                   c->tb->error = 1;
10481                   return FAILURE;
10482                 }
10483               me_arg = c->formal->sym;
10484             }
10485
10486           /* Now check that the argument-type matches.  */
10487           gcc_assert (me_arg);
10488           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
10489               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
10490               || (me_arg->ts.type == BT_CLASS
10491                   && me_arg->ts.u.derived->components->ts.u.derived != sym))
10492             {
10493               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10494                          " the derived type '%s'", me_arg->name, c->name,
10495                          me_arg->name, &c->loc, sym->name);
10496               c->tb->error = 1;
10497               return FAILURE;
10498             }
10499
10500           /* Check for C453.  */
10501           if (me_arg->attr.dimension)
10502             {
10503               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10504                          "must be scalar", me_arg->name, c->name, me_arg->name,
10505                          &c->loc);
10506               c->tb->error = 1;
10507               return FAILURE;
10508             }
10509
10510           if (me_arg->attr.pointer)
10511             {
10512               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10513                          "may not have the POINTER attribute", me_arg->name,
10514                          c->name, me_arg->name, &c->loc);
10515               c->tb->error = 1;
10516               return FAILURE;
10517             }
10518
10519           if (me_arg->attr.allocatable)
10520             {
10521               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10522                          "may not be ALLOCATABLE", me_arg->name, c->name,
10523                          me_arg->name, &c->loc);
10524               c->tb->error = 1;
10525               return FAILURE;
10526             }
10527
10528           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
10529             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10530                        " at %L", c->name, &c->loc);
10531
10532         }
10533
10534       /* Check type-spec if this is not the parent-type component.  */
10535       if ((!sym->attr.extension || c != sym->components)
10536           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
10537         return FAILURE;
10538
10539       /* If this type is an extension, set the accessibility of the parent
10540          component.  */
10541       if (super_type && c == sym->components
10542           && strcmp (super_type->name, c->name) == 0)
10543         c->attr.access = super_type->attr.access;
10544       
10545       /* If this type is an extension, see if this component has the same name
10546          as an inherited type-bound procedure.  */
10547       if (super_type
10548           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
10549         {
10550           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
10551                      " inherited type-bound procedure",
10552                      c->name, sym->name, &c->loc);
10553           return FAILURE;
10554         }
10555
10556       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer)
10557         {
10558          if (c->ts.u.cl->length == NULL
10559              || (resolve_charlen (c->ts.u.cl) == FAILURE)
10560              || !gfc_is_constant_expr (c->ts.u.cl->length))
10561            {
10562              gfc_error ("Character length of component '%s' needs to "
10563                         "be a constant specification expression at %L",
10564                         c->name,
10565                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
10566              return FAILURE;
10567            }
10568         }
10569
10570       if (c->ts.type == BT_DERIVED
10571           && sym->component_access != ACCESS_PRIVATE
10572           && gfc_check_access (sym->attr.access, sym->ns->default_access)
10573           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
10574           && !c->ts.u.derived->attr.use_assoc
10575           && !gfc_check_access (c->ts.u.derived->attr.access,
10576                                 c->ts.u.derived->ns->default_access)
10577           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
10578                              "is a PRIVATE type and cannot be a component of "
10579                              "'%s', which is PUBLIC at %L", c->name,
10580                              sym->name, &sym->declared_at) == FAILURE)
10581         return FAILURE;
10582
10583       if (sym->attr.sequence)
10584         {
10585           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
10586             {
10587               gfc_error ("Component %s of SEQUENCE type declared at %L does "
10588                          "not have the SEQUENCE attribute",
10589                          c->ts.u.derived->name, &sym->declared_at);
10590               return FAILURE;
10591             }
10592         }
10593
10594       if (c->ts.type == BT_DERIVED && c->attr.pointer
10595           && c->ts.u.derived->components == NULL
10596           && !c->ts.u.derived->attr.zero_comp)
10597         {
10598           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
10599                      "that has not been declared", c->name, sym->name,
10600                      &c->loc);
10601           return FAILURE;
10602         }
10603
10604       /* C437.  */
10605       if (c->ts.type == BT_CLASS
10606           && !(c->ts.u.derived->components->attr.pointer
10607                || c->ts.u.derived->components->attr.allocatable))
10608         {
10609           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
10610                      "or pointer", c->name, &c->loc);
10611           return FAILURE;
10612         }
10613
10614       /* Ensure that all the derived type components are put on the
10615          derived type list; even in formal namespaces, where derived type
10616          pointer components might not have been declared.  */
10617       if (c->ts.type == BT_DERIVED
10618             && c->ts.u.derived
10619             && c->ts.u.derived->components
10620             && c->attr.pointer
10621             && sym != c->ts.u.derived)
10622         add_dt_to_dt_list (c->ts.u.derived);
10623
10624       if (c->attr.pointer || c->attr.proc_pointer || c->attr.allocatable
10625           || c->as == NULL)
10626         continue;
10627
10628       for (i = 0; i < c->as->rank; i++)
10629         {
10630           if (c->as->lower[i] == NULL
10631               || (resolve_index_expr (c->as->lower[i]) == FAILURE)
10632               || !gfc_is_constant_expr (c->as->lower[i])
10633               || c->as->upper[i] == NULL
10634               || (resolve_index_expr (c->as->upper[i]) == FAILURE)
10635               || !gfc_is_constant_expr (c->as->upper[i]))
10636             {
10637               gfc_error ("Component '%s' of '%s' at %L must have "
10638                          "constant array bounds",
10639                          c->name, sym->name, &c->loc);
10640               return FAILURE;
10641             }
10642         }
10643     }
10644
10645   /* Resolve the type-bound procedures.  */
10646   if (resolve_typebound_procedures (sym) == FAILURE)
10647     return FAILURE;
10648
10649   /* Resolve the finalizer procedures.  */
10650   if (gfc_resolve_finalizers (sym) == FAILURE)
10651     return FAILURE;
10652
10653   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
10654      all DEFERRED bindings are overridden.  */
10655   if (super_type && super_type->attr.abstract && !sym->attr.abstract
10656       && ensure_not_abstract (sym, super_type) == FAILURE)
10657     return FAILURE;
10658
10659   /* Add derived type to the derived type list.  */
10660   add_dt_to_dt_list (sym);
10661
10662   return SUCCESS;
10663 }
10664
10665
10666 static gfc_try
10667 resolve_fl_namelist (gfc_symbol *sym)
10668 {
10669   gfc_namelist *nl;
10670   gfc_symbol *nlsym;
10671
10672   /* Reject PRIVATE objects in a PUBLIC namelist.  */
10673   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
10674     {
10675       for (nl = sym->namelist; nl; nl = nl->next)
10676         {
10677           if (!nl->sym->attr.use_assoc
10678               && !is_sym_host_assoc (nl->sym, sym->ns)
10679               && !gfc_check_access(nl->sym->attr.access,
10680                                 nl->sym->ns->default_access))
10681             {
10682               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
10683                          "cannot be member of PUBLIC namelist '%s' at %L",
10684                          nl->sym->name, sym->name, &sym->declared_at);
10685               return FAILURE;
10686             }
10687
10688           /* Types with private components that came here by USE-association.  */
10689           if (nl->sym->ts.type == BT_DERIVED
10690               && derived_inaccessible (nl->sym->ts.u.derived))
10691             {
10692               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
10693                          "components and cannot be member of namelist '%s' at %L",
10694                          nl->sym->name, sym->name, &sym->declared_at);
10695               return FAILURE;
10696             }
10697
10698           /* Types with private components that are defined in the same module.  */
10699           if (nl->sym->ts.type == BT_DERIVED
10700               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
10701               && !gfc_check_access (nl->sym->ts.u.derived->attr.private_comp
10702                                         ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
10703                                         nl->sym->ns->default_access))
10704             {
10705               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
10706                          "cannot be a member of PUBLIC namelist '%s' at %L",
10707                          nl->sym->name, sym->name, &sym->declared_at);
10708               return FAILURE;
10709             }
10710         }
10711     }
10712
10713   for (nl = sym->namelist; nl; nl = nl->next)
10714     {
10715       /* Reject namelist arrays of assumed shape.  */
10716       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
10717           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
10718                              "must not have assumed shape in namelist "
10719                              "'%s' at %L", nl->sym->name, sym->name,
10720                              &sym->declared_at) == FAILURE)
10721             return FAILURE;
10722
10723       /* Reject namelist arrays that are not constant shape.  */
10724       if (is_non_constant_shape_array (nl->sym))
10725         {
10726           gfc_error ("NAMELIST array object '%s' must have constant "
10727                      "shape in namelist '%s' at %L", nl->sym->name,
10728                      sym->name, &sym->declared_at);
10729           return FAILURE;
10730         }
10731
10732       /* Namelist objects cannot have allocatable or pointer components.  */
10733       if (nl->sym->ts.type != BT_DERIVED)
10734         continue;
10735
10736       if (nl->sym->ts.u.derived->attr.alloc_comp)
10737         {
10738           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
10739                      "have ALLOCATABLE components",
10740                      nl->sym->name, sym->name, &sym->declared_at);
10741           return FAILURE;
10742         }
10743
10744       if (nl->sym->ts.u.derived->attr.pointer_comp)
10745         {
10746           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
10747                      "have POINTER components", 
10748                      nl->sym->name, sym->name, &sym->declared_at);
10749           return FAILURE;
10750         }
10751     }
10752
10753
10754   /* 14.1.2 A module or internal procedure represent local entities
10755      of the same type as a namelist member and so are not allowed.  */
10756   for (nl = sym->namelist; nl; nl = nl->next)
10757     {
10758       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
10759         continue;
10760
10761       if (nl->sym->attr.function && nl->sym == nl->sym->result)
10762         if ((nl->sym == sym->ns->proc_name)
10763                ||
10764             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
10765           continue;
10766
10767       nlsym = NULL;
10768       if (nl->sym && nl->sym->name)
10769         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
10770       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
10771         {
10772           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
10773                      "attribute in '%s' at %L", nlsym->name,
10774                      &sym->declared_at);
10775           return FAILURE;
10776         }
10777     }
10778
10779   return SUCCESS;
10780 }
10781
10782
10783 static gfc_try
10784 resolve_fl_parameter (gfc_symbol *sym)
10785 {
10786   /* A parameter array's shape needs to be constant.  */
10787   if (sym->as != NULL 
10788       && (sym->as->type == AS_DEFERRED
10789           || is_non_constant_shape_array (sym)))
10790     {
10791       gfc_error ("Parameter array '%s' at %L cannot be automatic "
10792                  "or of deferred shape", sym->name, &sym->declared_at);
10793       return FAILURE;
10794     }
10795
10796   /* Make sure a parameter that has been implicitly typed still
10797      matches the implicit type, since PARAMETER statements can precede
10798      IMPLICIT statements.  */
10799   if (sym->attr.implicit_type
10800       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
10801                                                              sym->ns)))
10802     {
10803       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
10804                  "later IMPLICIT type", sym->name, &sym->declared_at);
10805       return FAILURE;
10806     }
10807
10808   /* Make sure the types of derived parameters are consistent.  This
10809      type checking is deferred until resolution because the type may
10810      refer to a derived type from the host.  */
10811   if (sym->ts.type == BT_DERIVED
10812       && !gfc_compare_types (&sym->ts, &sym->value->ts))
10813     {
10814       gfc_error ("Incompatible derived type in PARAMETER at %L",
10815                  &sym->value->where);
10816       return FAILURE;
10817     }
10818   return SUCCESS;
10819 }
10820
10821
10822 /* Do anything necessary to resolve a symbol.  Right now, we just
10823    assume that an otherwise unknown symbol is a variable.  This sort
10824    of thing commonly happens for symbols in module.  */
10825
10826 static void
10827 resolve_symbol (gfc_symbol *sym)
10828 {
10829   int check_constant, mp_flag;
10830   gfc_symtree *symtree;
10831   gfc_symtree *this_symtree;
10832   gfc_namespace *ns;
10833   gfc_component *c;
10834
10835   if (sym->attr.flavor == FL_UNKNOWN)
10836     {
10837
10838     /* If we find that a flavorless symbol is an interface in one of the
10839        parent namespaces, find its symtree in this namespace, free the
10840        symbol and set the symtree to point to the interface symbol.  */
10841       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
10842         {
10843           symtree = gfc_find_symtree (ns->sym_root, sym->name);
10844           if (symtree && symtree->n.sym->generic)
10845             {
10846               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
10847                                                sym->name);
10848               sym->refs--;
10849               if (!sym->refs)
10850                 gfc_free_symbol (sym);
10851               symtree->n.sym->refs++;
10852               this_symtree->n.sym = symtree->n.sym;
10853               return;
10854             }
10855         }
10856
10857       /* Otherwise give it a flavor according to such attributes as
10858          it has.  */
10859       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
10860         sym->attr.flavor = FL_VARIABLE;
10861       else
10862         {
10863           sym->attr.flavor = FL_PROCEDURE;
10864           if (sym->attr.dimension)
10865             sym->attr.function = 1;
10866         }
10867     }
10868
10869   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
10870     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
10871
10872   if (sym->attr.procedure && sym->ts.interface
10873       && sym->attr.if_source != IFSRC_DECL)
10874     {
10875       if (sym->ts.interface == sym)
10876         {
10877           gfc_error ("PROCEDURE '%s' at %L may not be used as its own "
10878                      "interface", sym->name, &sym->declared_at);
10879           return;
10880         }
10881       if (sym->ts.interface->attr.procedure)
10882         {
10883           gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared"
10884                      " in a later PROCEDURE statement", sym->ts.interface->name,
10885                      sym->name,&sym->declared_at);
10886           return;
10887         }
10888
10889       /* Get the attributes from the interface (now resolved).  */
10890       if (sym->ts.interface->attr.if_source
10891           || sym->ts.interface->attr.intrinsic)
10892         {
10893           gfc_symbol *ifc = sym->ts.interface;
10894           resolve_symbol (ifc);
10895
10896           if (ifc->attr.intrinsic)
10897             resolve_intrinsic (ifc, &ifc->declared_at);
10898
10899           if (ifc->result)
10900             sym->ts = ifc->result->ts;
10901           else   
10902             sym->ts = ifc->ts;
10903           sym->ts.interface = ifc;
10904           sym->attr.function = ifc->attr.function;
10905           sym->attr.subroutine = ifc->attr.subroutine;
10906           gfc_copy_formal_args (sym, ifc);
10907
10908           sym->attr.allocatable = ifc->attr.allocatable;
10909           sym->attr.pointer = ifc->attr.pointer;
10910           sym->attr.pure = ifc->attr.pure;
10911           sym->attr.elemental = ifc->attr.elemental;
10912           sym->attr.dimension = ifc->attr.dimension;
10913           sym->attr.recursive = ifc->attr.recursive;
10914           sym->attr.always_explicit = ifc->attr.always_explicit;
10915           sym->attr.ext_attr |= ifc->attr.ext_attr;
10916           /* Copy array spec.  */
10917           sym->as = gfc_copy_array_spec (ifc->as);
10918           if (sym->as)
10919             {
10920               int i;
10921               for (i = 0; i < sym->as->rank; i++)
10922                 {
10923                   gfc_expr_replace_symbols (sym->as->lower[i], sym);
10924                   gfc_expr_replace_symbols (sym->as->upper[i], sym);
10925                 }
10926             }
10927           /* Copy char length.  */
10928           if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
10929             {
10930               sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
10931               gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
10932             }
10933         }
10934       else if (sym->ts.interface->name[0] != '\0')
10935         {
10936           gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
10937                     sym->ts.interface->name, sym->name, &sym->declared_at);
10938           return;
10939         }
10940     }
10941
10942   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
10943     return;
10944
10945   /* Symbols that are module procedures with results (functions) have
10946      the types and array specification copied for type checking in
10947      procedures that call them, as well as for saving to a module
10948      file.  These symbols can't stand the scrutiny that their results
10949      can.  */
10950   mp_flag = (sym->result != NULL && sym->result != sym);
10951
10952
10953   /* Make sure that the intrinsic is consistent with its internal 
10954      representation. This needs to be done before assigning a default 
10955      type to avoid spurious warnings.  */
10956   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
10957       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
10958     return;
10959
10960   /* Assign default type to symbols that need one and don't have one.  */
10961   if (sym->ts.type == BT_UNKNOWN)
10962     {
10963       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
10964         gfc_set_default_type (sym, 1, NULL);
10965
10966       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
10967           && !sym->attr.function && !sym->attr.subroutine
10968           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
10969         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
10970
10971       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
10972         {
10973           /* The specific case of an external procedure should emit an error
10974              in the case that there is no implicit type.  */
10975           if (!mp_flag)
10976             gfc_set_default_type (sym, sym->attr.external, NULL);
10977           else
10978             {
10979               /* Result may be in another namespace.  */
10980               resolve_symbol (sym->result);
10981
10982               if (!sym->result->attr.proc_pointer)
10983                 {
10984                   sym->ts = sym->result->ts;
10985                   sym->as = gfc_copy_array_spec (sym->result->as);
10986                   sym->attr.dimension = sym->result->attr.dimension;
10987                   sym->attr.pointer = sym->result->attr.pointer;
10988                   sym->attr.allocatable = sym->result->attr.allocatable;
10989                 }
10990             }
10991         }
10992     }
10993
10994   /* Assumed size arrays and assumed shape arrays must be dummy
10995      arguments.  */
10996
10997   if (sym->as != NULL
10998       && (sym->as->type == AS_ASSUMED_SIZE
10999           || sym->as->type == AS_ASSUMED_SHAPE)
11000       && sym->attr.dummy == 0)
11001     {
11002       if (sym->as->type == AS_ASSUMED_SIZE)
11003         gfc_error ("Assumed size array at %L must be a dummy argument",
11004                    &sym->declared_at);
11005       else
11006         gfc_error ("Assumed shape array at %L must be a dummy argument",
11007                    &sym->declared_at);
11008       return;
11009     }
11010
11011   /* Make sure symbols with known intent or optional are really dummy
11012      variable.  Because of ENTRY statement, this has to be deferred
11013      until resolution time.  */
11014
11015   if (!sym->attr.dummy
11016       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
11017     {
11018       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
11019       return;
11020     }
11021
11022   if (sym->attr.value && !sym->attr.dummy)
11023     {
11024       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
11025                  "it is not a dummy argument", sym->name, &sym->declared_at);
11026       return;
11027     }
11028
11029   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
11030     {
11031       gfc_charlen *cl = sym->ts.u.cl;
11032       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
11033         {
11034           gfc_error ("Character dummy variable '%s' at %L with VALUE "
11035                      "attribute must have constant length",
11036                      sym->name, &sym->declared_at);
11037           return;
11038         }
11039
11040       if (sym->ts.is_c_interop
11041           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
11042         {
11043           gfc_error ("C interoperable character dummy variable '%s' at %L "
11044                      "with VALUE attribute must have length one",
11045                      sym->name, &sym->declared_at);
11046           return;
11047         }
11048     }
11049
11050   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
11051      do this for something that was implicitly typed because that is handled
11052      in gfc_set_default_type.  Handle dummy arguments and procedure
11053      definitions separately.  Also, anything that is use associated is not
11054      handled here but instead is handled in the module it is declared in.
11055      Finally, derived type definitions are allowed to be BIND(C) since that
11056      only implies that they're interoperable, and they are checked fully for
11057      interoperability when a variable is declared of that type.  */
11058   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
11059       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
11060       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
11061     {
11062       gfc_try t = SUCCESS;
11063       
11064       /* First, make sure the variable is declared at the
11065          module-level scope (J3/04-007, Section 15.3).  */
11066       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
11067           sym->attr.in_common == 0)
11068         {
11069           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
11070                      "is neither a COMMON block nor declared at the "
11071                      "module level scope", sym->name, &(sym->declared_at));
11072           t = FAILURE;
11073         }
11074       else if (sym->common_head != NULL)
11075         {
11076           t = verify_com_block_vars_c_interop (sym->common_head);
11077         }
11078       else
11079         {
11080           /* If type() declaration, we need to verify that the components
11081              of the given type are all C interoperable, etc.  */
11082           if (sym->ts.type == BT_DERIVED &&
11083               sym->ts.u.derived->attr.is_c_interop != 1)
11084             {
11085               /* Make sure the user marked the derived type as BIND(C).  If
11086                  not, call the verify routine.  This could print an error
11087                  for the derived type more than once if multiple variables
11088                  of that type are declared.  */
11089               if (sym->ts.u.derived->attr.is_bind_c != 1)
11090                 verify_bind_c_derived_type (sym->ts.u.derived);
11091               t = FAILURE;
11092             }
11093           
11094           /* Verify the variable itself as C interoperable if it
11095              is BIND(C).  It is not possible for this to succeed if
11096              the verify_bind_c_derived_type failed, so don't have to handle
11097              any error returned by verify_bind_c_derived_type.  */
11098           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
11099                                  sym->common_block);
11100         }
11101
11102       if (t == FAILURE)
11103         {
11104           /* clear the is_bind_c flag to prevent reporting errors more than
11105              once if something failed.  */
11106           sym->attr.is_bind_c = 0;
11107           return;
11108         }
11109     }
11110
11111   /* If a derived type symbol has reached this point, without its
11112      type being declared, we have an error.  Notice that most
11113      conditions that produce undefined derived types have already
11114      been dealt with.  However, the likes of:
11115      implicit type(t) (t) ..... call foo (t) will get us here if
11116      the type is not declared in the scope of the implicit
11117      statement. Change the type to BT_UNKNOWN, both because it is so
11118      and to prevent an ICE.  */
11119   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
11120       && !sym->ts.u.derived->attr.zero_comp)
11121     {
11122       gfc_error ("The derived type '%s' at %L is of type '%s', "
11123                  "which has not been defined", sym->name,
11124                   &sym->declared_at, sym->ts.u.derived->name);
11125       sym->ts.type = BT_UNKNOWN;
11126       return;
11127     }
11128
11129   /* Make sure that the derived type has been resolved and that the
11130      derived type is visible in the symbol's namespace, if it is a
11131      module function and is not PRIVATE.  */
11132   if (sym->ts.type == BT_DERIVED
11133         && sym->ts.u.derived->attr.use_assoc
11134         && sym->ns->proc_name
11135         && sym->ns->proc_name->attr.flavor == FL_MODULE)
11136     {
11137       gfc_symbol *ds;
11138
11139       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
11140         return;
11141
11142       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
11143       if (!ds && sym->attr.function
11144             && gfc_check_access (sym->attr.access, sym->ns->default_access))
11145         {
11146           symtree = gfc_new_symtree (&sym->ns->sym_root,
11147                                      sym->ts.u.derived->name);
11148           symtree->n.sym = sym->ts.u.derived;
11149           sym->ts.u.derived->refs++;
11150         }
11151     }
11152
11153   /* Unless the derived-type declaration is use associated, Fortran 95
11154      does not allow public entries of private derived types.
11155      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
11156      161 in 95-006r3.  */
11157   if (sym->ts.type == BT_DERIVED
11158       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
11159       && !sym->ts.u.derived->attr.use_assoc
11160       && gfc_check_access (sym->attr.access, sym->ns->default_access)
11161       && !gfc_check_access (sym->ts.u.derived->attr.access,
11162                             sym->ts.u.derived->ns->default_access)
11163       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
11164                          "of PRIVATE derived type '%s'",
11165                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
11166                          : "variable", sym->name, &sym->declared_at,
11167                          sym->ts.u.derived->name) == FAILURE)
11168     return;
11169
11170   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
11171      default initialization is defined (5.1.2.4.4).  */
11172   if (sym->ts.type == BT_DERIVED
11173       && sym->attr.dummy
11174       && sym->attr.intent == INTENT_OUT
11175       && sym->as
11176       && sym->as->type == AS_ASSUMED_SIZE)
11177     {
11178       for (c = sym->ts.u.derived->components; c; c = c->next)
11179         {
11180           if (c->initializer)
11181             {
11182               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
11183                          "ASSUMED SIZE and so cannot have a default initializer",
11184                          sym->name, &sym->declared_at);
11185               return;
11186             }
11187         }
11188     }
11189
11190   switch (sym->attr.flavor)
11191     {
11192     case FL_VARIABLE:
11193       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
11194         return;
11195       break;
11196
11197     case FL_PROCEDURE:
11198       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
11199         return;
11200       break;
11201
11202     case FL_NAMELIST:
11203       if (resolve_fl_namelist (sym) == FAILURE)
11204         return;
11205       break;
11206
11207     case FL_PARAMETER:
11208       if (resolve_fl_parameter (sym) == FAILURE)
11209         return;
11210       break;
11211
11212     default:
11213       break;
11214     }
11215
11216   /* Resolve array specifier. Check as well some constraints
11217      on COMMON blocks.  */
11218
11219   check_constant = sym->attr.in_common && !sym->attr.pointer;
11220
11221   /* Set the formal_arg_flag so that check_conflict will not throw
11222      an error for host associated variables in the specification
11223      expression for an array_valued function.  */
11224   if (sym->attr.function && sym->as)
11225     formal_arg_flag = 1;
11226
11227   gfc_resolve_array_spec (sym->as, check_constant);
11228
11229   formal_arg_flag = 0;
11230
11231   /* Resolve formal namespaces.  */
11232   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
11233       && !sym->attr.contained && !sym->attr.intrinsic)
11234     gfc_resolve (sym->formal_ns);
11235
11236   /* Make sure the formal namespace is present.  */
11237   if (sym->formal && !sym->formal_ns)
11238     {
11239       gfc_formal_arglist *formal = sym->formal;
11240       while (formal && !formal->sym)
11241         formal = formal->next;
11242
11243       if (formal)
11244         {
11245           sym->formal_ns = formal->sym->ns;
11246           sym->formal_ns->refs++;
11247         }
11248     }
11249
11250   /* Check threadprivate restrictions.  */
11251   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
11252       && (!sym->attr.in_common
11253           && sym->module == NULL
11254           && (sym->ns->proc_name == NULL
11255               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
11256     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
11257
11258   /* If we have come this far we can apply default-initializers, as
11259      described in 14.7.5, to those variables that have not already
11260      been assigned one.  */
11261   if (sym->ts.type == BT_DERIVED
11262       && sym->attr.referenced
11263       && sym->ns == gfc_current_ns
11264       && !sym->value
11265       && !sym->attr.allocatable
11266       && !sym->attr.alloc_comp)
11267     {
11268       symbol_attribute *a = &sym->attr;
11269
11270       if ((!a->save && !a->dummy && !a->pointer
11271            && !a->in_common && !a->use_assoc
11272            && !(a->function && sym != sym->result))
11273           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
11274         apply_default_init (sym);
11275     }
11276
11277   /* If this symbol has a type-spec, check it.  */
11278   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
11279       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
11280     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
11281           == FAILURE)
11282       return;
11283 }
11284
11285
11286 /************* Resolve DATA statements *************/
11287
11288 static struct
11289 {
11290   gfc_data_value *vnode;
11291   mpz_t left;
11292 }
11293 values;
11294
11295
11296 /* Advance the values structure to point to the next value in the data list.  */
11297
11298 static gfc_try
11299 next_data_value (void)
11300 {
11301   while (mpz_cmp_ui (values.left, 0) == 0)
11302     {
11303
11304       if (values.vnode->next == NULL)
11305         return FAILURE;
11306
11307       values.vnode = values.vnode->next;
11308       mpz_set (values.left, values.vnode->repeat);
11309     }
11310
11311   return SUCCESS;
11312 }
11313
11314
11315 static gfc_try
11316 check_data_variable (gfc_data_variable *var, locus *where)
11317 {
11318   gfc_expr *e;
11319   mpz_t size;
11320   mpz_t offset;
11321   gfc_try t;
11322   ar_type mark = AR_UNKNOWN;
11323   int i;
11324   mpz_t section_index[GFC_MAX_DIMENSIONS];
11325   gfc_ref *ref;
11326   gfc_array_ref *ar;
11327   gfc_symbol *sym;
11328   int has_pointer;
11329
11330   if (gfc_resolve_expr (var->expr) == FAILURE)
11331     return FAILURE;
11332
11333   ar = NULL;
11334   mpz_init_set_si (offset, 0);
11335   e = var->expr;
11336
11337   if (e->expr_type != EXPR_VARIABLE)
11338     gfc_internal_error ("check_data_variable(): Bad expression");
11339
11340   sym = e->symtree->n.sym;
11341
11342   if (sym->ns->is_block_data && !sym->attr.in_common)
11343     {
11344       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
11345                  sym->name, &sym->declared_at);
11346     }
11347
11348   if (e->ref == NULL && sym->as)
11349     {
11350       gfc_error ("DATA array '%s' at %L must be specified in a previous"
11351                  " declaration", sym->name, where);
11352       return FAILURE;
11353     }
11354
11355   has_pointer = sym->attr.pointer;
11356
11357   for (ref = e->ref; ref; ref = ref->next)
11358     {
11359       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
11360         has_pointer = 1;
11361
11362       if (has_pointer
11363             && ref->type == REF_ARRAY
11364             && ref->u.ar.type != AR_FULL)
11365           {
11366             gfc_error ("DATA element '%s' at %L is a pointer and so must "
11367                         "be a full array", sym->name, where);
11368             return FAILURE;
11369           }
11370     }
11371
11372   if (e->rank == 0 || has_pointer)
11373     {
11374       mpz_init_set_ui (size, 1);
11375       ref = NULL;
11376     }
11377   else
11378     {
11379       ref = e->ref;
11380
11381       /* Find the array section reference.  */
11382       for (ref = e->ref; ref; ref = ref->next)
11383         {
11384           if (ref->type != REF_ARRAY)
11385             continue;
11386           if (ref->u.ar.type == AR_ELEMENT)
11387             continue;
11388           break;
11389         }
11390       gcc_assert (ref);
11391
11392       /* Set marks according to the reference pattern.  */
11393       switch (ref->u.ar.type)
11394         {
11395         case AR_FULL:
11396           mark = AR_FULL;
11397           break;
11398
11399         case AR_SECTION:
11400           ar = &ref->u.ar;
11401           /* Get the start position of array section.  */
11402           gfc_get_section_index (ar, section_index, &offset);
11403           mark = AR_SECTION;
11404           break;
11405
11406         default:
11407           gcc_unreachable ();
11408         }
11409
11410       if (gfc_array_size (e, &size) == FAILURE)
11411         {
11412           gfc_error ("Nonconstant array section at %L in DATA statement",
11413                      &e->where);
11414           mpz_clear (offset);
11415           return FAILURE;
11416         }
11417     }
11418
11419   t = SUCCESS;
11420
11421   while (mpz_cmp_ui (size, 0) > 0)
11422     {
11423       if (next_data_value () == FAILURE)
11424         {
11425           gfc_error ("DATA statement at %L has more variables than values",
11426                      where);
11427           t = FAILURE;
11428           break;
11429         }
11430
11431       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
11432       if (t == FAILURE)
11433         break;
11434
11435       /* If we have more than one element left in the repeat count,
11436          and we have more than one element left in the target variable,
11437          then create a range assignment.  */
11438       /* FIXME: Only done for full arrays for now, since array sections
11439          seem tricky.  */
11440       if (mark == AR_FULL && ref && ref->next == NULL
11441           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
11442         {
11443           mpz_t range;
11444
11445           if (mpz_cmp (size, values.left) >= 0)
11446             {
11447               mpz_init_set (range, values.left);
11448               mpz_sub (size, size, values.left);
11449               mpz_set_ui (values.left, 0);
11450             }
11451           else
11452             {
11453               mpz_init_set (range, size);
11454               mpz_sub (values.left, values.left, size);
11455               mpz_set_ui (size, 0);
11456             }
11457
11458           gfc_assign_data_value_range (var->expr, values.vnode->expr,
11459                                        offset, range);
11460
11461           mpz_add (offset, offset, range);
11462           mpz_clear (range);
11463         }
11464
11465       /* Assign initial value to symbol.  */
11466       else
11467         {
11468           mpz_sub_ui (values.left, values.left, 1);
11469           mpz_sub_ui (size, size, 1);
11470
11471           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
11472           if (t == FAILURE)
11473             break;
11474
11475           if (mark == AR_FULL)
11476             mpz_add_ui (offset, offset, 1);
11477
11478           /* Modify the array section indexes and recalculate the offset
11479              for next element.  */
11480           else if (mark == AR_SECTION)
11481             gfc_advance_section (section_index, ar, &offset);
11482         }
11483     }
11484
11485   if (mark == AR_SECTION)
11486     {
11487       for (i = 0; i < ar->dimen; i++)
11488         mpz_clear (section_index[i]);
11489     }
11490
11491   mpz_clear (size);
11492   mpz_clear (offset);
11493
11494   return t;
11495 }
11496
11497
11498 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
11499
11500 /* Iterate over a list of elements in a DATA statement.  */
11501
11502 static gfc_try
11503 traverse_data_list (gfc_data_variable *var, locus *where)
11504 {
11505   mpz_t trip;
11506   iterator_stack frame;
11507   gfc_expr *e, *start, *end, *step;
11508   gfc_try retval = SUCCESS;
11509
11510   mpz_init (frame.value);
11511
11512   start = gfc_copy_expr (var->iter.start);
11513   end = gfc_copy_expr (var->iter.end);
11514   step = gfc_copy_expr (var->iter.step);
11515
11516   if (gfc_simplify_expr (start, 1) == FAILURE
11517       || start->expr_type != EXPR_CONSTANT)
11518     {
11519       gfc_error ("iterator start at %L does not simplify", &start->where);
11520       retval = FAILURE;
11521       goto cleanup;
11522     }
11523   if (gfc_simplify_expr (end, 1) == FAILURE
11524       || end->expr_type != EXPR_CONSTANT)
11525     {
11526       gfc_error ("iterator end at %L does not simplify", &end->where);
11527       retval = FAILURE;
11528       goto cleanup;
11529     }
11530   if (gfc_simplify_expr (step, 1) == FAILURE
11531       || step->expr_type != EXPR_CONSTANT)
11532     {
11533       gfc_error ("iterator step at %L does not simplify", &step->where);
11534       retval = FAILURE;
11535       goto cleanup;
11536     }
11537
11538   mpz_init_set (trip, end->value.integer);
11539   mpz_sub (trip, trip, start->value.integer);
11540   mpz_add (trip, trip, step->value.integer);
11541
11542   mpz_div (trip, trip, step->value.integer);
11543
11544   mpz_set (frame.value, start->value.integer);
11545
11546   frame.prev = iter_stack;
11547   frame.variable = var->iter.var->symtree;
11548   iter_stack = &frame;
11549
11550   while (mpz_cmp_ui (trip, 0) > 0)
11551     {
11552       if (traverse_data_var (var->list, where) == FAILURE)
11553         {
11554           mpz_clear (trip);
11555           retval = FAILURE;
11556           goto cleanup;
11557         }
11558
11559       e = gfc_copy_expr (var->expr);
11560       if (gfc_simplify_expr (e, 1) == FAILURE)
11561         {
11562           gfc_free_expr (e);
11563           mpz_clear (trip);
11564           retval = FAILURE;
11565           goto cleanup;
11566         }
11567
11568       mpz_add (frame.value, frame.value, step->value.integer);
11569
11570       mpz_sub_ui (trip, trip, 1);
11571     }
11572
11573   mpz_clear (trip);
11574 cleanup:
11575   mpz_clear (frame.value);
11576
11577   gfc_free_expr (start);
11578   gfc_free_expr (end);
11579   gfc_free_expr (step);
11580
11581   iter_stack = frame.prev;
11582   return retval;
11583 }
11584
11585
11586 /* Type resolve variables in the variable list of a DATA statement.  */
11587
11588 static gfc_try
11589 traverse_data_var (gfc_data_variable *var, locus *where)
11590 {
11591   gfc_try t;
11592
11593   for (; var; var = var->next)
11594     {
11595       if (var->expr == NULL)
11596         t = traverse_data_list (var, where);
11597       else
11598         t = check_data_variable (var, where);
11599
11600       if (t == FAILURE)
11601         return FAILURE;
11602     }
11603
11604   return SUCCESS;
11605 }
11606
11607
11608 /* Resolve the expressions and iterators associated with a data statement.
11609    This is separate from the assignment checking because data lists should
11610    only be resolved once.  */
11611
11612 static gfc_try
11613 resolve_data_variables (gfc_data_variable *d)
11614 {
11615   for (; d; d = d->next)
11616     {
11617       if (d->list == NULL)
11618         {
11619           if (gfc_resolve_expr (d->expr) == FAILURE)
11620             return FAILURE;
11621         }
11622       else
11623         {
11624           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
11625             return FAILURE;
11626
11627           if (resolve_data_variables (d->list) == FAILURE)
11628             return FAILURE;
11629         }
11630     }
11631
11632   return SUCCESS;
11633 }
11634
11635
11636 /* Resolve a single DATA statement.  We implement this by storing a pointer to
11637    the value list into static variables, and then recursively traversing the
11638    variables list, expanding iterators and such.  */
11639
11640 static void
11641 resolve_data (gfc_data *d)
11642 {
11643
11644   if (resolve_data_variables (d->var) == FAILURE)
11645     return;
11646
11647   values.vnode = d->value;
11648   if (d->value == NULL)
11649     mpz_set_ui (values.left, 0);
11650   else
11651     mpz_set (values.left, d->value->repeat);
11652
11653   if (traverse_data_var (d->var, &d->where) == FAILURE)
11654     return;
11655
11656   /* At this point, we better not have any values left.  */
11657
11658   if (next_data_value () == SUCCESS)
11659     gfc_error ("DATA statement at %L has more values than variables",
11660                &d->where);
11661 }
11662
11663
11664 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
11665    accessed by host or use association, is a dummy argument to a pure function,
11666    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
11667    is storage associated with any such variable, shall not be used in the
11668    following contexts: (clients of this function).  */
11669
11670 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
11671    procedure.  Returns zero if assignment is OK, nonzero if there is a
11672    problem.  */
11673 int
11674 gfc_impure_variable (gfc_symbol *sym)
11675 {
11676   gfc_symbol *proc;
11677   gfc_namespace *ns;
11678
11679   if (sym->attr.use_assoc || sym->attr.in_common)
11680     return 1;
11681
11682   /* Check if the symbol's ns is inside the pure procedure.  */
11683   for (ns = gfc_current_ns; ns; ns = ns->parent)
11684     {
11685       if (ns == sym->ns)
11686         break;
11687       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
11688         return 1;
11689     }
11690
11691   proc = sym->ns->proc_name;
11692   if (sym->attr.dummy && gfc_pure (proc)
11693         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
11694                 ||
11695              proc->attr.function))
11696     return 1;
11697
11698   /* TODO: Sort out what can be storage associated, if anything, and include
11699      it here.  In principle equivalences should be scanned but it does not
11700      seem to be possible to storage associate an impure variable this way.  */
11701   return 0;
11702 }
11703
11704
11705 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
11706    current namespace is inside a pure procedure.  */
11707
11708 int
11709 gfc_pure (gfc_symbol *sym)
11710 {
11711   symbol_attribute attr;
11712   gfc_namespace *ns;
11713
11714   if (sym == NULL)
11715     {
11716       /* Check if the current namespace or one of its parents
11717         belongs to a pure procedure.  */
11718       for (ns = gfc_current_ns; ns; ns = ns->parent)
11719         {
11720           sym = ns->proc_name;
11721           if (sym == NULL)
11722             return 0;
11723           attr = sym->attr;
11724           if (attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental))
11725             return 1;
11726         }
11727       return 0;
11728     }
11729
11730   attr = sym->attr;
11731
11732   return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
11733 }
11734
11735
11736 /* Test whether the current procedure is elemental or not.  */
11737
11738 int
11739 gfc_elemental (gfc_symbol *sym)
11740 {
11741   symbol_attribute attr;
11742
11743   if (sym == NULL)
11744     sym = gfc_current_ns->proc_name;
11745   if (sym == NULL)
11746     return 0;
11747   attr = sym->attr;
11748
11749   return attr.flavor == FL_PROCEDURE && attr.elemental;
11750 }
11751
11752
11753 /* Warn about unused labels.  */
11754
11755 static void
11756 warn_unused_fortran_label (gfc_st_label *label)
11757 {
11758   if (label == NULL)
11759     return;
11760
11761   warn_unused_fortran_label (label->left);
11762
11763   if (label->defined == ST_LABEL_UNKNOWN)
11764     return;
11765
11766   switch (label->referenced)
11767     {
11768     case ST_LABEL_UNKNOWN:
11769       gfc_warning ("Label %d at %L defined but not used", label->value,
11770                    &label->where);
11771       break;
11772
11773     case ST_LABEL_BAD_TARGET:
11774       gfc_warning ("Label %d at %L defined but cannot be used",
11775                    label->value, &label->where);
11776       break;
11777
11778     default:
11779       break;
11780     }
11781
11782   warn_unused_fortran_label (label->right);
11783 }
11784
11785
11786 /* Returns the sequence type of a symbol or sequence.  */
11787
11788 static seq_type
11789 sequence_type (gfc_typespec ts)
11790 {
11791   seq_type result;
11792   gfc_component *c;
11793
11794   switch (ts.type)
11795   {
11796     case BT_DERIVED:
11797
11798       if (ts.u.derived->components == NULL)
11799         return SEQ_NONDEFAULT;
11800
11801       result = sequence_type (ts.u.derived->components->ts);
11802       for (c = ts.u.derived->components->next; c; c = c->next)
11803         if (sequence_type (c->ts) != result)
11804           return SEQ_MIXED;
11805
11806       return result;
11807
11808     case BT_CHARACTER:
11809       if (ts.kind != gfc_default_character_kind)
11810           return SEQ_NONDEFAULT;
11811
11812       return SEQ_CHARACTER;
11813
11814     case BT_INTEGER:
11815       if (ts.kind != gfc_default_integer_kind)
11816           return SEQ_NONDEFAULT;
11817
11818       return SEQ_NUMERIC;
11819
11820     case BT_REAL:
11821       if (!(ts.kind == gfc_default_real_kind
11822             || ts.kind == gfc_default_double_kind))
11823           return SEQ_NONDEFAULT;
11824
11825       return SEQ_NUMERIC;
11826
11827     case BT_COMPLEX:
11828       if (ts.kind != gfc_default_complex_kind)
11829           return SEQ_NONDEFAULT;
11830
11831       return SEQ_NUMERIC;
11832
11833     case BT_LOGICAL:
11834       if (ts.kind != gfc_default_logical_kind)
11835           return SEQ_NONDEFAULT;
11836
11837       return SEQ_NUMERIC;
11838
11839     default:
11840       return SEQ_NONDEFAULT;
11841   }
11842 }
11843
11844
11845 /* Resolve derived type EQUIVALENCE object.  */
11846
11847 static gfc_try
11848 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
11849 {
11850   gfc_component *c = derived->components;
11851
11852   if (!derived)
11853     return SUCCESS;
11854
11855   /* Shall not be an object of nonsequence derived type.  */
11856   if (!derived->attr.sequence)
11857     {
11858       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
11859                  "attribute to be an EQUIVALENCE object", sym->name,
11860                  &e->where);
11861       return FAILURE;
11862     }
11863
11864   /* Shall not have allocatable components.  */
11865   if (derived->attr.alloc_comp)
11866     {
11867       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
11868                  "components to be an EQUIVALENCE object",sym->name,
11869                  &e->where);
11870       return FAILURE;
11871     }
11872
11873   if (sym->attr.in_common && has_default_initializer (sym->ts.u.derived))
11874     {
11875       gfc_error ("Derived type variable '%s' at %L with default "
11876                  "initialization cannot be in EQUIVALENCE with a variable "
11877                  "in COMMON", sym->name, &e->where);
11878       return FAILURE;
11879     }
11880
11881   for (; c ; c = c->next)
11882     {
11883       if (c->ts.type == BT_DERIVED
11884           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
11885         return FAILURE;
11886
11887       /* Shall not be an object of sequence derived type containing a pointer
11888          in the structure.  */
11889       if (c->attr.pointer)
11890         {
11891           gfc_error ("Derived type variable '%s' at %L with pointer "
11892                      "component(s) cannot be an EQUIVALENCE object",
11893                      sym->name, &e->where);
11894           return FAILURE;
11895         }
11896     }
11897   return SUCCESS;
11898 }
11899
11900
11901 /* Resolve equivalence object. 
11902    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
11903    an allocatable array, an object of nonsequence derived type, an object of
11904    sequence derived type containing a pointer at any level of component
11905    selection, an automatic object, a function name, an entry name, a result
11906    name, a named constant, a structure component, or a subobject of any of
11907    the preceding objects.  A substring shall not have length zero.  A
11908    derived type shall not have components with default initialization nor
11909    shall two objects of an equivalence group be initialized.
11910    Either all or none of the objects shall have an protected attribute.
11911    The simple constraints are done in symbol.c(check_conflict) and the rest
11912    are implemented here.  */
11913
11914 static void
11915 resolve_equivalence (gfc_equiv *eq)
11916 {
11917   gfc_symbol *sym;
11918   gfc_symbol *first_sym;
11919   gfc_expr *e;
11920   gfc_ref *r;
11921   locus *last_where = NULL;
11922   seq_type eq_type, last_eq_type;
11923   gfc_typespec *last_ts;
11924   int object, cnt_protected;
11925   const char *msg;
11926
11927   last_ts = &eq->expr->symtree->n.sym->ts;
11928
11929   first_sym = eq->expr->symtree->n.sym;
11930
11931   cnt_protected = 0;
11932
11933   for (object = 1; eq; eq = eq->eq, object++)
11934     {
11935       e = eq->expr;
11936
11937       e->ts = e->symtree->n.sym->ts;
11938       /* match_varspec might not know yet if it is seeing
11939          array reference or substring reference, as it doesn't
11940          know the types.  */
11941       if (e->ref && e->ref->type == REF_ARRAY)
11942         {
11943           gfc_ref *ref = e->ref;
11944           sym = e->symtree->n.sym;
11945
11946           if (sym->attr.dimension)
11947             {
11948               ref->u.ar.as = sym->as;
11949               ref = ref->next;
11950             }
11951
11952           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
11953           if (e->ts.type == BT_CHARACTER
11954               && ref
11955               && ref->type == REF_ARRAY
11956               && ref->u.ar.dimen == 1
11957               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
11958               && ref->u.ar.stride[0] == NULL)
11959             {
11960               gfc_expr *start = ref->u.ar.start[0];
11961               gfc_expr *end = ref->u.ar.end[0];
11962               void *mem = NULL;
11963
11964               /* Optimize away the (:) reference.  */
11965               if (start == NULL && end == NULL)
11966                 {
11967                   if (e->ref == ref)
11968                     e->ref = ref->next;
11969                   else
11970                     e->ref->next = ref->next;
11971                   mem = ref;
11972                 }
11973               else
11974                 {
11975                   ref->type = REF_SUBSTRING;
11976                   if (start == NULL)
11977                     start = gfc_int_expr (1);
11978                   ref->u.ss.start = start;
11979                   if (end == NULL && e->ts.u.cl)
11980                     end = gfc_copy_expr (e->ts.u.cl->length);
11981                   ref->u.ss.end = end;
11982                   ref->u.ss.length = e->ts.u.cl;
11983                   e->ts.u.cl = NULL;
11984                 }
11985               ref = ref->next;
11986               gfc_free (mem);
11987             }
11988
11989           /* Any further ref is an error.  */
11990           if (ref)
11991             {
11992               gcc_assert (ref->type == REF_ARRAY);
11993               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
11994                          &ref->u.ar.where);
11995               continue;
11996             }
11997         }
11998
11999       if (gfc_resolve_expr (e) == FAILURE)
12000         continue;
12001
12002       sym = e->symtree->n.sym;
12003
12004       if (sym->attr.is_protected)
12005         cnt_protected++;
12006       if (cnt_protected > 0 && cnt_protected != object)
12007         {
12008               gfc_error ("Either all or none of the objects in the "
12009                          "EQUIVALENCE set at %L shall have the "
12010                          "PROTECTED attribute",
12011                          &e->where);
12012               break;
12013         }
12014
12015       /* Shall not equivalence common block variables in a PURE procedure.  */
12016       if (sym->ns->proc_name
12017           && sym->ns->proc_name->attr.pure
12018           && sym->attr.in_common)
12019         {
12020           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
12021                      "object in the pure procedure '%s'",
12022                      sym->name, &e->where, sym->ns->proc_name->name);
12023           break;
12024         }
12025
12026       /* Shall not be a named constant.  */
12027       if (e->expr_type == EXPR_CONSTANT)
12028         {
12029           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
12030                      "object", sym->name, &e->where);
12031           continue;
12032         }
12033
12034       if (e->ts.type == BT_DERIVED
12035           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
12036         continue;
12037
12038       /* Check that the types correspond correctly:
12039          Note 5.28:
12040          A numeric sequence structure may be equivalenced to another sequence
12041          structure, an object of default integer type, default real type, double
12042          precision real type, default logical type such that components of the
12043          structure ultimately only become associated to objects of the same
12044          kind. A character sequence structure may be equivalenced to an object
12045          of default character kind or another character sequence structure.
12046          Other objects may be equivalenced only to objects of the same type and
12047          kind parameters.  */
12048
12049       /* Identical types are unconditionally OK.  */
12050       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
12051         goto identical_types;
12052
12053       last_eq_type = sequence_type (*last_ts);
12054       eq_type = sequence_type (sym->ts);
12055
12056       /* Since the pair of objects is not of the same type, mixed or
12057          non-default sequences can be rejected.  */
12058
12059       msg = "Sequence %s with mixed components in EQUIVALENCE "
12060             "statement at %L with different type objects";
12061       if ((object ==2
12062            && last_eq_type == SEQ_MIXED
12063            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
12064               == FAILURE)
12065           || (eq_type == SEQ_MIXED
12066               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12067                                  &e->where) == FAILURE))
12068         continue;
12069
12070       msg = "Non-default type object or sequence %s in EQUIVALENCE "
12071             "statement at %L with objects of different type";
12072       if ((object ==2
12073            && last_eq_type == SEQ_NONDEFAULT
12074            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
12075                               last_where) == FAILURE)
12076           || (eq_type == SEQ_NONDEFAULT
12077               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12078                                  &e->where) == FAILURE))
12079         continue;
12080
12081       msg ="Non-CHARACTER object '%s' in default CHARACTER "
12082            "EQUIVALENCE statement at %L";
12083       if (last_eq_type == SEQ_CHARACTER
12084           && eq_type != SEQ_CHARACTER
12085           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12086                              &e->where) == FAILURE)
12087                 continue;
12088
12089       msg ="Non-NUMERIC object '%s' in default NUMERIC "
12090            "EQUIVALENCE statement at %L";
12091       if (last_eq_type == SEQ_NUMERIC
12092           && eq_type != SEQ_NUMERIC
12093           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12094                              &e->where) == FAILURE)
12095                 continue;
12096
12097   identical_types:
12098       last_ts =&sym->ts;
12099       last_where = &e->where;
12100
12101       if (!e->ref)
12102         continue;
12103
12104       /* Shall not be an automatic array.  */
12105       if (e->ref->type == REF_ARRAY
12106           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
12107         {
12108           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
12109                      "an EQUIVALENCE object", sym->name, &e->where);
12110           continue;
12111         }
12112
12113       r = e->ref;
12114       while (r)
12115         {
12116           /* Shall not be a structure component.  */
12117           if (r->type == REF_COMPONENT)
12118             {
12119               gfc_error ("Structure component '%s' at %L cannot be an "
12120                          "EQUIVALENCE object",
12121                          r->u.c.component->name, &e->where);
12122               break;
12123             }
12124
12125           /* A substring shall not have length zero.  */
12126           if (r->type == REF_SUBSTRING)
12127             {
12128               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
12129                 {
12130                   gfc_error ("Substring at %L has length zero",
12131                              &r->u.ss.start->where);
12132                   break;
12133                 }
12134             }
12135           r = r->next;
12136         }
12137     }
12138 }
12139
12140
12141 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
12142
12143 static void
12144 resolve_fntype (gfc_namespace *ns)
12145 {
12146   gfc_entry_list *el;
12147   gfc_symbol *sym;
12148
12149   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
12150     return;
12151
12152   /* If there are any entries, ns->proc_name is the entry master
12153      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
12154   if (ns->entries)
12155     sym = ns->entries->sym;
12156   else
12157     sym = ns->proc_name;
12158   if (sym->result == sym
12159       && sym->ts.type == BT_UNKNOWN
12160       && gfc_set_default_type (sym, 0, NULL) == FAILURE
12161       && !sym->attr.untyped)
12162     {
12163       gfc_error ("Function '%s' at %L has no IMPLICIT type",
12164                  sym->name, &sym->declared_at);
12165       sym->attr.untyped = 1;
12166     }
12167
12168   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
12169       && !sym->attr.contained
12170       && !gfc_check_access (sym->ts.u.derived->attr.access,
12171                             sym->ts.u.derived->ns->default_access)
12172       && gfc_check_access (sym->attr.access, sym->ns->default_access))
12173     {
12174       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
12175                       "%L of PRIVATE type '%s'", sym->name,
12176                       &sym->declared_at, sym->ts.u.derived->name);
12177     }
12178
12179     if (ns->entries)
12180     for (el = ns->entries->next; el; el = el->next)
12181       {
12182         if (el->sym->result == el->sym
12183             && el->sym->ts.type == BT_UNKNOWN
12184             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
12185             && !el->sym->attr.untyped)
12186           {
12187             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
12188                        el->sym->name, &el->sym->declared_at);
12189             el->sym->attr.untyped = 1;
12190           }
12191       }
12192 }
12193
12194
12195 /* 12.3.2.1.1 Defined operators.  */
12196
12197 static gfc_try
12198 check_uop_procedure (gfc_symbol *sym, locus where)
12199 {
12200   gfc_formal_arglist *formal;
12201
12202   if (!sym->attr.function)
12203     {
12204       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
12205                  sym->name, &where);
12206       return FAILURE;
12207     }
12208
12209   if (sym->ts.type == BT_CHARACTER
12210       && !(sym->ts.u.cl && sym->ts.u.cl->length)
12211       && !(sym->result && sym->result->ts.u.cl
12212            && sym->result->ts.u.cl->length))
12213     {
12214       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
12215                  "character length", sym->name, &where);
12216       return FAILURE;
12217     }
12218
12219   formal = sym->formal;
12220   if (!formal || !formal->sym)
12221     {
12222       gfc_error ("User operator procedure '%s' at %L must have at least "
12223                  "one argument", sym->name, &where);
12224       return FAILURE;
12225     }
12226
12227   if (formal->sym->attr.intent != INTENT_IN)
12228     {
12229       gfc_error ("First argument of operator interface at %L must be "
12230                  "INTENT(IN)", &where);
12231       return FAILURE;
12232     }
12233
12234   if (formal->sym->attr.optional)
12235     {
12236       gfc_error ("First argument of operator interface at %L cannot be "
12237                  "optional", &where);
12238       return FAILURE;
12239     }
12240
12241   formal = formal->next;
12242   if (!formal || !formal->sym)
12243     return SUCCESS;
12244
12245   if (formal->sym->attr.intent != INTENT_IN)
12246     {
12247       gfc_error ("Second argument of operator interface at %L must be "
12248                  "INTENT(IN)", &where);
12249       return FAILURE;
12250     }
12251
12252   if (formal->sym->attr.optional)
12253     {
12254       gfc_error ("Second argument of operator interface at %L cannot be "
12255                  "optional", &where);
12256       return FAILURE;
12257     }
12258
12259   if (formal->next)
12260     {
12261       gfc_error ("Operator interface at %L must have, at most, two "
12262                  "arguments", &where);
12263       return FAILURE;
12264     }
12265
12266   return SUCCESS;
12267 }
12268
12269 static void
12270 gfc_resolve_uops (gfc_symtree *symtree)
12271 {
12272   gfc_interface *itr;
12273
12274   if (symtree == NULL)
12275     return;
12276
12277   gfc_resolve_uops (symtree->left);
12278   gfc_resolve_uops (symtree->right);
12279
12280   for (itr = symtree->n.uop->op; itr; itr = itr->next)
12281     check_uop_procedure (itr->sym, itr->sym->declared_at);
12282 }
12283
12284
12285 /* Examine all of the expressions associated with a program unit,
12286    assign types to all intermediate expressions, make sure that all
12287    assignments are to compatible types and figure out which names
12288    refer to which functions or subroutines.  It doesn't check code
12289    block, which is handled by resolve_code.  */
12290
12291 static void
12292 resolve_types (gfc_namespace *ns)
12293 {
12294   gfc_namespace *n;
12295   gfc_charlen *cl;
12296   gfc_data *d;
12297   gfc_equiv *eq;
12298   gfc_namespace* old_ns = gfc_current_ns;
12299
12300   /* Check that all IMPLICIT types are ok.  */
12301   if (!ns->seen_implicit_none)
12302     {
12303       unsigned letter;
12304       for (letter = 0; letter != GFC_LETTERS; ++letter)
12305         if (ns->set_flag[letter]
12306             && resolve_typespec_used (&ns->default_type[letter],
12307                                       &ns->implicit_loc[letter],
12308                                       NULL) == FAILURE)
12309           return;
12310     }
12311
12312   gfc_current_ns = ns;
12313
12314   resolve_entries (ns);
12315
12316   resolve_common_vars (ns->blank_common.head, false);
12317   resolve_common_blocks (ns->common_root);
12318
12319   resolve_contained_functions (ns);
12320
12321   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
12322
12323   for (cl = ns->cl_list; cl; cl = cl->next)
12324     resolve_charlen (cl);
12325
12326   gfc_traverse_ns (ns, resolve_symbol);
12327
12328   resolve_fntype (ns);
12329
12330   for (n = ns->contained; n; n = n->sibling)
12331     {
12332       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
12333         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
12334                    "also be PURE", n->proc_name->name,
12335                    &n->proc_name->declared_at);
12336
12337       resolve_types (n);
12338     }
12339
12340   forall_flag = 0;
12341   gfc_check_interfaces (ns);
12342
12343   gfc_traverse_ns (ns, resolve_values);
12344
12345   if (ns->save_all)
12346     gfc_save_all (ns);
12347
12348   iter_stack = NULL;
12349   for (d = ns->data; d; d = d->next)
12350     resolve_data (d);
12351
12352   iter_stack = NULL;
12353   gfc_traverse_ns (ns, gfc_formalize_init_value);
12354
12355   gfc_traverse_ns (ns, gfc_verify_binding_labels);
12356
12357   if (ns->common_root != NULL)
12358     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
12359
12360   for (eq = ns->equiv; eq; eq = eq->next)
12361     resolve_equivalence (eq);
12362
12363   /* Warn about unused labels.  */
12364   if (warn_unused_label)
12365     warn_unused_fortran_label (ns->st_labels);
12366
12367   gfc_resolve_uops (ns->uop_root);
12368
12369   gfc_current_ns = old_ns;
12370 }
12371
12372
12373 /* Call resolve_code recursively.  */
12374
12375 static void
12376 resolve_codes (gfc_namespace *ns)
12377 {
12378   gfc_namespace *n;
12379   bitmap_obstack old_obstack;
12380
12381   for (n = ns->contained; n; n = n->sibling)
12382     resolve_codes (n);
12383
12384   gfc_current_ns = ns;
12385
12386   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
12387   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
12388     cs_base = NULL;
12389
12390   /* Set to an out of range value.  */
12391   current_entry_id = -1;
12392
12393   old_obstack = labels_obstack;
12394   bitmap_obstack_initialize (&labels_obstack);
12395
12396   resolve_code (ns->code, ns);
12397
12398   bitmap_obstack_release (&labels_obstack);
12399   labels_obstack = old_obstack;
12400 }
12401
12402
12403 /* This function is called after a complete program unit has been compiled.
12404    Its purpose is to examine all of the expressions associated with a program
12405    unit, assign types to all intermediate expressions, make sure that all
12406    assignments are to compatible types and figure out which names refer to
12407    which functions or subroutines.  */
12408
12409 void
12410 gfc_resolve (gfc_namespace *ns)
12411 {
12412   gfc_namespace *old_ns;
12413   code_stack *old_cs_base;
12414
12415   if (ns->resolved)
12416     return;
12417
12418   ns->resolved = -1;
12419   old_ns = gfc_current_ns;
12420   old_cs_base = cs_base;
12421
12422   resolve_types (ns);
12423   resolve_codes (ns);
12424
12425   gfc_current_ns = old_ns;
12426   cs_base = old_cs_base;
12427   ns->resolved = 1;
12428 }