OSDN Git Service

2010-03-03 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.name will be set.  */
2560   if (sym && sym->attr.abstract && !expr->value.function.name)
2561     {
2562       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2563                  sym->name, &expr->where);
2564       return FAILURE;
2565     }
2566
2567   /* Switch off assumed size checking and do this again for certain kinds
2568      of procedure, once the procedure itself is resolved.  */
2569   need_full_assumed_size++;
2570
2571   if (expr->symtree && expr->symtree->n.sym)
2572     p = expr->symtree->n.sym->attr.proc;
2573
2574   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2575   if (resolve_actual_arglist (expr->value.function.actual,
2576                               p, no_formal_args) == FAILURE)
2577       return FAILURE;
2578
2579   /* Need to setup the call to the correct c_associated, depending on
2580      the number of cptrs to user gives to compare.  */
2581   if (sym && sym->attr.is_iso_c == 1)
2582     {
2583       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2584           == FAILURE)
2585         return FAILURE;
2586       
2587       /* Get the symtree for the new symbol (resolved func).
2588          the old one will be freed later, when it's no longer used.  */
2589       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2590     }
2591   
2592   /* Resume assumed_size checking.  */
2593   need_full_assumed_size--;
2594
2595   /* If the procedure is external, check for usage.  */
2596   if (sym && is_external_proc (sym))
2597     resolve_global_procedure (sym, &expr->where,
2598                               &expr->value.function.actual, 0);
2599
2600   if (sym && sym->ts.type == BT_CHARACTER
2601       && sym->ts.u.cl
2602       && sym->ts.u.cl->length == NULL
2603       && !sym->attr.dummy
2604       && expr->value.function.esym == NULL
2605       && !sym->attr.contained)
2606     {
2607       /* Internal procedures are taken care of in resolve_contained_fntype.  */
2608       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2609                  "be used at %L since it is not a dummy argument",
2610                  sym->name, &expr->where);
2611       return FAILURE;
2612     }
2613
2614   /* See if function is already resolved.  */
2615
2616   if (expr->value.function.name != NULL)
2617     {
2618       if (expr->ts.type == BT_UNKNOWN)
2619         expr->ts = sym->ts;
2620       t = SUCCESS;
2621     }
2622   else
2623     {
2624       /* Apply the rules of section 14.1.2.  */
2625
2626       switch (procedure_kind (sym))
2627         {
2628         case PTYPE_GENERIC:
2629           t = resolve_generic_f (expr);
2630           break;
2631
2632         case PTYPE_SPECIFIC:
2633           t = resolve_specific_f (expr);
2634           break;
2635
2636         case PTYPE_UNKNOWN:
2637           t = resolve_unknown_f (expr);
2638           break;
2639
2640         default:
2641           gfc_internal_error ("resolve_function(): bad function type");
2642         }
2643     }
2644
2645   /* If the expression is still a function (it might have simplified),
2646      then we check to see if we are calling an elemental function.  */
2647
2648   if (expr->expr_type != EXPR_FUNCTION)
2649     return t;
2650
2651   temp = need_full_assumed_size;
2652   need_full_assumed_size = 0;
2653
2654   if (resolve_elemental_actual (expr, NULL) == FAILURE)
2655     return FAILURE;
2656
2657   if (omp_workshare_flag
2658       && expr->value.function.esym
2659       && ! gfc_elemental (expr->value.function.esym))
2660     {
2661       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2662                  "in WORKSHARE construct", expr->value.function.esym->name,
2663                  &expr->where);
2664       t = FAILURE;
2665     }
2666
2667 #define GENERIC_ID expr->value.function.isym->id
2668   else if (expr->value.function.actual != NULL
2669            && expr->value.function.isym != NULL
2670            && GENERIC_ID != GFC_ISYM_LBOUND
2671            && GENERIC_ID != GFC_ISYM_LEN
2672            && GENERIC_ID != GFC_ISYM_LOC
2673            && GENERIC_ID != GFC_ISYM_PRESENT)
2674     {
2675       /* Array intrinsics must also have the last upper bound of an
2676          assumed size array argument.  UBOUND and SIZE have to be
2677          excluded from the check if the second argument is anything
2678          than a constant.  */
2679
2680       for (arg = expr->value.function.actual; arg; arg = arg->next)
2681         {
2682           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
2683               && arg->next != NULL && arg->next->expr)
2684             {
2685               if (arg->next->expr->expr_type != EXPR_CONSTANT)
2686                 break;
2687
2688               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
2689                 break;
2690
2691               if ((int)mpz_get_si (arg->next->expr->value.integer)
2692                         < arg->expr->rank)
2693                 break;
2694             }
2695
2696           if (arg->expr != NULL
2697               && arg->expr->rank > 0
2698               && resolve_assumed_size_actual (arg->expr))
2699             return FAILURE;
2700         }
2701     }
2702 #undef GENERIC_ID
2703
2704   need_full_assumed_size = temp;
2705   name = NULL;
2706
2707   if (!pure_function (expr, &name) && name)
2708     {
2709       if (forall_flag)
2710         {
2711           gfc_error ("reference to non-PURE function '%s' at %L inside a "
2712                      "FORALL %s", name, &expr->where,
2713                      forall_flag == 2 ? "mask" : "block");
2714           t = FAILURE;
2715         }
2716       else if (gfc_pure (NULL))
2717         {
2718           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2719                      "procedure within a PURE procedure", name, &expr->where);
2720           t = FAILURE;
2721         }
2722     }
2723
2724   /* Functions without the RECURSIVE attribution are not allowed to
2725    * call themselves.  */
2726   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2727     {
2728       gfc_symbol *esym;
2729       esym = expr->value.function.esym;
2730
2731       if (is_illegal_recursion (esym, gfc_current_ns))
2732       {
2733         if (esym->attr.entry && esym->ns->entries)
2734           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
2735                      " function '%s' is not RECURSIVE",
2736                      esym->name, &expr->where, esym->ns->entries->sym->name);
2737         else
2738           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
2739                      " is not RECURSIVE", esym->name, &expr->where);
2740
2741         t = FAILURE;
2742       }
2743     }
2744
2745   /* Character lengths of use associated functions may contains references to
2746      symbols not referenced from the current program unit otherwise.  Make sure
2747      those symbols are marked as referenced.  */
2748
2749   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2750       && expr->value.function.esym->attr.use_assoc)
2751     {
2752       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
2753     }
2754
2755   if (t == SUCCESS
2756         && !((expr->value.function.esym
2757                 && expr->value.function.esym->attr.elemental)
2758                         ||
2759              (expr->value.function.isym
2760                 && expr->value.function.isym->elemental)))
2761     find_noncopying_intrinsics (expr->value.function.esym,
2762                                 expr->value.function.actual);
2763
2764   /* Make sure that the expression has a typespec that works.  */
2765   if (expr->ts.type == BT_UNKNOWN)
2766     {
2767       if (expr->symtree->n.sym->result
2768             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
2769             && !expr->symtree->n.sym->result->attr.proc_pointer)
2770         expr->ts = expr->symtree->n.sym->result->ts;
2771     }
2772
2773   return t;
2774 }
2775
2776
2777 /************* Subroutine resolution *************/
2778
2779 static void
2780 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2781 {
2782   if (gfc_pure (sym))
2783     return;
2784
2785   if (forall_flag)
2786     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2787                sym->name, &c->loc);
2788   else if (gfc_pure (NULL))
2789     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2790                &c->loc);
2791 }
2792
2793
2794 static match
2795 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2796 {
2797   gfc_symbol *s;
2798
2799   if (sym->attr.generic)
2800     {
2801       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2802       if (s != NULL)
2803         {
2804           c->resolved_sym = s;
2805           pure_subroutine (c, s);
2806           return MATCH_YES;
2807         }
2808
2809       /* TODO: Need to search for elemental references in generic interface.  */
2810     }
2811
2812   if (sym->attr.intrinsic)
2813     return gfc_intrinsic_sub_interface (c, 0);
2814
2815   return MATCH_NO;
2816 }
2817
2818
2819 static gfc_try
2820 resolve_generic_s (gfc_code *c)
2821 {
2822   gfc_symbol *sym;
2823   match m;
2824
2825   sym = c->symtree->n.sym;
2826
2827   for (;;)
2828     {
2829       m = resolve_generic_s0 (c, sym);
2830       if (m == MATCH_YES)
2831         return SUCCESS;
2832       else if (m == MATCH_ERROR)
2833         return FAILURE;
2834
2835 generic:
2836       if (sym->ns->parent == NULL)
2837         break;
2838       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2839
2840       if (sym == NULL)
2841         break;
2842       if (!generic_sym (sym))
2843         goto generic;
2844     }
2845
2846   /* Last ditch attempt.  See if the reference is to an intrinsic
2847      that possesses a matching interface.  14.1.2.4  */
2848   sym = c->symtree->n.sym;
2849
2850   if (!gfc_is_intrinsic (sym, 1, c->loc))
2851     {
2852       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2853                  sym->name, &c->loc);
2854       return FAILURE;
2855     }
2856
2857   m = gfc_intrinsic_sub_interface (c, 0);
2858   if (m == MATCH_YES)
2859     return SUCCESS;
2860   if (m == MATCH_NO)
2861     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
2862                "intrinsic subroutine interface", sym->name, &c->loc);
2863
2864   return FAILURE;
2865 }
2866
2867
2868 /* Set the name and binding label of the subroutine symbol in the call
2869    expression represented by 'c' to include the type and kind of the
2870    second parameter.  This function is for resolving the appropriate
2871    version of c_f_pointer() and c_f_procpointer().  For example, a
2872    call to c_f_pointer() for a default integer pointer could have a
2873    name of c_f_pointer_i4.  If no second arg exists, which is an error
2874    for these two functions, it defaults to the generic symbol's name
2875    and binding label.  */
2876
2877 static void
2878 set_name_and_label (gfc_code *c, gfc_symbol *sym,
2879                     char *name, char *binding_label)
2880 {
2881   gfc_expr *arg = NULL;
2882   char type;
2883   int kind;
2884
2885   /* The second arg of c_f_pointer and c_f_procpointer determines
2886      the type and kind for the procedure name.  */
2887   arg = c->ext.actual->next->expr;
2888
2889   if (arg != NULL)
2890     {
2891       /* Set up the name to have the given symbol's name,
2892          plus the type and kind.  */
2893       /* a derived type is marked with the type letter 'u' */
2894       if (arg->ts.type == BT_DERIVED)
2895         {
2896           type = 'd';
2897           kind = 0; /* set the kind as 0 for now */
2898         }
2899       else
2900         {
2901           type = gfc_type_letter (arg->ts.type);
2902           kind = arg->ts.kind;
2903         }
2904
2905       if (arg->ts.type == BT_CHARACTER)
2906         /* Kind info for character strings not needed.  */
2907         kind = 0;
2908
2909       sprintf (name, "%s_%c%d", sym->name, type, kind);
2910       /* Set up the binding label as the given symbol's label plus
2911          the type and kind.  */
2912       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
2913     }
2914   else
2915     {
2916       /* If the second arg is missing, set the name and label as
2917          was, cause it should at least be found, and the missing
2918          arg error will be caught by compare_parameters().  */
2919       sprintf (name, "%s", sym->name);
2920       sprintf (binding_label, "%s", sym->binding_label);
2921     }
2922    
2923   return;
2924 }
2925
2926
2927 /* Resolve a generic version of the iso_c_binding procedure given
2928    (sym) to the specific one based on the type and kind of the
2929    argument(s).  Currently, this function resolves c_f_pointer() and
2930    c_f_procpointer based on the type and kind of the second argument
2931    (FPTR).  Other iso_c_binding procedures aren't specially handled.
2932    Upon successfully exiting, c->resolved_sym will hold the resolved
2933    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
2934    otherwise.  */
2935
2936 match
2937 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
2938 {
2939   gfc_symbol *new_sym;
2940   /* this is fine, since we know the names won't use the max */
2941   char name[GFC_MAX_SYMBOL_LEN + 1];
2942   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2943   /* default to success; will override if find error */
2944   match m = MATCH_YES;
2945
2946   /* Make sure the actual arguments are in the necessary order (based on the 
2947      formal args) before resolving.  */
2948   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
2949
2950   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
2951       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
2952     {
2953       set_name_and_label (c, sym, name, binding_label);
2954       
2955       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
2956         {
2957           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
2958             {
2959               /* Make sure we got a third arg if the second arg has non-zero
2960                  rank.  We must also check that the type and rank are
2961                  correct since we short-circuit this check in
2962                  gfc_procedure_use() (called above to sort actual args).  */
2963               if (c->ext.actual->next->expr->rank != 0)
2964                 {
2965                   if(c->ext.actual->next->next == NULL 
2966                      || c->ext.actual->next->next->expr == NULL)
2967                     {
2968                       m = MATCH_ERROR;
2969                       gfc_error ("Missing SHAPE parameter for call to %s "
2970                                  "at %L", sym->name, &(c->loc));
2971                     }
2972                   else if (c->ext.actual->next->next->expr->ts.type
2973                            != BT_INTEGER
2974                            || c->ext.actual->next->next->expr->rank != 1)
2975                     {
2976                       m = MATCH_ERROR;
2977                       gfc_error ("SHAPE parameter for call to %s at %L must "
2978                                  "be a rank 1 INTEGER array", sym->name,
2979                                  &(c->loc));
2980                     }
2981                 }
2982             }
2983         }
2984       
2985       if (m != MATCH_ERROR)
2986         {
2987           /* the 1 means to add the optional arg to formal list */
2988           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
2989          
2990           /* for error reporting, say it's declared where the original was */
2991           new_sym->declared_at = sym->declared_at;
2992         }
2993     }
2994   else
2995     {
2996       /* no differences for c_loc or c_funloc */
2997       new_sym = sym;
2998     }
2999
3000   /* set the resolved symbol */
3001   if (m != MATCH_ERROR)
3002     c->resolved_sym = new_sym;
3003   else
3004     c->resolved_sym = sym;
3005   
3006   return m;
3007 }
3008
3009
3010 /* Resolve a subroutine call known to be specific.  */
3011
3012 static match
3013 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3014 {
3015   match m;
3016
3017   if(sym->attr.is_iso_c)
3018     {
3019       m = gfc_iso_c_sub_interface (c,sym);
3020       return m;
3021     }
3022   
3023   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3024     {
3025       if (sym->attr.dummy)
3026         {
3027           sym->attr.proc = PROC_DUMMY;
3028           goto found;
3029         }
3030
3031       sym->attr.proc = PROC_EXTERNAL;
3032       goto found;
3033     }
3034
3035   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3036     goto found;
3037
3038   if (sym->attr.intrinsic)
3039     {
3040       m = gfc_intrinsic_sub_interface (c, 1);
3041       if (m == MATCH_YES)
3042         return MATCH_YES;
3043       if (m == MATCH_NO)
3044         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3045                    "with an intrinsic", sym->name, &c->loc);
3046
3047       return MATCH_ERROR;
3048     }
3049
3050   return MATCH_NO;
3051
3052 found:
3053   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3054
3055   c->resolved_sym = sym;
3056   pure_subroutine (c, sym);
3057
3058   return MATCH_YES;
3059 }
3060
3061
3062 static gfc_try
3063 resolve_specific_s (gfc_code *c)
3064 {
3065   gfc_symbol *sym;
3066   match m;
3067
3068   sym = c->symtree->n.sym;
3069
3070   for (;;)
3071     {
3072       m = resolve_specific_s0 (c, sym);
3073       if (m == MATCH_YES)
3074         return SUCCESS;
3075       if (m == MATCH_ERROR)
3076         return FAILURE;
3077
3078       if (sym->ns->parent == NULL)
3079         break;
3080
3081       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3082
3083       if (sym == NULL)
3084         break;
3085     }
3086
3087   sym = c->symtree->n.sym;
3088   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3089              sym->name, &c->loc);
3090
3091   return FAILURE;
3092 }
3093
3094
3095 /* Resolve a subroutine call not known to be generic nor specific.  */
3096
3097 static gfc_try
3098 resolve_unknown_s (gfc_code *c)
3099 {
3100   gfc_symbol *sym;
3101
3102   sym = c->symtree->n.sym;
3103
3104   if (sym->attr.dummy)
3105     {
3106       sym->attr.proc = PROC_DUMMY;
3107       goto found;
3108     }
3109
3110   /* See if we have an intrinsic function reference.  */
3111
3112   if (gfc_is_intrinsic (sym, 1, c->loc))
3113     {
3114       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3115         return SUCCESS;
3116       return FAILURE;
3117     }
3118
3119   /* The reference is to an external name.  */
3120
3121 found:
3122   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3123
3124   c->resolved_sym = sym;
3125
3126   pure_subroutine (c, sym);
3127
3128   return SUCCESS;
3129 }
3130
3131
3132 /* Resolve a subroutine call.  Although it was tempting to use the same code
3133    for functions, subroutines and functions are stored differently and this
3134    makes things awkward.  */
3135
3136 static gfc_try
3137 resolve_call (gfc_code *c)
3138 {
3139   gfc_try t;
3140   procedure_type ptype = PROC_INTRINSIC;
3141   gfc_symbol *csym, *sym;
3142   bool no_formal_args;
3143
3144   csym = c->symtree ? c->symtree->n.sym : NULL;
3145
3146   if (csym && csym->ts.type != BT_UNKNOWN)
3147     {
3148       gfc_error ("'%s' at %L has a type, which is not consistent with "
3149                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3150       return FAILURE;
3151     }
3152
3153   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3154     {
3155       gfc_symtree *st;
3156       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3157       sym = st ? st->n.sym : NULL;
3158       if (sym && csym != sym
3159               && sym->ns == gfc_current_ns
3160               && sym->attr.flavor == FL_PROCEDURE
3161               && sym->attr.contained)
3162         {
3163           sym->refs++;
3164           if (csym->attr.generic)
3165             c->symtree->n.sym = sym;
3166           else
3167             c->symtree = st;
3168           csym = c->symtree->n.sym;
3169         }
3170     }
3171
3172   /* If this ia a deferred TBP with an abstract interface
3173      (which may of course be referenced), c->expr1 will be set.  */
3174   if (csym && csym->attr.abstract && !c->expr1)
3175     {
3176       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3177                  csym->name, &c->loc);
3178       return FAILURE;
3179     }
3180
3181   /* Subroutines without the RECURSIVE attribution are not allowed to
3182    * call themselves.  */
3183   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3184     {
3185       if (csym->attr.entry && csym->ns->entries)
3186         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3187                    " subroutine '%s' is not RECURSIVE",
3188                    csym->name, &c->loc, csym->ns->entries->sym->name);
3189       else
3190         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3191                    " is not RECURSIVE", csym->name, &c->loc);
3192
3193       t = FAILURE;
3194     }
3195
3196   /* Switch off assumed size checking and do this again for certain kinds
3197      of procedure, once the procedure itself is resolved.  */
3198   need_full_assumed_size++;
3199
3200   if (csym)
3201     ptype = csym->attr.proc;
3202
3203   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3204   if (resolve_actual_arglist (c->ext.actual, ptype,
3205                               no_formal_args) == FAILURE)
3206     return FAILURE;
3207
3208   /* Resume assumed_size checking.  */
3209   need_full_assumed_size--;
3210
3211   /* If external, check for usage.  */
3212   if (csym && is_external_proc (csym))
3213     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3214
3215   t = SUCCESS;
3216   if (c->resolved_sym == NULL)
3217     {
3218       c->resolved_isym = NULL;
3219       switch (procedure_kind (csym))
3220         {
3221         case PTYPE_GENERIC:
3222           t = resolve_generic_s (c);
3223           break;
3224
3225         case PTYPE_SPECIFIC:
3226           t = resolve_specific_s (c);
3227           break;
3228
3229         case PTYPE_UNKNOWN:
3230           t = resolve_unknown_s (c);
3231           break;
3232
3233         default:
3234           gfc_internal_error ("resolve_subroutine(): bad function type");
3235         }
3236     }
3237
3238   /* Some checks of elemental subroutine actual arguments.  */
3239   if (resolve_elemental_actual (NULL, c) == FAILURE)
3240     return FAILURE;
3241
3242   if (t == SUCCESS && !(c->resolved_sym && c->resolved_sym->attr.elemental))
3243     find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
3244   return t;
3245 }
3246
3247
3248 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3249    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3250    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3251    if their shapes do not match.  If either op1->shape or op2->shape is
3252    NULL, return SUCCESS.  */
3253
3254 static gfc_try
3255 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3256 {
3257   gfc_try t;
3258   int i;
3259
3260   t = SUCCESS;
3261
3262   if (op1->shape != NULL && op2->shape != NULL)
3263     {
3264       for (i = 0; i < op1->rank; i++)
3265         {
3266           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3267            {
3268              gfc_error ("Shapes for operands at %L and %L are not conformable",
3269                          &op1->where, &op2->where);
3270              t = FAILURE;
3271              break;
3272            }
3273         }
3274     }
3275
3276   return t;
3277 }
3278
3279
3280 /* Resolve an operator expression node.  This can involve replacing the
3281    operation with a user defined function call.  */
3282
3283 static gfc_try
3284 resolve_operator (gfc_expr *e)
3285 {
3286   gfc_expr *op1, *op2;
3287   char msg[200];
3288   bool dual_locus_error;
3289   gfc_try t;
3290
3291   /* Resolve all subnodes-- give them types.  */
3292
3293   switch (e->value.op.op)
3294     {
3295     default:
3296       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3297         return FAILURE;
3298
3299     /* Fall through...  */
3300
3301     case INTRINSIC_NOT:
3302     case INTRINSIC_UPLUS:
3303     case INTRINSIC_UMINUS:
3304     case INTRINSIC_PARENTHESES:
3305       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3306         return FAILURE;
3307       break;
3308     }
3309
3310   /* Typecheck the new node.  */
3311
3312   op1 = e->value.op.op1;
3313   op2 = e->value.op.op2;
3314   dual_locus_error = false;
3315
3316   if ((op1 && op1->expr_type == EXPR_NULL)
3317       || (op2 && op2->expr_type == EXPR_NULL))
3318     {
3319       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3320       goto bad_op;
3321     }
3322
3323   switch (e->value.op.op)
3324     {
3325     case INTRINSIC_UPLUS:
3326     case INTRINSIC_UMINUS:
3327       if (op1->ts.type == BT_INTEGER
3328           || op1->ts.type == BT_REAL
3329           || op1->ts.type == BT_COMPLEX)
3330         {
3331           e->ts = op1->ts;
3332           break;
3333         }
3334
3335       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3336                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3337       goto bad_op;
3338
3339     case INTRINSIC_PLUS:
3340     case INTRINSIC_MINUS:
3341     case INTRINSIC_TIMES:
3342     case INTRINSIC_DIVIDE:
3343     case INTRINSIC_POWER:
3344       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3345         {
3346           gfc_type_convert_binary (e, 1);
3347           break;
3348         }
3349
3350       sprintf (msg,
3351                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3352                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3353                gfc_typename (&op2->ts));
3354       goto bad_op;
3355
3356     case INTRINSIC_CONCAT:
3357       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3358           && op1->ts.kind == op2->ts.kind)
3359         {
3360           e->ts.type = BT_CHARACTER;
3361           e->ts.kind = op1->ts.kind;
3362           break;
3363         }
3364
3365       sprintf (msg,
3366                _("Operands of string concatenation operator at %%L are %s/%s"),
3367                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3368       goto bad_op;
3369
3370     case INTRINSIC_AND:
3371     case INTRINSIC_OR:
3372     case INTRINSIC_EQV:
3373     case INTRINSIC_NEQV:
3374       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3375         {
3376           e->ts.type = BT_LOGICAL;
3377           e->ts.kind = gfc_kind_max (op1, op2);
3378           if (op1->ts.kind < e->ts.kind)
3379             gfc_convert_type (op1, &e->ts, 2);
3380           else if (op2->ts.kind < e->ts.kind)
3381             gfc_convert_type (op2, &e->ts, 2);
3382           break;
3383         }
3384
3385       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3386                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3387                gfc_typename (&op2->ts));
3388
3389       goto bad_op;
3390
3391     case INTRINSIC_NOT:
3392       if (op1->ts.type == BT_LOGICAL)
3393         {
3394           e->ts.type = BT_LOGICAL;
3395           e->ts.kind = op1->ts.kind;
3396           break;
3397         }
3398
3399       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3400                gfc_typename (&op1->ts));
3401       goto bad_op;
3402
3403     case INTRINSIC_GT:
3404     case INTRINSIC_GT_OS:
3405     case INTRINSIC_GE:
3406     case INTRINSIC_GE_OS:
3407     case INTRINSIC_LT:
3408     case INTRINSIC_LT_OS:
3409     case INTRINSIC_LE:
3410     case INTRINSIC_LE_OS:
3411       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3412         {
3413           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3414           goto bad_op;
3415         }
3416
3417       /* Fall through...  */
3418
3419     case INTRINSIC_EQ:
3420     case INTRINSIC_EQ_OS:
3421     case INTRINSIC_NE:
3422     case INTRINSIC_NE_OS:
3423       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3424           && op1->ts.kind == op2->ts.kind)
3425         {
3426           e->ts.type = BT_LOGICAL;
3427           e->ts.kind = gfc_default_logical_kind;
3428           break;
3429         }
3430
3431       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3432         {
3433           gfc_type_convert_binary (e, 1);
3434
3435           e->ts.type = BT_LOGICAL;
3436           e->ts.kind = gfc_default_logical_kind;
3437           break;
3438         }
3439
3440       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3441         sprintf (msg,
3442                  _("Logicals at %%L must be compared with %s instead of %s"),
3443                  (e->value.op.op == INTRINSIC_EQ 
3444                   || e->value.op.op == INTRINSIC_EQ_OS)
3445                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3446       else
3447         sprintf (msg,
3448                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3449                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3450                  gfc_typename (&op2->ts));
3451
3452       goto bad_op;
3453
3454     case INTRINSIC_USER:
3455       if (e->value.op.uop->op == NULL)
3456         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3457       else if (op2 == NULL)
3458         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3459                  e->value.op.uop->name, gfc_typename (&op1->ts));
3460       else
3461         sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3462                  e->value.op.uop->name, gfc_typename (&op1->ts),
3463                  gfc_typename (&op2->ts));
3464
3465       goto bad_op;
3466
3467     case INTRINSIC_PARENTHESES:
3468       e->ts = op1->ts;
3469       if (e->ts.type == BT_CHARACTER)
3470         e->ts.u.cl = op1->ts.u.cl;
3471       break;
3472
3473     default:
3474       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3475     }
3476
3477   /* Deal with arrayness of an operand through an operator.  */
3478
3479   t = SUCCESS;
3480
3481   switch (e->value.op.op)
3482     {
3483     case INTRINSIC_PLUS:
3484     case INTRINSIC_MINUS:
3485     case INTRINSIC_TIMES:
3486     case INTRINSIC_DIVIDE:
3487     case INTRINSIC_POWER:
3488     case INTRINSIC_CONCAT:
3489     case INTRINSIC_AND:
3490     case INTRINSIC_OR:
3491     case INTRINSIC_EQV:
3492     case INTRINSIC_NEQV:
3493     case INTRINSIC_EQ:
3494     case INTRINSIC_EQ_OS:
3495     case INTRINSIC_NE:
3496     case INTRINSIC_NE_OS:
3497     case INTRINSIC_GT:
3498     case INTRINSIC_GT_OS:
3499     case INTRINSIC_GE:
3500     case INTRINSIC_GE_OS:
3501     case INTRINSIC_LT:
3502     case INTRINSIC_LT_OS:
3503     case INTRINSIC_LE:
3504     case INTRINSIC_LE_OS:
3505
3506       if (op1->rank == 0 && op2->rank == 0)
3507         e->rank = 0;
3508
3509       if (op1->rank == 0 && op2->rank != 0)
3510         {
3511           e->rank = op2->rank;
3512
3513           if (e->shape == NULL)
3514             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3515         }
3516
3517       if (op1->rank != 0 && op2->rank == 0)
3518         {
3519           e->rank = op1->rank;
3520
3521           if (e->shape == NULL)
3522             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3523         }
3524
3525       if (op1->rank != 0 && op2->rank != 0)
3526         {
3527           if (op1->rank == op2->rank)
3528             {
3529               e->rank = op1->rank;
3530               if (e->shape == NULL)
3531                 {
3532                   t = compare_shapes(op1, op2);
3533                   if (t == FAILURE)
3534                     e->shape = NULL;
3535                   else
3536                 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3537                 }
3538             }
3539           else
3540             {
3541               /* Allow higher level expressions to work.  */
3542               e->rank = 0;
3543
3544               /* Try user-defined operators, and otherwise throw an error.  */
3545               dual_locus_error = true;
3546               sprintf (msg,
3547                        _("Inconsistent ranks for operator at %%L and %%L"));
3548               goto bad_op;
3549             }
3550         }
3551
3552       break;
3553
3554     case INTRINSIC_PARENTHESES:
3555     case INTRINSIC_NOT:
3556     case INTRINSIC_UPLUS:
3557     case INTRINSIC_UMINUS:
3558       /* Simply copy arrayness attribute */
3559       e->rank = op1->rank;
3560
3561       if (e->shape == NULL)
3562         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3563
3564       break;
3565
3566     default:
3567       break;
3568     }
3569
3570   /* Attempt to simplify the expression.  */
3571   if (t == SUCCESS)
3572     {
3573       t = gfc_simplify_expr (e, 0);
3574       /* Some calls do not succeed in simplification and return FAILURE
3575          even though there is no error; e.g. variable references to
3576          PARAMETER arrays.  */
3577       if (!gfc_is_constant_expr (e))
3578         t = SUCCESS;
3579     }
3580   return t;
3581
3582 bad_op:
3583
3584   {
3585     bool real_error;
3586     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3587       return SUCCESS;
3588
3589     if (real_error)
3590       return FAILURE;
3591   }
3592
3593   if (dual_locus_error)
3594     gfc_error (msg, &op1->where, &op2->where);
3595   else
3596     gfc_error (msg, &e->where);
3597
3598   return FAILURE;
3599 }
3600
3601
3602 /************** Array resolution subroutines **************/
3603
3604 typedef enum
3605 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3606 comparison;
3607
3608 /* Compare two integer expressions.  */
3609
3610 static comparison
3611 compare_bound (gfc_expr *a, gfc_expr *b)
3612 {
3613   int i;
3614
3615   if (a == NULL || a->expr_type != EXPR_CONSTANT
3616       || b == NULL || b->expr_type != EXPR_CONSTANT)
3617     return CMP_UNKNOWN;
3618
3619   /* If either of the types isn't INTEGER, we must have
3620      raised an error earlier.  */
3621
3622   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3623     return CMP_UNKNOWN;
3624
3625   i = mpz_cmp (a->value.integer, b->value.integer);
3626
3627   if (i < 0)
3628     return CMP_LT;
3629   if (i > 0)
3630     return CMP_GT;
3631   return CMP_EQ;
3632 }
3633
3634
3635 /* Compare an integer expression with an integer.  */
3636
3637 static comparison
3638 compare_bound_int (gfc_expr *a, int b)
3639 {
3640   int i;
3641
3642   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3643     return CMP_UNKNOWN;
3644
3645   if (a->ts.type != BT_INTEGER)
3646     gfc_internal_error ("compare_bound_int(): Bad expression");
3647
3648   i = mpz_cmp_si (a->value.integer, b);
3649
3650   if (i < 0)
3651     return CMP_LT;
3652   if (i > 0)
3653     return CMP_GT;
3654   return CMP_EQ;
3655 }
3656
3657
3658 /* Compare an integer expression with a mpz_t.  */
3659
3660 static comparison
3661 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3662 {
3663   int i;
3664
3665   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3666     return CMP_UNKNOWN;
3667
3668   if (a->ts.type != BT_INTEGER)
3669     gfc_internal_error ("compare_bound_int(): Bad expression");
3670
3671   i = mpz_cmp (a->value.integer, b);
3672
3673   if (i < 0)
3674     return CMP_LT;
3675   if (i > 0)
3676     return CMP_GT;
3677   return CMP_EQ;
3678 }
3679
3680
3681 /* Compute the last value of a sequence given by a triplet.  
3682    Return 0 if it wasn't able to compute the last value, or if the
3683    sequence if empty, and 1 otherwise.  */
3684
3685 static int
3686 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
3687                                 gfc_expr *stride, mpz_t last)
3688 {
3689   mpz_t rem;
3690
3691   if (start == NULL || start->expr_type != EXPR_CONSTANT
3692       || end == NULL || end->expr_type != EXPR_CONSTANT
3693       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
3694     return 0;
3695
3696   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
3697       || (stride != NULL && stride->ts.type != BT_INTEGER))
3698     return 0;
3699
3700   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
3701     {
3702       if (compare_bound (start, end) == CMP_GT)
3703         return 0;
3704       mpz_set (last, end->value.integer);
3705       return 1;
3706     }
3707
3708   if (compare_bound_int (stride, 0) == CMP_GT)
3709     {
3710       /* Stride is positive */
3711       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
3712         return 0;
3713     }
3714   else
3715     {
3716       /* Stride is negative */
3717       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
3718         return 0;
3719     }
3720
3721   mpz_init (rem);
3722   mpz_sub (rem, end->value.integer, start->value.integer);
3723   mpz_tdiv_r (rem, rem, stride->value.integer);
3724   mpz_sub (last, end->value.integer, rem);
3725   mpz_clear (rem);
3726
3727   return 1;
3728 }
3729
3730
3731 /* Compare a single dimension of an array reference to the array
3732    specification.  */
3733
3734 static gfc_try
3735 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
3736 {
3737   mpz_t last_value;
3738
3739 /* Given start, end and stride values, calculate the minimum and
3740    maximum referenced indexes.  */
3741
3742   switch (ar->dimen_type[i])
3743     {
3744     case DIMEN_VECTOR:
3745       break;
3746
3747     case DIMEN_ELEMENT:
3748       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
3749         {
3750           gfc_warning ("Array reference at %L is out of bounds "
3751                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3752                        mpz_get_si (ar->start[i]->value.integer),
3753                        mpz_get_si (as->lower[i]->value.integer), i+1);
3754           return SUCCESS;
3755         }
3756       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
3757         {
3758           gfc_warning ("Array reference at %L is out of bounds "
3759                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3760                        mpz_get_si (ar->start[i]->value.integer),
3761                        mpz_get_si (as->upper[i]->value.integer), i+1);
3762           return SUCCESS;
3763         }
3764
3765       break;
3766
3767     case DIMEN_RANGE:
3768       {
3769 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
3770 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
3771
3772         comparison comp_start_end = compare_bound (AR_START, AR_END);
3773
3774         /* Check for zero stride, which is not allowed.  */
3775         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
3776           {
3777             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
3778             return FAILURE;
3779           }
3780
3781         /* if start == len || (stride > 0 && start < len)
3782                            || (stride < 0 && start > len),
3783            then the array section contains at least one element.  In this
3784            case, there is an out-of-bounds access if
3785            (start < lower || start > upper).  */
3786         if (compare_bound (AR_START, AR_END) == CMP_EQ
3787             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
3788                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
3789             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
3790                 && comp_start_end == CMP_GT))
3791           {
3792             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
3793               {
3794                 gfc_warning ("Lower array reference at %L is out of bounds "
3795                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3796                        mpz_get_si (AR_START->value.integer),
3797                        mpz_get_si (as->lower[i]->value.integer), i+1);
3798                 return SUCCESS;
3799               }
3800             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
3801               {
3802                 gfc_warning ("Lower array reference at %L is out of bounds "
3803                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3804                        mpz_get_si (AR_START->value.integer),
3805                        mpz_get_si (as->upper[i]->value.integer), i+1);
3806                 return SUCCESS;
3807               }
3808           }
3809
3810         /* If we can compute the highest index of the array section,
3811            then it also has to be between lower and upper.  */
3812         mpz_init (last_value);
3813         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
3814                                             last_value))
3815           {
3816             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
3817               {
3818                 gfc_warning ("Upper array reference at %L is out of bounds "
3819                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3820                        mpz_get_si (last_value),
3821                        mpz_get_si (as->lower[i]->value.integer), i+1);
3822                 mpz_clear (last_value);
3823                 return SUCCESS;
3824               }
3825             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
3826               {
3827                 gfc_warning ("Upper array reference at %L is out of bounds "
3828                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3829                        mpz_get_si (last_value),
3830                        mpz_get_si (as->upper[i]->value.integer), i+1);
3831                 mpz_clear (last_value);
3832                 return SUCCESS;
3833               }
3834           }
3835         mpz_clear (last_value);
3836
3837 #undef AR_START
3838 #undef AR_END
3839       }
3840       break;
3841
3842     default:
3843       gfc_internal_error ("check_dimension(): Bad array reference");
3844     }
3845
3846   return SUCCESS;
3847 }
3848
3849
3850 /* Compare an array reference with an array specification.  */
3851
3852 static gfc_try
3853 compare_spec_to_ref (gfc_array_ref *ar)
3854 {
3855   gfc_array_spec *as;
3856   int i;
3857
3858   as = ar->as;
3859   i = as->rank - 1;
3860   /* TODO: Full array sections are only allowed as actual parameters.  */
3861   if (as->type == AS_ASSUMED_SIZE
3862       && (/*ar->type == AR_FULL
3863           ||*/ (ar->type == AR_SECTION
3864               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
3865     {
3866       gfc_error ("Rightmost upper bound of assumed size array section "
3867                  "not specified at %L", &ar->where);
3868       return FAILURE;
3869     }
3870
3871   if (ar->type == AR_FULL)
3872     return SUCCESS;
3873
3874   if (as->rank != ar->dimen)
3875     {
3876       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
3877                  &ar->where, ar->dimen, as->rank);
3878       return FAILURE;
3879     }
3880
3881   for (i = 0; i < as->rank; i++)
3882     if (check_dimension (i, ar, as) == FAILURE)
3883       return FAILURE;
3884
3885   return SUCCESS;
3886 }
3887
3888
3889 /* Resolve one part of an array index.  */
3890
3891 gfc_try
3892 gfc_resolve_index (gfc_expr *index, int check_scalar)
3893 {
3894   gfc_typespec ts;
3895
3896   if (index == NULL)
3897     return SUCCESS;
3898
3899   if (gfc_resolve_expr (index) == FAILURE)
3900     return FAILURE;
3901
3902   if (check_scalar && index->rank != 0)
3903     {
3904       gfc_error ("Array index at %L must be scalar", &index->where);
3905       return FAILURE;
3906     }
3907
3908   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
3909     {
3910       gfc_error ("Array index at %L must be of INTEGER type, found %s",
3911                  &index->where, gfc_basic_typename (index->ts.type));
3912       return FAILURE;
3913     }
3914
3915   if (index->ts.type == BT_REAL)
3916     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
3917                         &index->where) == FAILURE)
3918       return FAILURE;
3919
3920   if (index->ts.kind != gfc_index_integer_kind
3921       || index->ts.type != BT_INTEGER)
3922     {
3923       gfc_clear_ts (&ts);
3924       ts.type = BT_INTEGER;
3925       ts.kind = gfc_index_integer_kind;
3926
3927       gfc_convert_type_warn (index, &ts, 2, 0);
3928     }
3929
3930   return SUCCESS;
3931 }
3932
3933 /* Resolve a dim argument to an intrinsic function.  */
3934
3935 gfc_try
3936 gfc_resolve_dim_arg (gfc_expr *dim)
3937 {
3938   if (dim == NULL)
3939     return SUCCESS;
3940
3941   if (gfc_resolve_expr (dim) == FAILURE)
3942     return FAILURE;
3943
3944   if (dim->rank != 0)
3945     {
3946       gfc_error ("Argument dim at %L must be scalar", &dim->where);
3947       return FAILURE;
3948
3949     }
3950
3951   if (dim->ts.type != BT_INTEGER)
3952     {
3953       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
3954       return FAILURE;
3955     }
3956
3957   if (dim->ts.kind != gfc_index_integer_kind)
3958     {
3959       gfc_typespec ts;
3960
3961       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 = e->value.compcall.name;
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 (tbp->n.tb->is_generic)
5182     {
5183       /* If we have to match a passed class member, force the actual
5184          expression to have the correct type.  */
5185       if (!tbp->n.tb->nopass)
5186         {
5187           if (e->value.compcall.base_object == NULL)
5188             e->value.compcall.base_object =
5189                         extract_compcall_passed_object (e);
5190
5191           e->value.compcall.base_object->ts.type = BT_DERIVED;
5192           e->value.compcall.base_object->ts.u.derived = derived;
5193         }
5194     }
5195
5196   e->value.compcall.tbp = tbp->n.tb;
5197   e->value.compcall.name = tbp->name;
5198
5199   /* Let the original expresssion catch the assertion in
5200      resolve_compcall, since this flag does not appear to be reset or
5201      copied in some systems.  */
5202   e->value.compcall.assign = 0;
5203
5204   /* Do the renaming, PASSing, generic => specific and other
5205      good things for each class member.  */
5206   class_try = (resolve_compcall (e, fcn_flag) == SUCCESS)
5207                                 ? class_try : FAILURE;
5208
5209   /* Now transfer the found symbol to the esym list.  */
5210   if (class_try == SUCCESS)
5211     {
5212       etmp = list_e->value.function.class_esym;
5213       list_e->value.function.class_esym
5214                 = gfc_get_class_esym_list();
5215       list_e->value.function.class_esym->next = etmp;
5216       list_e->value.function.class_esym->derived = derived;
5217       list_e->value.function.class_esym->esym
5218                 = e->value.function.esym;
5219     }
5220
5221   gfc_free_expr (e);
5222   
5223   /* Burrow down into grandchildren types.  */
5224   if (derived->f2k_derived)
5225     gfc_traverse_ns (derived->f2k_derived, check_members);
5226 }
5227
5228
5229 /* Eliminate esym_lists where all the members point to the
5230    typebound procedure of the declared type; ie. one where
5231    type selection has no effect..  */
5232 static void
5233 resolve_class_esym (gfc_expr *e)
5234 {
5235   gfc_class_esym_list *p, *q;
5236   bool empty = true;
5237
5238   gcc_assert (e && e->expr_type == EXPR_FUNCTION);
5239
5240   p = e->value.function.class_esym;
5241   if (p == NULL)
5242     return;
5243
5244   for (; p; p = p->next)
5245     empty = empty && (e->value.function.esym == p->esym);
5246
5247   if (empty)
5248     {
5249       p = e->value.function.class_esym;
5250       for (; p; p = q)
5251         {
5252           q = p->next;
5253           gfc_free (p);
5254         }
5255       e->value.function.class_esym = NULL;
5256    }
5257 }
5258
5259
5260 /* Generate an expression for the hash value, given the reference to
5261    the class of the final expression (class_ref), the base of the
5262    full reference list (new_ref), the declared type and the class
5263    object (st).  */
5264 static gfc_expr*
5265 hash_value_expr (gfc_ref *class_ref, gfc_ref *new_ref, gfc_symtree *st)
5266 {
5267   gfc_expr *hash_value;
5268
5269   /* Build an expression for the correct hash_value; ie. that of the last
5270      CLASS reference.  */
5271   if (class_ref)
5272     {
5273       class_ref->next = NULL;
5274     }
5275   else
5276     {
5277       gfc_free_ref_list (new_ref);
5278       new_ref = NULL;
5279     }
5280   hash_value = gfc_get_expr ();
5281   hash_value->expr_type = EXPR_VARIABLE;
5282   hash_value->symtree = st;
5283   hash_value->symtree->n.sym->refs++;
5284   hash_value->ref = new_ref;
5285   gfc_add_component_ref (hash_value, "$vptr");
5286   gfc_add_component_ref (hash_value, "$hash");
5287
5288   return hash_value;
5289 }
5290
5291
5292 /* Get the ultimate declared type from an expression.  In addition,
5293    return the last class/derived type reference and the copy of the
5294    reference list.  */
5295 static gfc_symbol*
5296 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5297                         gfc_expr *e)
5298 {
5299   gfc_symbol *declared;
5300   gfc_ref *ref;
5301
5302   declared = NULL;
5303   *class_ref = NULL;
5304   *new_ref = gfc_copy_ref (e->ref);
5305   for (ref = *new_ref; ref; ref = ref->next)
5306     {
5307       if (ref->type != REF_COMPONENT)
5308         continue;
5309
5310       if (ref->u.c.component->ts.type == BT_CLASS
5311             || ref->u.c.component->ts.type == BT_DERIVED)
5312         {
5313           declared = ref->u.c.component->ts.u.derived;
5314           *class_ref = ref;
5315         }
5316     }
5317
5318   if (declared == NULL)
5319     declared = e->symtree->n.sym->ts.u.derived;
5320
5321   return declared;
5322 }
5323
5324
5325 /* Resolve the argument expressions so that any arguments expressions
5326    that include class methods are resolved before the current call.
5327    This is necessary because of the static variables used in CLASS
5328    method resolution.  */
5329 static void
5330 resolve_arg_exprs (gfc_actual_arglist *arg)
5331
5332   /* Resolve the actual arglist expressions.  */
5333   for (; arg; arg = arg->next)
5334     {
5335       if (arg->expr)
5336         gfc_resolve_expr (arg->expr);
5337     }
5338 }
5339
5340
5341 /* Resolve a CLASS typebound function, or 'method'.  */
5342 static gfc_try
5343 resolve_class_compcall (gfc_expr* e)
5344 {
5345   gfc_symbol *derived, *declared;
5346   gfc_ref *new_ref;
5347   gfc_ref *class_ref;
5348   gfc_symtree *st;
5349
5350   st = e->symtree;
5351   class_object = st->n.sym;
5352
5353   /* Get the CLASS declared type.  */
5354   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5355
5356   /* Weed out cases of the ultimate component being a derived type.  */
5357   if (class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5358     {
5359       gfc_free_ref_list (new_ref);
5360       return resolve_compcall (e, true);
5361     }
5362
5363   /* Resolve the argument expressions,  */
5364   resolve_arg_exprs (e->value.function.actual); 
5365
5366   /* Get the data component, which is of the declared type.  */
5367   derived = declared->components->ts.u.derived;
5368
5369   /* Resolve the function call for each member of the class.  */
5370   class_try = SUCCESS;
5371   fcn_flag = true;
5372   list_e = gfc_copy_expr (e);
5373   check_class_members (derived);
5374
5375   class_try = (resolve_compcall (e, true) == SUCCESS)
5376                  ? class_try : FAILURE;
5377
5378   /* Transfer the class list to the original expression.  Note that
5379      the class_esym list is cleaned up in trans-expr.c, as the calls
5380      are translated.  */
5381   e->value.function.class_esym = list_e->value.function.class_esym;
5382   list_e->value.function.class_esym = NULL;
5383   gfc_free_expr (list_e);
5384
5385   resolve_class_esym (e);
5386
5387   /* More than one typebound procedure so transmit an expression for
5388      the hash_value as the selector.  */
5389   if (e->value.function.class_esym != NULL)
5390     e->value.function.class_esym->hash_value
5391                 = hash_value_expr (class_ref, new_ref, st);
5392
5393   return class_try;
5394 }
5395
5396 /* Resolve a CLASS typebound subroutine, or 'method'.  */
5397 static gfc_try
5398 resolve_class_typebound_call (gfc_code *code)
5399 {
5400   gfc_symbol *derived, *declared;
5401   gfc_ref *new_ref;
5402   gfc_ref *class_ref;
5403   gfc_symtree *st;
5404
5405   st = code->expr1->symtree;
5406   class_object = st->n.sym;
5407
5408   /* Get the CLASS declared type.  */
5409   declared = get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5410
5411   /* Weed out cases of the ultimate component being a derived type.  */
5412   if (class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5413     {
5414       gfc_free_ref_list (new_ref);
5415       return resolve_typebound_call (code);
5416     } 
5417
5418   /* Resolve the argument expressions,  */
5419   resolve_arg_exprs (code->expr1->value.compcall.actual); 
5420
5421   /* Get the data component, which is of the declared type.  */
5422   derived = declared->components->ts.u.derived;
5423
5424   class_try = SUCCESS;
5425   fcn_flag = false;
5426   list_e = gfc_copy_expr (code->expr1);
5427   check_class_members (derived);
5428
5429   class_try = (resolve_typebound_call (code) == SUCCESS)
5430                  ? class_try : FAILURE;
5431
5432   /* Transfer the class list to the original expression.  Note that
5433      the class_esym list is cleaned up in trans-expr.c, as the calls
5434      are translated.  */
5435   code->expr1->value.function.class_esym
5436                         = list_e->value.function.class_esym;
5437   list_e->value.function.class_esym = NULL;
5438   gfc_free_expr (list_e);
5439
5440   resolve_class_esym (code->expr1);
5441
5442   /* More than one typebound procedure so transmit an expression for
5443      the hash_value as the selector.  */
5444   if (code->expr1->value.function.class_esym != NULL)
5445     code->expr1->value.function.class_esym->hash_value
5446                 = hash_value_expr (class_ref, new_ref, st);
5447
5448   return class_try;
5449 }
5450
5451
5452 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5453
5454 static gfc_try
5455 resolve_ppc_call (gfc_code* c)
5456 {
5457   gfc_component *comp;
5458   bool b;
5459
5460   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5461   gcc_assert (b);
5462
5463   c->resolved_sym = c->expr1->symtree->n.sym;
5464   c->expr1->expr_type = EXPR_VARIABLE;
5465
5466   if (!comp->attr.subroutine)
5467     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5468
5469   if (resolve_ref (c->expr1) == FAILURE)
5470     return FAILURE;
5471
5472   if (update_ppc_arglist (c->expr1) == FAILURE)
5473     return FAILURE;
5474
5475   c->ext.actual = c->expr1->value.compcall.actual;
5476
5477   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5478                               comp->formal == NULL) == FAILURE)
5479     return FAILURE;
5480
5481   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
5482
5483   return SUCCESS;
5484 }
5485
5486
5487 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
5488
5489 static gfc_try
5490 resolve_expr_ppc (gfc_expr* e)
5491 {
5492   gfc_component *comp;
5493   bool b;
5494
5495   b = gfc_is_proc_ptr_comp (e, &comp);
5496   gcc_assert (b);
5497
5498   /* Convert to EXPR_FUNCTION.  */
5499   e->expr_type = EXPR_FUNCTION;
5500   e->value.function.isym = NULL;
5501   e->value.function.actual = e->value.compcall.actual;
5502   e->ts = comp->ts;
5503   if (comp->as != NULL)
5504     e->rank = comp->as->rank;
5505
5506   if (!comp->attr.function)
5507     gfc_add_function (&comp->attr, comp->name, &e->where);
5508
5509   if (resolve_ref (e) == FAILURE)
5510     return FAILURE;
5511
5512   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
5513                               comp->formal == NULL) == FAILURE)
5514     return FAILURE;
5515
5516   if (update_ppc_arglist (e) == FAILURE)
5517     return FAILURE;
5518
5519   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
5520
5521   return SUCCESS;
5522 }
5523
5524
5525 static bool
5526 gfc_is_expandable_expr (gfc_expr *e)
5527 {
5528   gfc_constructor *con;
5529
5530   if (e->expr_type == EXPR_ARRAY)
5531     {
5532       /* Traverse the constructor looking for variables that are flavor
5533          parameter.  Parameters must be expanded since they are fully used at
5534          compile time.  */
5535       for (con = e->value.constructor; con; con = con->next)
5536         {
5537           if (con->expr->expr_type == EXPR_VARIABLE
5538           && con->expr->symtree
5539           && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
5540               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
5541             return true;
5542           if (con->expr->expr_type == EXPR_ARRAY
5543             && gfc_is_expandable_expr (con->expr))
5544             return true;
5545         }
5546     }
5547
5548   return false;
5549 }
5550
5551 /* Resolve an expression.  That is, make sure that types of operands agree
5552    with their operators, intrinsic operators are converted to function calls
5553    for overloaded types and unresolved function references are resolved.  */
5554
5555 gfc_try
5556 gfc_resolve_expr (gfc_expr *e)
5557 {
5558   gfc_try t;
5559
5560   if (e == NULL)
5561     return SUCCESS;
5562
5563   switch (e->expr_type)
5564     {
5565     case EXPR_OP:
5566       t = resolve_operator (e);
5567       break;
5568
5569     case EXPR_FUNCTION:
5570     case EXPR_VARIABLE:
5571
5572       if (check_host_association (e))
5573         t = resolve_function (e);
5574       else
5575         {
5576           t = resolve_variable (e);
5577           if (t == SUCCESS)
5578             expression_rank (e);
5579         }
5580
5581       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
5582           && e->ref->type != REF_SUBSTRING)
5583         gfc_resolve_substring_charlen (e);
5584
5585       break;
5586
5587     case EXPR_COMPCALL:
5588       if (e->symtree && e->symtree->n.sym->ts.type == BT_CLASS)
5589         t = resolve_class_compcall (e);
5590       else
5591         t = resolve_compcall (e, true);
5592       break;
5593
5594     case EXPR_SUBSTRING:
5595       t = resolve_ref (e);
5596       break;
5597
5598     case EXPR_CONSTANT:
5599     case EXPR_NULL:
5600       t = SUCCESS;
5601       break;
5602
5603     case EXPR_PPC:
5604       t = resolve_expr_ppc (e);
5605       break;
5606
5607     case EXPR_ARRAY:
5608       t = FAILURE;
5609       if (resolve_ref (e) == FAILURE)
5610         break;
5611
5612       t = gfc_resolve_array_constructor (e);
5613       /* Also try to expand a constructor.  */
5614       if (t == SUCCESS)
5615         {
5616           expression_rank (e);
5617           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
5618             gfc_expand_constructor (e);
5619         }
5620
5621       /* This provides the opportunity for the length of constructors with
5622          character valued function elements to propagate the string length
5623          to the expression.  */
5624       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
5625         {
5626           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
5627              here rather then add a duplicate test for it above.  */ 
5628           gfc_expand_constructor (e);
5629           t = gfc_resolve_character_array_constructor (e);
5630         }
5631
5632       break;
5633
5634     case EXPR_STRUCTURE:
5635       t = resolve_ref (e);
5636       if (t == FAILURE)
5637         break;
5638
5639       t = resolve_structure_cons (e);
5640       if (t == FAILURE)
5641         break;
5642
5643       t = gfc_simplify_expr (e, 0);
5644       break;
5645
5646     default:
5647       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
5648     }
5649
5650   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
5651     fixup_charlen (e);
5652
5653   return t;
5654 }
5655
5656
5657 /* Resolve an expression from an iterator.  They must be scalar and have
5658    INTEGER or (optionally) REAL type.  */
5659
5660 static gfc_try
5661 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
5662                            const char *name_msgid)
5663 {
5664   if (gfc_resolve_expr (expr) == FAILURE)
5665     return FAILURE;
5666
5667   if (expr->rank != 0)
5668     {
5669       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
5670       return FAILURE;
5671     }
5672
5673   if (expr->ts.type != BT_INTEGER)
5674     {
5675       if (expr->ts.type == BT_REAL)
5676         {
5677           if (real_ok)
5678             return gfc_notify_std (GFC_STD_F95_DEL,
5679                                    "Deleted feature: %s at %L must be integer",
5680                                    _(name_msgid), &expr->where);
5681           else
5682             {
5683               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
5684                          &expr->where);
5685               return FAILURE;
5686             }
5687         }
5688       else
5689         {
5690           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
5691           return FAILURE;
5692         }
5693     }
5694   return SUCCESS;
5695 }
5696
5697
5698 /* Resolve the expressions in an iterator structure.  If REAL_OK is
5699    false allow only INTEGER type iterators, otherwise allow REAL types.  */
5700
5701 gfc_try
5702 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
5703 {
5704   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
5705       == FAILURE)
5706     return FAILURE;
5707
5708   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
5709     {
5710       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
5711                  &iter->var->where);
5712       return FAILURE;
5713     }
5714
5715   if (gfc_resolve_iterator_expr (iter->start, real_ok,
5716                                  "Start expression in DO loop") == FAILURE)
5717     return FAILURE;
5718
5719   if (gfc_resolve_iterator_expr (iter->end, real_ok,
5720                                  "End expression in DO loop") == FAILURE)
5721     return FAILURE;
5722
5723   if (gfc_resolve_iterator_expr (iter->step, real_ok,
5724                                  "Step expression in DO loop") == FAILURE)
5725     return FAILURE;
5726
5727   if (iter->step->expr_type == EXPR_CONSTANT)
5728     {
5729       if ((iter->step->ts.type == BT_INTEGER
5730            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
5731           || (iter->step->ts.type == BT_REAL
5732               && mpfr_sgn (iter->step->value.real) == 0))
5733         {
5734           gfc_error ("Step expression in DO loop at %L cannot be zero",
5735                      &iter->step->where);
5736           return FAILURE;
5737         }
5738     }
5739
5740   /* Convert start, end, and step to the same type as var.  */
5741   if (iter->start->ts.kind != iter->var->ts.kind
5742       || iter->start->ts.type != iter->var->ts.type)
5743     gfc_convert_type (iter->start, &iter->var->ts, 2);
5744
5745   if (iter->end->ts.kind != iter->var->ts.kind
5746       || iter->end->ts.type != iter->var->ts.type)
5747     gfc_convert_type (iter->end, &iter->var->ts, 2);
5748
5749   if (iter->step->ts.kind != iter->var->ts.kind
5750       || iter->step->ts.type != iter->var->ts.type)
5751     gfc_convert_type (iter->step, &iter->var->ts, 2);
5752
5753   if (iter->start->expr_type == EXPR_CONSTANT
5754       && iter->end->expr_type == EXPR_CONSTANT
5755       && iter->step->expr_type == EXPR_CONSTANT)
5756     {
5757       int sgn, cmp;
5758       if (iter->start->ts.type == BT_INTEGER)
5759         {
5760           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
5761           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
5762         }
5763       else
5764         {
5765           sgn = mpfr_sgn (iter->step->value.real);
5766           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
5767         }
5768       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
5769         gfc_warning ("DO loop at %L will be executed zero times",
5770                      &iter->step->where);
5771     }
5772
5773   return SUCCESS;
5774 }
5775
5776
5777 /* Traversal function for find_forall_index.  f == 2 signals that
5778    that variable itself is not to be checked - only the references.  */
5779
5780 static bool
5781 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
5782 {
5783   if (expr->expr_type != EXPR_VARIABLE)
5784     return false;
5785   
5786   /* A scalar assignment  */
5787   if (!expr->ref || *f == 1)
5788     {
5789       if (expr->symtree->n.sym == sym)
5790         return true;
5791       else
5792         return false;
5793     }
5794
5795   if (*f == 2)
5796     *f = 1;
5797   return false;
5798 }
5799
5800
5801 /* Check whether the FORALL index appears in the expression or not.
5802    Returns SUCCESS if SYM is found in EXPR.  */
5803
5804 gfc_try
5805 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
5806 {
5807   if (gfc_traverse_expr (expr, sym, forall_index, f))
5808     return SUCCESS;
5809   else
5810     return FAILURE;
5811 }
5812
5813
5814 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
5815    to be a scalar INTEGER variable.  The subscripts and stride are scalar
5816    INTEGERs, and if stride is a constant it must be nonzero.
5817    Furthermore "A subscript or stride in a forall-triplet-spec shall
5818    not contain a reference to any index-name in the
5819    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
5820
5821 static void
5822 resolve_forall_iterators (gfc_forall_iterator *it)
5823 {
5824   gfc_forall_iterator *iter, *iter2;
5825
5826   for (iter = it; iter; iter = iter->next)
5827     {
5828       if (gfc_resolve_expr (iter->var) == SUCCESS
5829           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
5830         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
5831                    &iter->var->where);
5832
5833       if (gfc_resolve_expr (iter->start) == SUCCESS
5834           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
5835         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
5836                    &iter->start->where);
5837       if (iter->var->ts.kind != iter->start->ts.kind)
5838         gfc_convert_type (iter->start, &iter->var->ts, 2);
5839
5840       if (gfc_resolve_expr (iter->end) == SUCCESS
5841           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
5842         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
5843                    &iter->end->where);
5844       if (iter->var->ts.kind != iter->end->ts.kind)
5845         gfc_convert_type (iter->end, &iter->var->ts, 2);
5846
5847       if (gfc_resolve_expr (iter->stride) == SUCCESS)
5848         {
5849           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
5850             gfc_error ("FORALL stride expression at %L must be a scalar %s",
5851                        &iter->stride->where, "INTEGER");
5852
5853           if (iter->stride->expr_type == EXPR_CONSTANT
5854               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
5855             gfc_error ("FORALL stride expression at %L cannot be zero",
5856                        &iter->stride->where);
5857         }
5858       if (iter->var->ts.kind != iter->stride->ts.kind)
5859         gfc_convert_type (iter->stride, &iter->var->ts, 2);
5860     }
5861
5862   for (iter = it; iter; iter = iter->next)
5863     for (iter2 = iter; iter2; iter2 = iter2->next)
5864       {
5865         if (find_forall_index (iter2->start,
5866                                iter->var->symtree->n.sym, 0) == SUCCESS
5867             || find_forall_index (iter2->end,
5868                                   iter->var->symtree->n.sym, 0) == SUCCESS
5869             || find_forall_index (iter2->stride,
5870                                   iter->var->symtree->n.sym, 0) == SUCCESS)
5871           gfc_error ("FORALL index '%s' may not appear in triplet "
5872                      "specification at %L", iter->var->symtree->name,
5873                      &iter2->start->where);
5874       }
5875 }
5876
5877
5878 /* Given a pointer to a symbol that is a derived type, see if it's
5879    inaccessible, i.e. if it's defined in another module and the components are
5880    PRIVATE.  The search is recursive if necessary.  Returns zero if no
5881    inaccessible components are found, nonzero otherwise.  */
5882
5883 static int
5884 derived_inaccessible (gfc_symbol *sym)
5885 {
5886   gfc_component *c;
5887
5888   if (sym->attr.use_assoc && sym->attr.private_comp)
5889     return 1;
5890
5891   for (c = sym->components; c; c = c->next)
5892     {
5893         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
5894           return 1;
5895     }
5896
5897   return 0;
5898 }
5899
5900
5901 /* Resolve the argument of a deallocate expression.  The expression must be
5902    a pointer or a full array.  */
5903
5904 static gfc_try
5905 resolve_deallocate_expr (gfc_expr *e)
5906 {
5907   symbol_attribute attr;
5908   int allocatable, pointer, check_intent_in;
5909   gfc_ref *ref;
5910   gfc_symbol *sym;
5911   gfc_component *c;
5912
5913   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
5914   check_intent_in = 1;
5915
5916   if (gfc_resolve_expr (e) == FAILURE)
5917     return FAILURE;
5918
5919   if (e->expr_type != EXPR_VARIABLE)
5920     goto bad;
5921
5922   sym = e->symtree->n.sym;
5923
5924   if (sym->ts.type == BT_CLASS)
5925     {
5926       allocatable = sym->ts.u.derived->components->attr.allocatable;
5927       pointer = sym->ts.u.derived->components->attr.pointer;
5928     }
5929   else
5930     {
5931       allocatable = sym->attr.allocatable;
5932       pointer = sym->attr.pointer;
5933     }
5934   for (ref = e->ref; ref; ref = ref->next)
5935     {
5936       if (pointer)
5937         check_intent_in = 0;
5938
5939       switch (ref->type)
5940         {
5941         case REF_ARRAY:
5942           if (ref->u.ar.type != AR_FULL)
5943             allocatable = 0;
5944           break;
5945
5946         case REF_COMPONENT:
5947           c = ref->u.c.component;
5948           if (c->ts.type == BT_CLASS)
5949             {
5950               allocatable = c->ts.u.derived->components->attr.allocatable;
5951               pointer = c->ts.u.derived->components->attr.pointer;
5952             }
5953           else
5954             {
5955               allocatable = c->attr.allocatable;
5956               pointer = c->attr.pointer;
5957             }
5958           break;
5959
5960         case REF_SUBSTRING:
5961           allocatable = 0;
5962           break;
5963         }
5964     }
5965
5966   attr = gfc_expr_attr (e);
5967
5968   if (allocatable == 0 && attr.pointer == 0)
5969     {
5970     bad:
5971       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
5972                  &e->where);
5973     }
5974
5975   if (check_intent_in && sym->attr.intent == INTENT_IN)
5976     {
5977       gfc_error ("Cannot deallocate INTENT(IN) variable '%s' at %L",
5978                  sym->name, &e->where);
5979       return FAILURE;
5980     }
5981
5982   if (e->ts.type == BT_CLASS)
5983     {
5984       /* Only deallocate the DATA component.  */
5985       gfc_add_component_ref (e, "$data");
5986     }
5987
5988   return SUCCESS;
5989 }
5990
5991
5992 /* Returns true if the expression e contains a reference to the symbol sym.  */
5993 static bool
5994 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
5995 {
5996   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
5997     return true;
5998
5999   return false;
6000 }
6001
6002 bool
6003 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6004 {
6005   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6006 }
6007
6008
6009 /* Given the expression node e for an allocatable/pointer of derived type to be
6010    allocated, get the expression node to be initialized afterwards (needed for
6011    derived types with default initializers, and derived types with allocatable
6012    components that need nullification.)  */
6013
6014 gfc_expr *
6015 gfc_expr_to_initialize (gfc_expr *e)
6016 {
6017   gfc_expr *result;
6018   gfc_ref *ref;
6019   int i;
6020
6021   result = gfc_copy_expr (e);
6022
6023   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6024   for (ref = result->ref; ref; ref = ref->next)
6025     if (ref->type == REF_ARRAY && ref->next == NULL)
6026       {
6027         ref->u.ar.type = AR_FULL;
6028
6029         for (i = 0; i < ref->u.ar.dimen; i++)
6030           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6031
6032         result->rank = ref->u.ar.dimen;
6033         break;
6034       }
6035
6036   return result;
6037 }
6038
6039
6040 /* Used in resolve_allocate_expr to check that a allocation-object and
6041    a source-expr are conformable.  This does not catch all possible 
6042    cases; in particular a runtime checking is needed.  */
6043
6044 static gfc_try
6045 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6046 {
6047   /* First compare rank.  */
6048   if (e2->ref && e1->rank != e2->ref->u.ar.as->rank)
6049     {
6050       gfc_error ("Source-expr at %L must be scalar or have the "
6051                  "same rank as the allocate-object at %L",
6052                  &e1->where, &e2->where);
6053       return FAILURE;
6054     }
6055
6056   if (e1->shape)
6057     {
6058       int i;
6059       mpz_t s;
6060
6061       mpz_init (s);
6062
6063       for (i = 0; i < e1->rank; i++)
6064         {
6065           if (e2->ref->u.ar.end[i])
6066             {
6067               mpz_set (s, e2->ref->u.ar.end[i]->value.integer);
6068               mpz_sub (s, s, e2->ref->u.ar.start[i]->value.integer);
6069               mpz_add_ui (s, s, 1);
6070             }
6071           else
6072             {
6073               mpz_set (s, e2->ref->u.ar.start[i]->value.integer);
6074             }
6075
6076           if (mpz_cmp (e1->shape[i], s) != 0)
6077             {
6078               gfc_error ("Source-expr at %L and allocate-object at %L must "
6079                          "have the same shape", &e1->where, &e2->where);
6080               mpz_clear (s);
6081               return FAILURE;
6082             }
6083         }
6084
6085       mpz_clear (s);
6086     }
6087
6088   return SUCCESS;
6089 }
6090
6091
6092 /* Resolve the expression in an ALLOCATE statement, doing the additional
6093    checks to see whether the expression is OK or not.  The expression must
6094    have a trailing array reference that gives the size of the array.  */
6095
6096 static gfc_try
6097 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6098 {
6099   int i, pointer, allocatable, dimension, check_intent_in, is_abstract;
6100   symbol_attribute attr;
6101   gfc_ref *ref, *ref2;
6102   gfc_array_ref *ar;
6103   gfc_symbol *sym;
6104   gfc_alloc *a;
6105   gfc_component *c;
6106   gfc_expr *init_e;
6107
6108   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
6109   check_intent_in = 1;
6110
6111   if (gfc_resolve_expr (e) == FAILURE)
6112     return FAILURE;
6113
6114   /* Make sure the expression is allocatable or a pointer.  If it is
6115      pointer, the next-to-last reference must be a pointer.  */
6116
6117   ref2 = NULL;
6118   if (e->symtree)
6119     sym = e->symtree->n.sym;
6120
6121   /* Check whether ultimate component is abstract and CLASS.  */
6122   is_abstract = 0;
6123
6124   if (e->expr_type != EXPR_VARIABLE)
6125     {
6126       allocatable = 0;
6127       attr = gfc_expr_attr (e);
6128       pointer = attr.pointer;
6129       dimension = attr.dimension;
6130     }
6131   else
6132     {
6133       if (sym->ts.type == BT_CLASS)
6134         {
6135           allocatable = sym->ts.u.derived->components->attr.allocatable;
6136           pointer = sym->ts.u.derived->components->attr.pointer;
6137           dimension = sym->ts.u.derived->components->attr.dimension;
6138           is_abstract = sym->ts.u.derived->components->attr.abstract;
6139         }
6140       else
6141         {
6142           allocatable = sym->attr.allocatable;
6143           pointer = sym->attr.pointer;
6144           dimension = sym->attr.dimension;
6145         }
6146
6147       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6148         {
6149           if (pointer)
6150             check_intent_in = 0;
6151
6152           switch (ref->type)
6153             {
6154               case REF_ARRAY:
6155                 if (ref->next != NULL)
6156                   pointer = 0;
6157                 break;
6158
6159               case REF_COMPONENT:
6160                 c = ref->u.c.component;
6161                 if (c->ts.type == BT_CLASS)
6162                   {
6163                     allocatable = c->ts.u.derived->components->attr.allocatable;
6164                     pointer = c->ts.u.derived->components->attr.pointer;
6165                     dimension = c->ts.u.derived->components->attr.dimension;
6166                     is_abstract = c->ts.u.derived->components->attr.abstract;
6167                   }
6168                 else
6169                   {
6170                     allocatable = c->attr.allocatable;
6171                     pointer = c->attr.pointer;
6172                     dimension = c->attr.dimension;
6173                     is_abstract = c->attr.abstract;
6174                   }
6175                 break;
6176
6177               case REF_SUBSTRING:
6178                 allocatable = 0;
6179                 pointer = 0;
6180                 break;
6181             }
6182         }
6183     }
6184
6185   if (allocatable == 0 && pointer == 0)
6186     {
6187       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6188                  &e->where);
6189       return FAILURE;
6190     }
6191
6192   /* Some checks for the SOURCE tag.  */
6193   if (code->expr3)
6194     {
6195       /* Check F03:C631.  */
6196       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6197         {
6198           gfc_error ("Type of entity at %L is type incompatible with "
6199                       "source-expr at %L", &e->where, &code->expr3->where);
6200           return FAILURE;
6201         }
6202
6203       /* Check F03:C632 and restriction following Note 6.18.  */
6204       if (code->expr3->rank > 0
6205           && conformable_arrays (code->expr3, e) == FAILURE)
6206         return FAILURE;
6207
6208       /* Check F03:C633.  */
6209       if (code->expr3->ts.kind != e->ts.kind)
6210         {
6211           gfc_error ("The allocate-object at %L and the source-expr at %L "
6212                       "shall have the same kind type parameter",
6213                       &e->where, &code->expr3->where);
6214           return FAILURE;
6215         }
6216     }
6217   else if (is_abstract&& code->ext.alloc.ts.type == BT_UNKNOWN)
6218     {
6219       gcc_assert (e->ts.type == BT_CLASS);
6220       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6221                  "type-spec or SOURCE=", sym->name, &e->where);
6222       return FAILURE;
6223     }
6224
6225   if (check_intent_in && sym->attr.intent == INTENT_IN)
6226     {
6227       gfc_error ("Cannot allocate INTENT(IN) variable '%s' at %L",
6228                  sym->name, &e->where);
6229       return FAILURE;
6230     }
6231     
6232   if (!code->expr3)
6233     {
6234       /* Add default initializer for those derived types that need them.  */
6235       if (e->ts.type == BT_DERIVED
6236           && (init_e = gfc_default_initializer (&e->ts)))
6237         {
6238           gfc_code *init_st = gfc_get_code ();
6239           init_st->loc = code->loc;
6240           init_st->op = EXEC_INIT_ASSIGN;
6241           init_st->expr1 = gfc_expr_to_initialize (e);
6242           init_st->expr2 = init_e;
6243           init_st->next = code->next;
6244           code->next = init_st;
6245         }
6246       else if (e->ts.type == BT_CLASS
6247                && ((code->ext.alloc.ts.type == BT_UNKNOWN
6248                     && (init_e = gfc_default_initializer (&e->ts.u.derived->components->ts)))
6249                    || (code->ext.alloc.ts.type == BT_DERIVED
6250                        && (init_e = gfc_default_initializer (&code->ext.alloc.ts)))))
6251         {
6252           gfc_code *init_st = gfc_get_code ();
6253           init_st->loc = code->loc;
6254           init_st->op = EXEC_INIT_ASSIGN;
6255           init_st->expr1 = gfc_expr_to_initialize (e);
6256           init_st->expr2 = init_e;
6257           init_st->next = code->next;
6258           code->next = init_st;
6259         }
6260     }
6261
6262   if (pointer || dimension == 0)
6263     return SUCCESS;
6264
6265   /* Make sure the next-to-last reference node is an array specification.  */
6266
6267   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL)
6268     {
6269       gfc_error ("Array specification required in ALLOCATE statement "
6270                  "at %L", &e->where);
6271       return FAILURE;
6272     }
6273
6274   /* Make sure that the array section reference makes sense in the
6275     context of an ALLOCATE specification.  */
6276
6277   ar = &ref2->u.ar;
6278
6279   for (i = 0; i < ar->dimen; i++)
6280     {
6281       if (ref2->u.ar.type == AR_ELEMENT)
6282         goto check_symbols;
6283
6284       switch (ar->dimen_type[i])
6285         {
6286         case DIMEN_ELEMENT:
6287           break;
6288
6289         case DIMEN_RANGE:
6290           if (ar->start[i] != NULL
6291               && ar->end[i] != NULL
6292               && ar->stride[i] == NULL)
6293             break;
6294
6295           /* Fall Through...  */
6296
6297         case DIMEN_UNKNOWN:
6298         case DIMEN_VECTOR:
6299           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6300                      &e->where);
6301           return FAILURE;
6302         }
6303
6304 check_symbols:
6305
6306       for (a = code->ext.alloc.list; a; a = a->next)
6307         {
6308           sym = a->expr->symtree->n.sym;
6309
6310           /* TODO - check derived type components.  */
6311           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6312             continue;
6313
6314           if ((ar->start[i] != NULL
6315                && gfc_find_sym_in_expr (sym, ar->start[i]))
6316               || (ar->end[i] != NULL
6317                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6318             {
6319               gfc_error ("'%s' must not appear in the array specification at "
6320                          "%L in the same ALLOCATE statement where it is "
6321                          "itself allocated", sym->name, &ar->where);
6322               return FAILURE;
6323             }
6324         }
6325     }
6326
6327   return SUCCESS;
6328 }
6329
6330 static void
6331 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6332 {
6333   gfc_expr *stat, *errmsg, *pe, *qe;
6334   gfc_alloc *a, *p, *q;
6335
6336   stat = code->expr1 ? code->expr1 : NULL;
6337
6338   errmsg = code->expr2 ? code->expr2 : NULL;
6339
6340   /* Check the stat variable.  */
6341   if (stat)
6342     {
6343       if (stat->symtree->n.sym->attr.intent == INTENT_IN)
6344         gfc_error ("Stat-variable '%s' at %L cannot be INTENT(IN)",
6345                    stat->symtree->n.sym->name, &stat->where);
6346
6347       if (gfc_pure (NULL) && gfc_impure_variable (stat->symtree->n.sym))
6348         gfc_error ("Illegal stat-variable at %L for a PURE procedure",
6349                    &stat->where);
6350
6351       if ((stat->ts.type != BT_INTEGER
6352            && !(stat->ref && (stat->ref->type == REF_ARRAY
6353                               || stat->ref->type == REF_COMPONENT)))
6354           || stat->rank > 0)
6355         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6356                    "variable", &stat->where);
6357
6358       for (p = code->ext.alloc.list; p; p = p->next)
6359         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6360           gfc_error ("Stat-variable at %L shall not be %sd within "
6361                      "the same %s statement", &stat->where, fcn, fcn);
6362     }
6363
6364   /* Check the errmsg variable.  */
6365   if (errmsg)
6366     {
6367       if (!stat)
6368         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
6369                      &errmsg->where);
6370
6371       if (errmsg->symtree->n.sym->attr.intent == INTENT_IN)
6372         gfc_error ("Errmsg-variable '%s' at %L cannot be INTENT(IN)",
6373                    errmsg->symtree->n.sym->name, &errmsg->where);
6374
6375       if (gfc_pure (NULL) && gfc_impure_variable (errmsg->symtree->n.sym))
6376         gfc_error ("Illegal errmsg-variable at %L for a PURE procedure",
6377                    &errmsg->where);
6378
6379       if ((errmsg->ts.type != BT_CHARACTER
6380            && !(errmsg->ref
6381                 && (errmsg->ref->type == REF_ARRAY
6382                     || errmsg->ref->type == REF_COMPONENT)))
6383           || errmsg->rank > 0 )
6384         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
6385                    "variable", &errmsg->where);
6386
6387       for (p = code->ext.alloc.list; p; p = p->next)
6388         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
6389           gfc_error ("Errmsg-variable at %L shall not be %sd within "
6390                      "the same %s statement", &errmsg->where, fcn, fcn);
6391     }
6392
6393   /* Check that an allocate-object appears only once in the statement.  
6394      FIXME: Checking derived types is disabled.  */
6395   for (p = code->ext.alloc.list; p; p = p->next)
6396     {
6397       pe = p->expr;
6398       if ((pe->ref && pe->ref->type != REF_COMPONENT)
6399            && (pe->symtree->n.sym->ts.type != BT_DERIVED))
6400         {
6401           for (q = p->next; q; q = q->next)
6402             {
6403               qe = q->expr;
6404               if ((qe->ref && qe->ref->type != REF_COMPONENT)
6405                   && (qe->symtree->n.sym->ts.type != BT_DERIVED)
6406                   && (pe->symtree->n.sym->name == qe->symtree->n.sym->name))
6407                 gfc_error ("Allocate-object at %L also appears at %L",
6408                            &pe->where, &qe->where);
6409             }
6410         }
6411     }
6412
6413   if (strcmp (fcn, "ALLOCATE") == 0)
6414     {
6415       for (a = code->ext.alloc.list; a; a = a->next)
6416         resolve_allocate_expr (a->expr, code);
6417     }
6418   else
6419     {
6420       for (a = code->ext.alloc.list; a; a = a->next)
6421         resolve_deallocate_expr (a->expr);
6422     }
6423 }
6424
6425
6426 /************ SELECT CASE resolution subroutines ************/
6427
6428 /* Callback function for our mergesort variant.  Determines interval
6429    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
6430    op1 > op2.  Assumes we're not dealing with the default case.  
6431    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
6432    There are nine situations to check.  */
6433
6434 static int
6435 compare_cases (const gfc_case *op1, const gfc_case *op2)
6436 {
6437   int retval;
6438
6439   if (op1->low == NULL) /* op1 = (:L)  */
6440     {
6441       /* op2 = (:N), so overlap.  */
6442       retval = 0;
6443       /* op2 = (M:) or (M:N),  L < M  */
6444       if (op2->low != NULL
6445           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6446         retval = -1;
6447     }
6448   else if (op1->high == NULL) /* op1 = (K:)  */
6449     {
6450       /* op2 = (M:), so overlap.  */
6451       retval = 0;
6452       /* op2 = (:N) or (M:N), K > N  */
6453       if (op2->high != NULL
6454           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6455         retval = 1;
6456     }
6457   else /* op1 = (K:L)  */
6458     {
6459       if (op2->low == NULL)       /* op2 = (:N), K > N  */
6460         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6461                  ? 1 : 0;
6462       else if (op2->high == NULL) /* op2 = (M:), L < M  */
6463         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6464                  ? -1 : 0;
6465       else                      /* op2 = (M:N)  */
6466         {
6467           retval =  0;
6468           /* L < M  */
6469           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6470             retval =  -1;
6471           /* K > N  */
6472           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6473             retval =  1;
6474         }
6475     }
6476
6477   return retval;
6478 }
6479
6480
6481 /* Merge-sort a double linked case list, detecting overlap in the
6482    process.  LIST is the head of the double linked case list before it
6483    is sorted.  Returns the head of the sorted list if we don't see any
6484    overlap, or NULL otherwise.  */
6485
6486 static gfc_case *
6487 check_case_overlap (gfc_case *list)
6488 {
6489   gfc_case *p, *q, *e, *tail;
6490   int insize, nmerges, psize, qsize, cmp, overlap_seen;
6491
6492   /* If the passed list was empty, return immediately.  */
6493   if (!list)
6494     return NULL;
6495
6496   overlap_seen = 0;
6497   insize = 1;
6498
6499   /* Loop unconditionally.  The only exit from this loop is a return
6500      statement, when we've finished sorting the case list.  */
6501   for (;;)
6502     {
6503       p = list;
6504       list = NULL;
6505       tail = NULL;
6506
6507       /* Count the number of merges we do in this pass.  */
6508       nmerges = 0;
6509
6510       /* Loop while there exists a merge to be done.  */
6511       while (p)
6512         {
6513           int i;
6514
6515           /* Count this merge.  */
6516           nmerges++;
6517
6518           /* Cut the list in two pieces by stepping INSIZE places
6519              forward in the list, starting from P.  */
6520           psize = 0;
6521           q = p;
6522           for (i = 0; i < insize; i++)
6523             {
6524               psize++;
6525               q = q->right;
6526               if (!q)
6527                 break;
6528             }
6529           qsize = insize;
6530
6531           /* Now we have two lists.  Merge them!  */
6532           while (psize > 0 || (qsize > 0 && q != NULL))
6533             {
6534               /* See from which the next case to merge comes from.  */
6535               if (psize == 0)
6536                 {
6537                   /* P is empty so the next case must come from Q.  */
6538                   e = q;
6539                   q = q->right;
6540                   qsize--;
6541                 }
6542               else if (qsize == 0 || q == NULL)
6543                 {
6544                   /* Q is empty.  */
6545                   e = p;
6546                   p = p->right;
6547                   psize--;
6548                 }
6549               else
6550                 {
6551                   cmp = compare_cases (p, q);
6552                   if (cmp < 0)
6553                     {
6554                       /* The whole case range for P is less than the
6555                          one for Q.  */
6556                       e = p;
6557                       p = p->right;
6558                       psize--;
6559                     }
6560                   else if (cmp > 0)
6561                     {
6562                       /* The whole case range for Q is greater than
6563                          the case range for P.  */
6564                       e = q;
6565                       q = q->right;
6566                       qsize--;
6567                     }
6568                   else
6569                     {
6570                       /* The cases overlap, or they are the same
6571                          element in the list.  Either way, we must
6572                          issue an error and get the next case from P.  */
6573                       /* FIXME: Sort P and Q by line number.  */
6574                       gfc_error ("CASE label at %L overlaps with CASE "
6575                                  "label at %L", &p->where, &q->where);
6576                       overlap_seen = 1;
6577                       e = p;
6578                       p = p->right;
6579                       psize--;
6580                     }
6581                 }
6582
6583                 /* Add the next element to the merged list.  */
6584               if (tail)
6585                 tail->right = e;
6586               else
6587                 list = e;
6588               e->left = tail;
6589               tail = e;
6590             }
6591
6592           /* P has now stepped INSIZE places along, and so has Q.  So
6593              they're the same.  */
6594           p = q;
6595         }
6596       tail->right = NULL;
6597
6598       /* If we have done only one merge or none at all, we've
6599          finished sorting the cases.  */
6600       if (nmerges <= 1)
6601         {
6602           if (!overlap_seen)
6603             return list;
6604           else
6605             return NULL;
6606         }
6607
6608       /* Otherwise repeat, merging lists twice the size.  */
6609       insize *= 2;
6610     }
6611 }
6612
6613
6614 /* Check to see if an expression is suitable for use in a CASE statement.
6615    Makes sure that all case expressions are scalar constants of the same
6616    type.  Return FAILURE if anything is wrong.  */
6617
6618 static gfc_try
6619 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
6620 {
6621   if (e == NULL) return SUCCESS;
6622
6623   if (e->ts.type != case_expr->ts.type)
6624     {
6625       gfc_error ("Expression in CASE statement at %L must be of type %s",
6626                  &e->where, gfc_basic_typename (case_expr->ts.type));
6627       return FAILURE;
6628     }
6629
6630   /* C805 (R808) For a given case-construct, each case-value shall be of
6631      the same type as case-expr.  For character type, length differences
6632      are allowed, but the kind type parameters shall be the same.  */
6633
6634   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
6635     {
6636       gfc_error ("Expression in CASE statement at %L must be of kind %d",
6637                  &e->where, case_expr->ts.kind);
6638       return FAILURE;
6639     }
6640
6641   /* Convert the case value kind to that of case expression kind, if needed.
6642      FIXME:  Should a warning be issued?  */
6643   if (e->ts.kind != case_expr->ts.kind)
6644     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
6645
6646   if (e->rank != 0)
6647     {
6648       gfc_error ("Expression in CASE statement at %L must be scalar",
6649                  &e->where);
6650       return FAILURE;
6651     }
6652
6653   return SUCCESS;
6654 }
6655
6656
6657 /* Given a completely parsed select statement, we:
6658
6659      - Validate all expressions and code within the SELECT.
6660      - Make sure that the selection expression is not of the wrong type.
6661      - Make sure that no case ranges overlap.
6662      - Eliminate unreachable cases and unreachable code resulting from
6663        removing case labels.
6664
6665    The standard does allow unreachable cases, e.g. CASE (5:3).  But
6666    they are a hassle for code generation, and to prevent that, we just
6667    cut them out here.  This is not necessary for overlapping cases
6668    because they are illegal and we never even try to generate code.
6669
6670    We have the additional caveat that a SELECT construct could have
6671    been a computed GOTO in the source code. Fortunately we can fairly
6672    easily work around that here: The case_expr for a "real" SELECT CASE
6673    is in code->expr1, but for a computed GOTO it is in code->expr2. All
6674    we have to do is make sure that the case_expr is a scalar integer
6675    expression.  */
6676
6677 static void
6678 resolve_select (gfc_code *code)
6679 {
6680   gfc_code *body;
6681   gfc_expr *case_expr;
6682   gfc_case *cp, *default_case, *tail, *head;
6683   int seen_unreachable;
6684   int seen_logical;
6685   int ncases;
6686   bt type;
6687   gfc_try t;
6688
6689   if (code->expr1 == NULL)
6690     {
6691       /* This was actually a computed GOTO statement.  */
6692       case_expr = code->expr2;
6693       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
6694         gfc_error ("Selection expression in computed GOTO statement "
6695                    "at %L must be a scalar integer expression",
6696                    &case_expr->where);
6697
6698       /* Further checking is not necessary because this SELECT was built
6699          by the compiler, so it should always be OK.  Just move the
6700          case_expr from expr2 to expr so that we can handle computed
6701          GOTOs as normal SELECTs from here on.  */
6702       code->expr1 = code->expr2;
6703       code->expr2 = NULL;
6704       return;
6705     }
6706
6707   case_expr = code->expr1;
6708
6709   type = case_expr->ts.type;
6710   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
6711     {
6712       gfc_error ("Argument of SELECT statement at %L cannot be %s",
6713                  &case_expr->where, gfc_typename (&case_expr->ts));
6714
6715       /* Punt. Going on here just produce more garbage error messages.  */
6716       return;
6717     }
6718
6719   if (case_expr->rank != 0)
6720     {
6721       gfc_error ("Argument of SELECT statement at %L must be a scalar "
6722                  "expression", &case_expr->where);
6723
6724       /* Punt.  */
6725       return;
6726     }
6727
6728   /* PR 19168 has a long discussion concerning a mismatch of the kinds
6729      of the SELECT CASE expression and its CASE values.  Walk the lists
6730      of case values, and if we find a mismatch, promote case_expr to
6731      the appropriate kind.  */
6732
6733   if (type == BT_LOGICAL || type == BT_INTEGER)
6734     {
6735       for (body = code->block; body; body = body->block)
6736         {
6737           /* Walk the case label list.  */
6738           for (cp = body->ext.case_list; cp; cp = cp->next)
6739             {
6740               /* Intercept the DEFAULT case.  It does not have a kind.  */
6741               if (cp->low == NULL && cp->high == NULL)
6742                 continue;
6743
6744               /* Unreachable case ranges are discarded, so ignore.  */
6745               if (cp->low != NULL && cp->high != NULL
6746                   && cp->low != cp->high
6747                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
6748                 continue;
6749
6750               /* FIXME: Should a warning be issued?  */
6751               if (cp->low != NULL
6752                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
6753                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
6754
6755               if (cp->high != NULL
6756                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
6757                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
6758             }
6759          }
6760     }
6761
6762   /* Assume there is no DEFAULT case.  */
6763   default_case = NULL;
6764   head = tail = NULL;
6765   ncases = 0;
6766   seen_logical = 0;
6767
6768   for (body = code->block; body; body = body->block)
6769     {
6770       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
6771       t = SUCCESS;
6772       seen_unreachable = 0;
6773
6774       /* Walk the case label list, making sure that all case labels
6775          are legal.  */
6776       for (cp = body->ext.case_list; cp; cp = cp->next)
6777         {
6778           /* Count the number of cases in the whole construct.  */
6779           ncases++;
6780
6781           /* Intercept the DEFAULT case.  */
6782           if (cp->low == NULL && cp->high == NULL)
6783             {
6784               if (default_case != NULL)
6785                 {
6786                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
6787                              "by a second DEFAULT CASE at %L",
6788                              &default_case->where, &cp->where);
6789                   t = FAILURE;
6790                   break;
6791                 }
6792               else
6793                 {
6794                   default_case = cp;
6795                   continue;
6796                 }
6797             }
6798
6799           /* Deal with single value cases and case ranges.  Errors are
6800              issued from the validation function.  */
6801           if(validate_case_label_expr (cp->low, case_expr) != SUCCESS
6802              || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
6803             {
6804               t = FAILURE;
6805               break;
6806             }
6807
6808           if (type == BT_LOGICAL
6809               && ((cp->low == NULL || cp->high == NULL)
6810                   || cp->low != cp->high))
6811             {
6812               gfc_error ("Logical range in CASE statement at %L is not "
6813                          "allowed", &cp->low->where);
6814               t = FAILURE;
6815               break;
6816             }
6817
6818           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
6819             {
6820               int value;
6821               value = cp->low->value.logical == 0 ? 2 : 1;
6822               if (value & seen_logical)
6823                 {
6824                   gfc_error ("constant logical value in CASE statement "
6825                              "is repeated at %L",
6826                              &cp->low->where);
6827                   t = FAILURE;
6828                   break;
6829                 }
6830               seen_logical |= value;
6831             }
6832
6833           if (cp->low != NULL && cp->high != NULL
6834               && cp->low != cp->high
6835               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
6836             {
6837               if (gfc_option.warn_surprising)
6838                 gfc_warning ("Range specification at %L can never "
6839                              "be matched", &cp->where);
6840
6841               cp->unreachable = 1;
6842               seen_unreachable = 1;
6843             }
6844           else
6845             {
6846               /* If the case range can be matched, it can also overlap with
6847                  other cases.  To make sure it does not, we put it in a
6848                  double linked list here.  We sort that with a merge sort
6849                  later on to detect any overlapping cases.  */
6850               if (!head)
6851                 {
6852                   head = tail = cp;
6853                   head->right = head->left = NULL;
6854                 }
6855               else
6856                 {
6857                   tail->right = cp;
6858                   tail->right->left = tail;
6859                   tail = tail->right;
6860                   tail->right = NULL;
6861                 }
6862             }
6863         }
6864
6865       /* It there was a failure in the previous case label, give up
6866          for this case label list.  Continue with the next block.  */
6867       if (t == FAILURE)
6868         continue;
6869
6870       /* See if any case labels that are unreachable have been seen.
6871          If so, we eliminate them.  This is a bit of a kludge because
6872          the case lists for a single case statement (label) is a
6873          single forward linked lists.  */
6874       if (seen_unreachable)
6875       {
6876         /* Advance until the first case in the list is reachable.  */
6877         while (body->ext.case_list != NULL
6878                && body->ext.case_list->unreachable)
6879           {
6880             gfc_case *n = body->ext.case_list;
6881             body->ext.case_list = body->ext.case_list->next;
6882             n->next = NULL;
6883             gfc_free_case_list (n);
6884           }
6885
6886         /* Strip all other unreachable cases.  */
6887         if (body->ext.case_list)
6888           {
6889             for (cp = body->ext.case_list; cp->next; cp = cp->next)
6890               {
6891                 if (cp->next->unreachable)
6892                   {
6893                     gfc_case *n = cp->next;
6894                     cp->next = cp->next->next;
6895                     n->next = NULL;
6896                     gfc_free_case_list (n);
6897                   }
6898               }
6899           }
6900       }
6901     }
6902
6903   /* See if there were overlapping cases.  If the check returns NULL,
6904      there was overlap.  In that case we don't do anything.  If head
6905      is non-NULL, we prepend the DEFAULT case.  The sorted list can
6906      then used during code generation for SELECT CASE constructs with
6907      a case expression of a CHARACTER type.  */
6908   if (head)
6909     {
6910       head = check_case_overlap (head);
6911
6912       /* Prepend the default_case if it is there.  */
6913       if (head != NULL && default_case)
6914         {
6915           default_case->left = NULL;
6916           default_case->right = head;
6917           head->left = default_case;
6918         }
6919     }
6920
6921   /* Eliminate dead blocks that may be the result if we've seen
6922      unreachable case labels for a block.  */
6923   for (body = code; body && body->block; body = body->block)
6924     {
6925       if (body->block->ext.case_list == NULL)
6926         {
6927           /* Cut the unreachable block from the code chain.  */
6928           gfc_code *c = body->block;
6929           body->block = c->block;
6930
6931           /* Kill the dead block, but not the blocks below it.  */
6932           c->block = NULL;
6933           gfc_free_statements (c);
6934         }
6935     }
6936
6937   /* More than two cases is legal but insane for logical selects.
6938      Issue a warning for it.  */
6939   if (gfc_option.warn_surprising && type == BT_LOGICAL
6940       && ncases > 2)
6941     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
6942                  &code->loc);
6943 }
6944
6945
6946 /* Check if a derived type is extensible.  */
6947
6948 bool
6949 gfc_type_is_extensible (gfc_symbol *sym)
6950 {
6951   return !(sym->attr.is_bind_c || sym->attr.sequence);
6952 }
6953
6954
6955 /* Resolve a SELECT TYPE statement.  */
6956
6957 static void
6958 resolve_select_type (gfc_code *code)
6959 {
6960   gfc_symbol *selector_type;
6961   gfc_code *body, *new_st, *if_st, *tail;
6962   gfc_code *class_is = NULL, *default_case = NULL;
6963   gfc_case *c;
6964   gfc_symtree *st;
6965   char name[GFC_MAX_SYMBOL_LEN];
6966   gfc_namespace *ns;
6967   int error = 0;
6968
6969   ns = code->ext.ns;
6970   gfc_resolve (ns);
6971
6972   if (code->expr2)
6973     selector_type = code->expr2->ts.u.derived->components->ts.u.derived;
6974   else
6975     selector_type = code->expr1->ts.u.derived->components->ts.u.derived;
6976
6977   /* Loop over TYPE IS / CLASS IS cases.  */
6978   for (body = code->block; body; body = body->block)
6979     {
6980       c = body->ext.case_list;
6981
6982       /* Check F03:C815.  */
6983       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
6984           && !gfc_type_is_extensible (c->ts.u.derived))
6985         {
6986           gfc_error ("Derived type '%s' at %L must be extensible",
6987                      c->ts.u.derived->name, &c->where);
6988           error++;
6989           continue;
6990         }
6991
6992       /* Check F03:C816.  */
6993       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
6994           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
6995         {
6996           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
6997                      c->ts.u.derived->name, &c->where, selector_type->name);
6998           error++;
6999           continue;
7000         }
7001
7002       /* Intercept the DEFAULT case.  */
7003       if (c->ts.type == BT_UNKNOWN)
7004         {
7005           /* Check F03:C818.  */
7006           if (default_case)
7007             {
7008               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7009                          "by a second DEFAULT CASE at %L",
7010                          &default_case->ext.case_list->where, &c->where);
7011               error++;
7012               continue;
7013             }
7014           else
7015             default_case = body;
7016         }
7017     }
7018     
7019   if (error>0)
7020     return;
7021
7022   if (code->expr2)
7023     {
7024       /* Insert assignment for selector variable.  */
7025       new_st = gfc_get_code ();
7026       new_st->op = EXEC_ASSIGN;
7027       new_st->expr1 = gfc_copy_expr (code->expr1);
7028       new_st->expr2 = gfc_copy_expr (code->expr2);
7029       ns->code = new_st;
7030     }
7031
7032   /* Put SELECT TYPE statement inside a BLOCK.  */
7033   new_st = gfc_get_code ();
7034   new_st->op = code->op;
7035   new_st->expr1 = code->expr1;
7036   new_st->expr2 = code->expr2;
7037   new_st->block = code->block;
7038   if (!ns->code)
7039     ns->code = new_st;
7040   else
7041     ns->code->next = new_st;
7042   code->op = EXEC_BLOCK;
7043   code->expr1 = code->expr2 =  NULL;
7044   code->block = NULL;
7045
7046   code = new_st;
7047
7048   /* Transform to EXEC_SELECT.  */
7049   code->op = EXEC_SELECT;
7050   gfc_add_component_ref (code->expr1, "$vptr");
7051   gfc_add_component_ref (code->expr1, "$hash");
7052
7053   /* Loop over TYPE IS / CLASS IS cases.  */
7054   for (body = code->block; body; body = body->block)
7055     {
7056       c = body->ext.case_list;
7057       
7058       if (c->ts.type == BT_DERIVED)
7059         c->low = c->high = gfc_int_expr (c->ts.u.derived->hash_value);
7060       else if (c->ts.type == BT_UNKNOWN)
7061         continue;
7062       
7063       /* Assign temporary to selector.  */
7064       if (c->ts.type == BT_CLASS)
7065         sprintf (name, "tmp$class$%s", c->ts.u.derived->name);
7066       else
7067         sprintf (name, "tmp$type$%s", c->ts.u.derived->name);
7068       st = gfc_find_symtree (ns->sym_root, name);
7069       new_st = gfc_get_code ();
7070       new_st->expr1 = gfc_get_variable_expr (st);
7071       new_st->expr2 = gfc_get_variable_expr (code->expr1->symtree);
7072       if (c->ts.type == BT_DERIVED)
7073         {
7074           new_st->op = EXEC_POINTER_ASSIGN;
7075           gfc_add_component_ref (new_st->expr2, "$data");
7076         }
7077       else
7078         new_st->op = EXEC_POINTER_ASSIGN;
7079       new_st->next = body->next;
7080       body->next = new_st;
7081     }
7082     
7083   /* Take out CLASS IS cases for separate treatment.  */
7084   body = code;
7085   while (body && body->block)
7086     {
7087       if (body->block->ext.case_list->ts.type == BT_CLASS)
7088         {
7089           /* Add to class_is list.  */
7090           if (class_is == NULL)
7091             { 
7092               class_is = body->block;
7093               tail = class_is;
7094             }
7095           else
7096             {
7097               for (tail = class_is; tail->block; tail = tail->block) ;
7098               tail->block = body->block;
7099               tail = tail->block;
7100             }
7101           /* Remove from EXEC_SELECT list.  */
7102           body->block = body->block->block;
7103           tail->block = NULL;
7104         }
7105       else
7106         body = body->block;
7107     }
7108
7109   if (class_is)
7110     {
7111       gfc_symbol *vtab;
7112       
7113       if (!default_case)
7114         {
7115           /* Add a default case to hold the CLASS IS cases.  */
7116           for (tail = code; tail->block; tail = tail->block) ;
7117           tail->block = gfc_get_code ();
7118           tail = tail->block;
7119           tail->op = EXEC_SELECT_TYPE;
7120           tail->ext.case_list = gfc_get_case ();
7121           tail->ext.case_list->ts.type = BT_UNKNOWN;
7122           tail->next = NULL;
7123           default_case = tail;
7124         }
7125       
7126       /* More than one CLASS IS block?  */
7127       if (class_is->block)
7128         {
7129           gfc_code **c1,*c2;
7130           bool swapped;
7131           /* Sort CLASS IS blocks by extension level.  */
7132           do
7133             {
7134               swapped = false;
7135               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
7136                 {
7137                   c2 = (*c1)->block;
7138                   /* F03:C817 (check for doubles).  */
7139                   if ((*c1)->ext.case_list->ts.u.derived->hash_value
7140                       == c2->ext.case_list->ts.u.derived->hash_value)
7141                     {
7142                       gfc_error ("Double CLASS IS block in SELECT TYPE "
7143                                  "statement at %L", &c2->ext.case_list->where);
7144                       return;
7145                     }
7146                   if ((*c1)->ext.case_list->ts.u.derived->attr.extension
7147                       < c2->ext.case_list->ts.u.derived->attr.extension)
7148                     {
7149                       /* Swap.  */
7150                       (*c1)->block = c2->block;
7151                       c2->block = *c1;
7152                       *c1 = c2;
7153                       swapped = true;
7154                     }
7155                 }
7156             }
7157           while (swapped);
7158         }
7159         
7160       /* Generate IF chain.  */
7161       if_st = gfc_get_code ();
7162       if_st->op = EXEC_IF;
7163       new_st = if_st;
7164       for (body = class_is; body; body = body->block)
7165         {
7166           new_st->block = gfc_get_code ();
7167           new_st = new_st->block;
7168           new_st->op = EXEC_IF;
7169           /* Set up IF condition: Call _gfortran_is_extension_of.  */
7170           new_st->expr1 = gfc_get_expr ();
7171           new_st->expr1->expr_type = EXPR_FUNCTION;
7172           new_st->expr1->ts.type = BT_LOGICAL;
7173           new_st->expr1->ts.kind = 4;
7174           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
7175           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
7176           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
7177           /* Set up arguments.  */
7178           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
7179           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
7180           gfc_add_component_ref (new_st->expr1->value.function.actual->expr, "$vptr");
7181           vtab = gfc_find_derived_vtab (body->ext.case_list->ts.u.derived);
7182           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
7183           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
7184           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
7185           new_st->next = body->next;
7186         }
7187         if (default_case->next)
7188           {
7189             new_st->block = gfc_get_code ();
7190             new_st = new_st->block;
7191             new_st->op = EXEC_IF;
7192             new_st->next = default_case->next;
7193           }
7194           
7195         /* Replace CLASS DEFAULT code by the IF chain.  */
7196         default_case->next = if_st;
7197     }
7198
7199   resolve_select (code);
7200
7201 }
7202
7203
7204 /* Resolve a transfer statement. This is making sure that:
7205    -- a derived type being transferred has only non-pointer components
7206    -- a derived type being transferred doesn't have private components, unless 
7207       it's being transferred from the module where the type was defined
7208    -- we're not trying to transfer a whole assumed size array.  */
7209
7210 static void
7211 resolve_transfer (gfc_code *code)
7212 {
7213   gfc_typespec *ts;
7214   gfc_symbol *sym;
7215   gfc_ref *ref;
7216   gfc_expr *exp;
7217
7218   exp = code->expr1;
7219
7220   if (exp->expr_type != EXPR_VARIABLE && exp->expr_type != EXPR_FUNCTION)
7221     return;
7222
7223   sym = exp->symtree->n.sym;
7224   ts = &sym->ts;
7225
7226   /* Go to actual component transferred.  */
7227   for (ref = code->expr1->ref; ref; ref = ref->next)
7228     if (ref->type == REF_COMPONENT)
7229       ts = &ref->u.c.component->ts;
7230
7231   if (ts->type == BT_DERIVED)
7232     {
7233       /* Check that transferred derived type doesn't contain POINTER
7234          components.  */
7235       if (ts->u.derived->attr.pointer_comp)
7236         {
7237           gfc_error ("Data transfer element at %L cannot have "
7238                      "POINTER components", &code->loc);
7239           return;
7240         }
7241
7242       if (ts->u.derived->attr.alloc_comp)
7243         {
7244           gfc_error ("Data transfer element at %L cannot have "
7245                      "ALLOCATABLE components", &code->loc);
7246           return;
7247         }
7248
7249       if (derived_inaccessible (ts->u.derived))
7250         {
7251           gfc_error ("Data transfer element at %L cannot have "
7252                      "PRIVATE components",&code->loc);
7253           return;
7254         }
7255     }
7256
7257   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
7258       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
7259     {
7260       gfc_error ("Data transfer element at %L cannot be a full reference to "
7261                  "an assumed-size array", &code->loc);
7262       return;
7263     }
7264 }
7265
7266
7267 /*********** Toplevel code resolution subroutines ***********/
7268
7269 /* Find the set of labels that are reachable from this block.  We also
7270    record the last statement in each block.  */
7271      
7272 static void
7273 find_reachable_labels (gfc_code *block)
7274 {
7275   gfc_code *c;
7276
7277   if (!block)
7278     return;
7279
7280   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
7281
7282   /* Collect labels in this block.  We don't keep those corresponding
7283      to END {IF|SELECT}, these are checked in resolve_branch by going
7284      up through the code_stack.  */
7285   for (c = block; c; c = c->next)
7286     {
7287       if (c->here && c->op != EXEC_END_BLOCK)
7288         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
7289     }
7290
7291   /* Merge with labels from parent block.  */
7292   if (cs_base->prev)
7293     {
7294       gcc_assert (cs_base->prev->reachable_labels);
7295       bitmap_ior_into (cs_base->reachable_labels,
7296                        cs_base->prev->reachable_labels);
7297     }
7298 }
7299
7300 /* Given a branch to a label, see if the branch is conforming.
7301    The code node describes where the branch is located.  */
7302
7303 static void
7304 resolve_branch (gfc_st_label *label, gfc_code *code)
7305 {
7306   code_stack *stack;
7307
7308   if (label == NULL)
7309     return;
7310
7311   /* Step one: is this a valid branching target?  */
7312
7313   if (label->defined == ST_LABEL_UNKNOWN)
7314     {
7315       gfc_error ("Label %d referenced at %L is never defined", label->value,
7316                  &label->where);
7317       return;
7318     }
7319
7320   if (label->defined != ST_LABEL_TARGET)
7321     {
7322       gfc_error ("Statement at %L is not a valid branch target statement "
7323                  "for the branch statement at %L", &label->where, &code->loc);
7324       return;
7325     }
7326
7327   /* Step two: make sure this branch is not a branch to itself ;-)  */
7328
7329   if (code->here == label)
7330     {
7331       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
7332       return;
7333     }
7334
7335   /* Step three:  See if the label is in the same block as the
7336      branching statement.  The hard work has been done by setting up
7337      the bitmap reachable_labels.  */
7338
7339   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
7340     return;
7341
7342   /* Step four:  If we haven't found the label in the bitmap, it may
7343     still be the label of the END of the enclosing block, in which
7344     case we find it by going up the code_stack.  */
7345
7346   for (stack = cs_base; stack; stack = stack->prev)
7347     if (stack->current->next && stack->current->next->here == label)
7348       break;
7349
7350   if (stack)
7351     {
7352       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
7353       return;
7354     }
7355
7356   /* The label is not in an enclosing block, so illegal.  This was
7357      allowed in Fortran 66, so we allow it as extension.  No
7358      further checks are necessary in this case.  */
7359   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
7360                   "as the GOTO statement at %L", &label->where,
7361                   &code->loc);
7362   return;
7363 }
7364
7365
7366 /* Check whether EXPR1 has the same shape as EXPR2.  */
7367
7368 static gfc_try
7369 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
7370 {
7371   mpz_t shape[GFC_MAX_DIMENSIONS];
7372   mpz_t shape2[GFC_MAX_DIMENSIONS];
7373   gfc_try result = FAILURE;
7374   int i;
7375
7376   /* Compare the rank.  */
7377   if (expr1->rank != expr2->rank)
7378     return result;
7379
7380   /* Compare the size of each dimension.  */
7381   for (i=0; i<expr1->rank; i++)
7382     {
7383       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
7384         goto ignore;
7385
7386       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
7387         goto ignore;
7388
7389       if (mpz_cmp (shape[i], shape2[i]))
7390         goto over;
7391     }
7392
7393   /* When either of the two expression is an assumed size array, we
7394      ignore the comparison of dimension sizes.  */
7395 ignore:
7396   result = SUCCESS;
7397
7398 over:
7399   for (i--; i >= 0; i--)
7400     {
7401       mpz_clear (shape[i]);
7402       mpz_clear (shape2[i]);
7403     }
7404   return result;
7405 }
7406
7407
7408 /* Check whether a WHERE assignment target or a WHERE mask expression
7409    has the same shape as the outmost WHERE mask expression.  */
7410
7411 static void
7412 resolve_where (gfc_code *code, gfc_expr *mask)
7413 {
7414   gfc_code *cblock;
7415   gfc_code *cnext;
7416   gfc_expr *e = NULL;
7417
7418   cblock = code->block;
7419
7420   /* Store the first WHERE mask-expr of the WHERE statement or construct.
7421      In case of nested WHERE, only the outmost one is stored.  */
7422   if (mask == NULL) /* outmost WHERE */
7423     e = cblock->expr1;
7424   else /* inner WHERE */
7425     e = mask;
7426
7427   while (cblock)
7428     {
7429       if (cblock->expr1)
7430         {
7431           /* Check if the mask-expr has a consistent shape with the
7432              outmost WHERE mask-expr.  */
7433           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
7434             gfc_error ("WHERE mask at %L has inconsistent shape",
7435                        &cblock->expr1->where);
7436          }
7437
7438       /* the assignment statement of a WHERE statement, or the first
7439          statement in where-body-construct of a WHERE construct */
7440       cnext = cblock->next;
7441       while (cnext)
7442         {
7443           switch (cnext->op)
7444             {
7445             /* WHERE assignment statement */
7446             case EXEC_ASSIGN:
7447
7448               /* Check shape consistent for WHERE assignment target.  */
7449               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
7450                gfc_error ("WHERE assignment target at %L has "
7451                           "inconsistent shape", &cnext->expr1->where);
7452               break;
7453
7454   
7455             case EXEC_ASSIGN_CALL:
7456               resolve_call (cnext);
7457               if (!cnext->resolved_sym->attr.elemental)
7458                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7459                           &cnext->ext.actual->expr->where);
7460               break;
7461
7462             /* WHERE or WHERE construct is part of a where-body-construct */
7463             case EXEC_WHERE:
7464               resolve_where (cnext, e);
7465               break;
7466
7467             default:
7468               gfc_error ("Unsupported statement inside WHERE at %L",
7469                          &cnext->loc);
7470             }
7471          /* the next statement within the same where-body-construct */
7472          cnext = cnext->next;
7473        }
7474     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7475     cblock = cblock->block;
7476   }
7477 }
7478
7479
7480 /* Resolve assignment in FORALL construct.
7481    NVAR is the number of FORALL index variables, and VAR_EXPR records the
7482    FORALL index variables.  */
7483
7484 static void
7485 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
7486 {
7487   int n;
7488
7489   for (n = 0; n < nvar; n++)
7490     {
7491       gfc_symbol *forall_index;
7492
7493       forall_index = var_expr[n]->symtree->n.sym;
7494
7495       /* Check whether the assignment target is one of the FORALL index
7496          variable.  */
7497       if ((code->expr1->expr_type == EXPR_VARIABLE)
7498           && (code->expr1->symtree->n.sym == forall_index))
7499         gfc_error ("Assignment to a FORALL index variable at %L",
7500                    &code->expr1->where);
7501       else
7502         {
7503           /* If one of the FORALL index variables doesn't appear in the
7504              assignment variable, then there could be a many-to-one
7505              assignment.  Emit a warning rather than an error because the
7506              mask could be resolving this problem.  */
7507           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
7508             gfc_warning ("The FORALL with index '%s' is not used on the "
7509                          "left side of the assignment at %L and so might "
7510                          "cause multiple assignment to this object",
7511                          var_expr[n]->symtree->name, &code->expr1->where);
7512         }
7513     }
7514 }
7515
7516
7517 /* Resolve WHERE statement in FORALL construct.  */
7518
7519 static void
7520 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
7521                                   gfc_expr **var_expr)
7522 {
7523   gfc_code *cblock;
7524   gfc_code *cnext;
7525
7526   cblock = code->block;
7527   while (cblock)
7528     {
7529       /* the assignment statement of a WHERE statement, or the first
7530          statement in where-body-construct of a WHERE construct */
7531       cnext = cblock->next;
7532       while (cnext)
7533         {
7534           switch (cnext->op)
7535             {
7536             /* WHERE assignment statement */
7537             case EXEC_ASSIGN:
7538               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
7539               break;
7540   
7541             /* WHERE operator assignment statement */
7542             case EXEC_ASSIGN_CALL:
7543               resolve_call (cnext);
7544               if (!cnext->resolved_sym->attr.elemental)
7545                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7546                           &cnext->ext.actual->expr->where);
7547               break;
7548
7549             /* WHERE or WHERE construct is part of a where-body-construct */
7550             case EXEC_WHERE:
7551               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
7552               break;
7553
7554             default:
7555               gfc_error ("Unsupported statement inside WHERE at %L",
7556                          &cnext->loc);
7557             }
7558           /* the next statement within the same where-body-construct */
7559           cnext = cnext->next;
7560         }
7561       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7562       cblock = cblock->block;
7563     }
7564 }
7565
7566
7567 /* Traverse the FORALL body to check whether the following errors exist:
7568    1. For assignment, check if a many-to-one assignment happens.
7569    2. For WHERE statement, check the WHERE body to see if there is any
7570       many-to-one assignment.  */
7571
7572 static void
7573 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
7574 {
7575   gfc_code *c;
7576
7577   c = code->block->next;
7578   while (c)
7579     {
7580       switch (c->op)
7581         {
7582         case EXEC_ASSIGN:
7583         case EXEC_POINTER_ASSIGN:
7584           gfc_resolve_assign_in_forall (c, nvar, var_expr);
7585           break;
7586
7587         case EXEC_ASSIGN_CALL:
7588           resolve_call (c);
7589           break;
7590
7591         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
7592            there is no need to handle it here.  */
7593         case EXEC_FORALL:
7594           break;
7595         case EXEC_WHERE:
7596           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
7597           break;
7598         default:
7599           break;
7600         }
7601       /* The next statement in the FORALL body.  */
7602       c = c->next;
7603     }
7604 }
7605
7606
7607 /* Counts the number of iterators needed inside a forall construct, including
7608    nested forall constructs. This is used to allocate the needed memory 
7609    in gfc_resolve_forall.  */
7610
7611 static int 
7612 gfc_count_forall_iterators (gfc_code *code)
7613 {
7614   int max_iters, sub_iters, current_iters;
7615   gfc_forall_iterator *fa;
7616
7617   gcc_assert(code->op == EXEC_FORALL);
7618   max_iters = 0;
7619   current_iters = 0;
7620
7621   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7622     current_iters ++;
7623   
7624   code = code->block->next;
7625
7626   while (code)
7627     {          
7628       if (code->op == EXEC_FORALL)
7629         {
7630           sub_iters = gfc_count_forall_iterators (code);
7631           if (sub_iters > max_iters)
7632             max_iters = sub_iters;
7633         }
7634       code = code->next;
7635     }
7636
7637   return current_iters + max_iters;
7638 }
7639
7640
7641 /* Given a FORALL construct, first resolve the FORALL iterator, then call
7642    gfc_resolve_forall_body to resolve the FORALL body.  */
7643
7644 static void
7645 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
7646 {
7647   static gfc_expr **var_expr;
7648   static int total_var = 0;
7649   static int nvar = 0;
7650   int old_nvar, tmp;
7651   gfc_forall_iterator *fa;
7652   int i;
7653
7654   old_nvar = nvar;
7655
7656   /* Start to resolve a FORALL construct   */
7657   if (forall_save == 0)
7658     {
7659       /* Count the total number of FORALL index in the nested FORALL
7660          construct in order to allocate the VAR_EXPR with proper size.  */
7661       total_var = gfc_count_forall_iterators (code);
7662
7663       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
7664       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
7665     }
7666
7667   /* The information about FORALL iterator, including FORALL index start, end
7668      and stride. The FORALL index can not appear in start, end or stride.  */
7669   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7670     {
7671       /* Check if any outer FORALL index name is the same as the current
7672          one.  */
7673       for (i = 0; i < nvar; i++)
7674         {
7675           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
7676             {
7677               gfc_error ("An outer FORALL construct already has an index "
7678                          "with this name %L", &fa->var->where);
7679             }
7680         }
7681
7682       /* Record the current FORALL index.  */
7683       var_expr[nvar] = gfc_copy_expr (fa->var);
7684
7685       nvar++;
7686
7687       /* No memory leak.  */
7688       gcc_assert (nvar <= total_var);
7689     }
7690
7691   /* Resolve the FORALL body.  */
7692   gfc_resolve_forall_body (code, nvar, var_expr);
7693
7694   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
7695   gfc_resolve_blocks (code->block, ns);
7696
7697   tmp = nvar;
7698   nvar = old_nvar;
7699   /* Free only the VAR_EXPRs allocated in this frame.  */
7700   for (i = nvar; i < tmp; i++)
7701      gfc_free_expr (var_expr[i]);
7702
7703   if (nvar == 0)
7704     {
7705       /* We are in the outermost FORALL construct.  */
7706       gcc_assert (forall_save == 0);
7707
7708       /* VAR_EXPR is not needed any more.  */
7709       gfc_free (var_expr);
7710       total_var = 0;
7711     }
7712 }
7713
7714
7715 /* Resolve a BLOCK construct statement.  */
7716
7717 static void
7718 resolve_block_construct (gfc_code* code)
7719 {
7720   /* Eventually, we may want to do some checks here or handle special stuff.
7721      But so far the only thing we can do is resolving the local namespace.  */
7722
7723   gfc_resolve (code->ext.ns);
7724 }
7725
7726
7727 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
7728    DO code nodes.  */
7729
7730 static void resolve_code (gfc_code *, gfc_namespace *);
7731
7732 void
7733 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
7734 {
7735   gfc_try t;
7736
7737   for (; b; b = b->block)
7738     {
7739       t = gfc_resolve_expr (b->expr1);
7740       if (gfc_resolve_expr (b->expr2) == FAILURE)
7741         t = FAILURE;
7742
7743       switch (b->op)
7744         {
7745         case EXEC_IF:
7746           if (t == SUCCESS && b->expr1 != NULL
7747               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
7748             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
7749                        &b->expr1->where);
7750           break;
7751
7752         case EXEC_WHERE:
7753           if (t == SUCCESS
7754               && b->expr1 != NULL
7755               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
7756             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
7757                        &b->expr1->where);
7758           break;
7759
7760         case EXEC_GOTO:
7761           resolve_branch (b->label1, b);
7762           break;
7763
7764         case EXEC_BLOCK:
7765           resolve_block_construct (b);
7766           break;
7767
7768         case EXEC_SELECT:
7769         case EXEC_SELECT_TYPE:
7770         case EXEC_FORALL:
7771         case EXEC_DO:
7772         case EXEC_DO_WHILE:
7773         case EXEC_READ:
7774         case EXEC_WRITE:
7775         case EXEC_IOLENGTH:
7776         case EXEC_WAIT:
7777           break;
7778
7779         case EXEC_OMP_ATOMIC:
7780         case EXEC_OMP_CRITICAL:
7781         case EXEC_OMP_DO:
7782         case EXEC_OMP_MASTER:
7783         case EXEC_OMP_ORDERED:
7784         case EXEC_OMP_PARALLEL:
7785         case EXEC_OMP_PARALLEL_DO:
7786         case EXEC_OMP_PARALLEL_SECTIONS:
7787         case EXEC_OMP_PARALLEL_WORKSHARE:
7788         case EXEC_OMP_SECTIONS:
7789         case EXEC_OMP_SINGLE:
7790         case EXEC_OMP_TASK:
7791         case EXEC_OMP_TASKWAIT:
7792         case EXEC_OMP_WORKSHARE:
7793           break;
7794
7795         default:
7796           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
7797         }
7798
7799       resolve_code (b->next, ns);
7800     }
7801 }
7802
7803
7804 /* Does everything to resolve an ordinary assignment.  Returns true
7805    if this is an interface assignment.  */
7806 static bool
7807 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
7808 {
7809   bool rval = false;
7810   gfc_expr *lhs;
7811   gfc_expr *rhs;
7812   int llen = 0;
7813   int rlen = 0;
7814   int n;
7815   gfc_ref *ref;
7816
7817   if (gfc_extend_assign (code, ns) == SUCCESS)
7818     {
7819       gfc_expr** rhsptr;
7820
7821       if (code->op == EXEC_ASSIGN_CALL)
7822         {
7823           lhs = code->ext.actual->expr;
7824           rhsptr = &code->ext.actual->next->expr;
7825         }
7826       else
7827         {
7828           gfc_actual_arglist* args;
7829           gfc_typebound_proc* tbp;
7830
7831           gcc_assert (code->op == EXEC_COMPCALL);
7832
7833           args = code->expr1->value.compcall.actual;
7834           lhs = args->expr;
7835           rhsptr = &args->next->expr;
7836
7837           tbp = code->expr1->value.compcall.tbp;
7838           gcc_assert (!tbp->is_generic);
7839         }
7840
7841       /* Make a temporary rhs when there is a default initializer
7842          and rhs is the same symbol as the lhs.  */
7843       if ((*rhsptr)->expr_type == EXPR_VARIABLE
7844             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
7845             && has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
7846             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
7847         *rhsptr = gfc_get_parentheses (*rhsptr);
7848
7849       return true;
7850     }
7851
7852   lhs = code->expr1;
7853   rhs = code->expr2;
7854
7855   if (rhs->is_boz
7856       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
7857                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
7858                          &code->loc) == FAILURE)
7859     return false;
7860
7861   /* Handle the case of a BOZ literal on the RHS.  */
7862   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
7863     {
7864       int rc;
7865       if (gfc_option.warn_surprising)
7866         gfc_warning ("BOZ literal at %L is bitwise transferred "
7867                      "non-integer symbol '%s'", &code->loc,
7868                      lhs->symtree->n.sym->name);
7869
7870       if (!gfc_convert_boz (rhs, &lhs->ts))
7871         return false;
7872       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
7873         {
7874           if (rc == ARITH_UNDERFLOW)
7875             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
7876                        ". This check can be disabled with the option "
7877                        "-fno-range-check", &rhs->where);
7878           else if (rc == ARITH_OVERFLOW)
7879             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
7880                        ". This check can be disabled with the option "
7881                        "-fno-range-check", &rhs->where);
7882           else if (rc == ARITH_NAN)
7883             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
7884                        ". This check can be disabled with the option "
7885                        "-fno-range-check", &rhs->where);
7886           return false;
7887         }
7888     }
7889
7890
7891   if (lhs->ts.type == BT_CHARACTER
7892         && gfc_option.warn_character_truncation)
7893     {
7894       if (lhs->ts.u.cl != NULL
7895             && lhs->ts.u.cl->length != NULL
7896             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
7897         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
7898
7899       if (rhs->expr_type == EXPR_CONSTANT)
7900         rlen = rhs->value.character.length;
7901
7902       else if (rhs->ts.u.cl != NULL
7903                  && rhs->ts.u.cl->length != NULL
7904                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
7905         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
7906
7907       if (rlen && llen && rlen > llen)
7908         gfc_warning_now ("CHARACTER expression will be truncated "
7909                          "in assignment (%d/%d) at %L",
7910                          llen, rlen, &code->loc);
7911     }
7912
7913   /* Ensure that a vector index expression for the lvalue is evaluated
7914      to a temporary if the lvalue symbol is referenced in it.  */
7915   if (lhs->rank)
7916     {
7917       for (ref = lhs->ref; ref; ref= ref->next)
7918         if (ref->type == REF_ARRAY)
7919           {
7920             for (n = 0; n < ref->u.ar.dimen; n++)
7921               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
7922                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
7923                                            ref->u.ar.start[n]))
7924                 ref->u.ar.start[n]
7925                         = gfc_get_parentheses (ref->u.ar.start[n]);
7926           }
7927     }
7928
7929   if (gfc_pure (NULL))
7930     {
7931       if (gfc_impure_variable (lhs->symtree->n.sym))
7932         {
7933           gfc_error ("Cannot assign to variable '%s' in PURE "
7934                      "procedure at %L",
7935                       lhs->symtree->n.sym->name,
7936                       &lhs->where);
7937           return rval;
7938         }
7939
7940       if (lhs->ts.type == BT_DERIVED
7941             && lhs->expr_type == EXPR_VARIABLE
7942             && lhs->ts.u.derived->attr.pointer_comp
7943             && gfc_impure_variable (rhs->symtree->n.sym))
7944         {
7945           gfc_error ("The impure variable at %L is assigned to "
7946                      "a derived type variable with a POINTER "
7947                      "component in a PURE procedure (12.6)",
7948                      &rhs->where);
7949           return rval;
7950         }
7951     }
7952
7953   /* F03:7.4.1.2.  */
7954   if (lhs->ts.type == BT_CLASS)
7955     {
7956       gfc_error ("Variable must not be polymorphic in assignment at %L",
7957                  &lhs->where);
7958       return false;
7959     }
7960
7961   gfc_check_assign (lhs, rhs, 1);
7962   return false;
7963 }
7964
7965
7966 /* Given a block of code, recursively resolve everything pointed to by this
7967    code block.  */
7968
7969 static void
7970 resolve_code (gfc_code *code, gfc_namespace *ns)
7971 {
7972   int omp_workshare_save;
7973   int forall_save;
7974   code_stack frame;
7975   gfc_try t;
7976
7977   frame.prev = cs_base;
7978   frame.head = code;
7979   cs_base = &frame;
7980
7981   find_reachable_labels (code);
7982
7983   for (; code; code = code->next)
7984     {
7985       frame.current = code;
7986       forall_save = forall_flag;
7987
7988       if (code->op == EXEC_FORALL)
7989         {
7990           forall_flag = 1;
7991           gfc_resolve_forall (code, ns, forall_save);
7992           forall_flag = 2;
7993         }
7994       else if (code->block)
7995         {
7996           omp_workshare_save = -1;
7997           switch (code->op)
7998             {
7999             case EXEC_OMP_PARALLEL_WORKSHARE:
8000               omp_workshare_save = omp_workshare_flag;
8001               omp_workshare_flag = 1;
8002               gfc_resolve_omp_parallel_blocks (code, ns);
8003               break;
8004             case EXEC_OMP_PARALLEL:
8005             case EXEC_OMP_PARALLEL_DO:
8006             case EXEC_OMP_PARALLEL_SECTIONS:
8007             case EXEC_OMP_TASK:
8008               omp_workshare_save = omp_workshare_flag;
8009               omp_workshare_flag = 0;
8010               gfc_resolve_omp_parallel_blocks (code, ns);
8011               break;
8012             case EXEC_OMP_DO:
8013               gfc_resolve_omp_do_blocks (code, ns);
8014               break;
8015             case EXEC_SELECT_TYPE:
8016               gfc_current_ns = code->ext.ns;
8017               gfc_resolve_blocks (code->block, gfc_current_ns);
8018               gfc_current_ns = ns;
8019               break;
8020             case EXEC_OMP_WORKSHARE:
8021               omp_workshare_save = omp_workshare_flag;
8022               omp_workshare_flag = 1;
8023               /* FALLTHROUGH */
8024             default:
8025               gfc_resolve_blocks (code->block, ns);
8026               break;
8027             }
8028
8029           if (omp_workshare_save != -1)
8030             omp_workshare_flag = omp_workshare_save;
8031         }
8032
8033       t = SUCCESS;
8034       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
8035         t = gfc_resolve_expr (code->expr1);
8036       forall_flag = forall_save;
8037
8038       if (gfc_resolve_expr (code->expr2) == FAILURE)
8039         t = FAILURE;
8040
8041       if (code->op == EXEC_ALLOCATE
8042           && gfc_resolve_expr (code->expr3) == FAILURE)
8043         t = FAILURE;
8044
8045       switch (code->op)
8046         {
8047         case EXEC_NOP:
8048         case EXEC_END_BLOCK:
8049         case EXEC_CYCLE:
8050         case EXEC_PAUSE:
8051         case EXEC_STOP:
8052         case EXEC_EXIT:
8053         case EXEC_CONTINUE:
8054         case EXEC_DT_END:
8055         case EXEC_ASSIGN_CALL:
8056           break;
8057
8058         case EXEC_ENTRY:
8059           /* Keep track of which entry we are up to.  */
8060           current_entry_id = code->ext.entry->id;
8061           break;
8062
8063         case EXEC_WHERE:
8064           resolve_where (code, NULL);
8065           break;
8066
8067         case EXEC_GOTO:
8068           if (code->expr1 != NULL)
8069             {
8070               if (code->expr1->ts.type != BT_INTEGER)
8071                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
8072                            "INTEGER variable", &code->expr1->where);
8073               else if (code->expr1->symtree->n.sym->attr.assign != 1)
8074                 gfc_error ("Variable '%s' has not been assigned a target "
8075                            "label at %L", code->expr1->symtree->n.sym->name,
8076                            &code->expr1->where);
8077             }
8078           else
8079             resolve_branch (code->label1, code);
8080           break;
8081
8082         case EXEC_RETURN:
8083           if (code->expr1 != NULL
8084                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
8085             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
8086                        "INTEGER return specifier", &code->expr1->where);
8087           break;
8088
8089         case EXEC_INIT_ASSIGN:
8090         case EXEC_END_PROCEDURE:
8091           break;
8092
8093         case EXEC_ASSIGN:
8094           if (t == FAILURE)
8095             break;
8096
8097           if (resolve_ordinary_assign (code, ns))
8098             {
8099               if (code->op == EXEC_COMPCALL)
8100                 goto compcall;
8101               else
8102                 goto call;
8103             }
8104           break;
8105
8106         case EXEC_LABEL_ASSIGN:
8107           if (code->label1->defined == ST_LABEL_UNKNOWN)
8108             gfc_error ("Label %d referenced at %L is never defined",
8109                        code->label1->value, &code->label1->where);
8110           if (t == SUCCESS
8111               && (code->expr1->expr_type != EXPR_VARIABLE
8112                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
8113                   || code->expr1->symtree->n.sym->ts.kind
8114                      != gfc_default_integer_kind
8115                   || code->expr1->symtree->n.sym->as != NULL))
8116             gfc_error ("ASSIGN statement at %L requires a scalar "
8117                        "default INTEGER variable", &code->expr1->where);
8118           break;
8119
8120         case EXEC_POINTER_ASSIGN:
8121           if (t == FAILURE)
8122             break;
8123
8124           gfc_check_pointer_assign (code->expr1, code->expr2);
8125           break;
8126
8127         case EXEC_ARITHMETIC_IF:
8128           if (t == SUCCESS
8129               && code->expr1->ts.type != BT_INTEGER
8130               && code->expr1->ts.type != BT_REAL)
8131             gfc_error ("Arithmetic IF statement at %L requires a numeric "
8132                        "expression", &code->expr1->where);
8133
8134           resolve_branch (code->label1, code);
8135           resolve_branch (code->label2, code);
8136           resolve_branch (code->label3, code);
8137           break;
8138
8139         case EXEC_IF:
8140           if (t == SUCCESS && code->expr1 != NULL
8141               && (code->expr1->ts.type != BT_LOGICAL
8142                   || code->expr1->rank != 0))
8143             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8144                        &code->expr1->where);
8145           break;
8146
8147         case EXEC_CALL:
8148         call:
8149           resolve_call (code);
8150           break;
8151
8152         case EXEC_COMPCALL:
8153         compcall:
8154           if (code->expr1->symtree
8155                 && code->expr1->symtree->n.sym->ts.type == BT_CLASS)
8156             resolve_class_typebound_call (code);
8157           else
8158             resolve_typebound_call (code);
8159           break;
8160
8161         case EXEC_CALL_PPC:
8162           resolve_ppc_call (code);
8163           break;
8164
8165         case EXEC_SELECT:
8166           /* Select is complicated. Also, a SELECT construct could be
8167              a transformed computed GOTO.  */
8168           resolve_select (code);
8169           break;
8170
8171         case EXEC_SELECT_TYPE:
8172           resolve_select_type (code);
8173           break;
8174
8175         case EXEC_BLOCK:
8176           gfc_resolve (code->ext.ns);
8177           break;
8178
8179         case EXEC_DO:
8180           if (code->ext.iterator != NULL)
8181             {
8182               gfc_iterator *iter = code->ext.iterator;
8183               if (gfc_resolve_iterator (iter, true) != FAILURE)
8184                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
8185             }
8186           break;
8187
8188         case EXEC_DO_WHILE:
8189           if (code->expr1 == NULL)
8190             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
8191           if (t == SUCCESS
8192               && (code->expr1->rank != 0
8193                   || code->expr1->ts.type != BT_LOGICAL))
8194             gfc_error ("Exit condition of DO WHILE loop at %L must be "
8195                        "a scalar LOGICAL expression", &code->expr1->where);
8196           break;
8197
8198         case EXEC_ALLOCATE:
8199           if (t == SUCCESS)
8200             resolve_allocate_deallocate (code, "ALLOCATE");
8201
8202           break;
8203
8204         case EXEC_DEALLOCATE:
8205           if (t == SUCCESS)
8206             resolve_allocate_deallocate (code, "DEALLOCATE");
8207
8208           break;
8209
8210         case EXEC_OPEN:
8211           if (gfc_resolve_open (code->ext.open) == FAILURE)
8212             break;
8213
8214           resolve_branch (code->ext.open->err, code);
8215           break;
8216
8217         case EXEC_CLOSE:
8218           if (gfc_resolve_close (code->ext.close) == FAILURE)
8219             break;
8220
8221           resolve_branch (code->ext.close->err, code);
8222           break;
8223
8224         case EXEC_BACKSPACE:
8225         case EXEC_ENDFILE:
8226         case EXEC_REWIND:
8227         case EXEC_FLUSH:
8228           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
8229             break;
8230
8231           resolve_branch (code->ext.filepos->err, code);
8232           break;
8233
8234         case EXEC_INQUIRE:
8235           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8236               break;
8237
8238           resolve_branch (code->ext.inquire->err, code);
8239           break;
8240
8241         case EXEC_IOLENGTH:
8242           gcc_assert (code->ext.inquire != NULL);
8243           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8244             break;
8245
8246           resolve_branch (code->ext.inquire->err, code);
8247           break;
8248
8249         case EXEC_WAIT:
8250           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
8251             break;
8252
8253           resolve_branch (code->ext.wait->err, code);
8254           resolve_branch (code->ext.wait->end, code);
8255           resolve_branch (code->ext.wait->eor, code);
8256           break;
8257
8258         case EXEC_READ:
8259         case EXEC_WRITE:
8260           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
8261             break;
8262
8263           resolve_branch (code->ext.dt->err, code);
8264           resolve_branch (code->ext.dt->end, code);
8265           resolve_branch (code->ext.dt->eor, code);
8266           break;
8267
8268         case EXEC_TRANSFER:
8269           resolve_transfer (code);
8270           break;
8271
8272         case EXEC_FORALL:
8273           resolve_forall_iterators (code->ext.forall_iterator);
8274
8275           if (code->expr1 != NULL && code->expr1->ts.type != BT_LOGICAL)
8276             gfc_error ("FORALL mask clause at %L requires a LOGICAL "
8277                        "expression", &code->expr1->where);
8278           break;
8279
8280         case EXEC_OMP_ATOMIC:
8281         case EXEC_OMP_BARRIER:
8282         case EXEC_OMP_CRITICAL:
8283         case EXEC_OMP_FLUSH:
8284         case EXEC_OMP_DO:
8285         case EXEC_OMP_MASTER:
8286         case EXEC_OMP_ORDERED:
8287         case EXEC_OMP_SECTIONS:
8288         case EXEC_OMP_SINGLE:
8289         case EXEC_OMP_TASKWAIT:
8290         case EXEC_OMP_WORKSHARE:
8291           gfc_resolve_omp_directive (code, ns);
8292           break;
8293
8294         case EXEC_OMP_PARALLEL:
8295         case EXEC_OMP_PARALLEL_DO:
8296         case EXEC_OMP_PARALLEL_SECTIONS:
8297         case EXEC_OMP_PARALLEL_WORKSHARE:
8298         case EXEC_OMP_TASK:
8299           omp_workshare_save = omp_workshare_flag;
8300           omp_workshare_flag = 0;
8301           gfc_resolve_omp_directive (code, ns);
8302           omp_workshare_flag = omp_workshare_save;
8303           break;
8304
8305         default:
8306           gfc_internal_error ("resolve_code(): Bad statement code");
8307         }
8308     }
8309
8310   cs_base = frame.prev;
8311 }
8312
8313
8314 /* Resolve initial values and make sure they are compatible with
8315    the variable.  */
8316
8317 static void
8318 resolve_values (gfc_symbol *sym)
8319 {
8320   if (sym->value == NULL)
8321     return;
8322
8323   if (gfc_resolve_expr (sym->value) == FAILURE)
8324     return;
8325
8326   gfc_check_assign_symbol (sym, sym->value);
8327 }
8328
8329
8330 /* Verify the binding labels for common blocks that are BIND(C).  The label
8331    for a BIND(C) common block must be identical in all scoping units in which
8332    the common block is declared.  Further, the binding label can not collide
8333    with any other global entity in the program.  */
8334
8335 static void
8336 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
8337 {
8338   if (comm_block_tree->n.common->is_bind_c == 1)
8339     {
8340       gfc_gsymbol *binding_label_gsym;
8341       gfc_gsymbol *comm_name_gsym;
8342
8343       /* See if a global symbol exists by the common block's name.  It may
8344          be NULL if the common block is use-associated.  */
8345       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
8346                                          comm_block_tree->n.common->name);
8347       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
8348         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
8349                    "with the global entity '%s' at %L",
8350                    comm_block_tree->n.common->binding_label,
8351                    comm_block_tree->n.common->name,
8352                    &(comm_block_tree->n.common->where),
8353                    comm_name_gsym->name, &(comm_name_gsym->where));
8354       else if (comm_name_gsym != NULL
8355                && strcmp (comm_name_gsym->name,
8356                           comm_block_tree->n.common->name) == 0)
8357         {
8358           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
8359              as expected.  */
8360           if (comm_name_gsym->binding_label == NULL)
8361             /* No binding label for common block stored yet; save this one.  */
8362             comm_name_gsym->binding_label =
8363               comm_block_tree->n.common->binding_label;
8364           else
8365             if (strcmp (comm_name_gsym->binding_label,
8366                         comm_block_tree->n.common->binding_label) != 0)
8367               {
8368                 /* Common block names match but binding labels do not.  */
8369                 gfc_error ("Binding label '%s' for common block '%s' at %L "
8370                            "does not match the binding label '%s' for common "
8371                            "block '%s' at %L",
8372                            comm_block_tree->n.common->binding_label,
8373                            comm_block_tree->n.common->name,
8374                            &(comm_block_tree->n.common->where),
8375                            comm_name_gsym->binding_label,
8376                            comm_name_gsym->name,
8377                            &(comm_name_gsym->where));
8378                 return;
8379               }
8380         }
8381
8382       /* There is no binding label (NAME="") so we have nothing further to
8383          check and nothing to add as a global symbol for the label.  */
8384       if (comm_block_tree->n.common->binding_label[0] == '\0' )
8385         return;
8386       
8387       binding_label_gsym =
8388         gfc_find_gsymbol (gfc_gsym_root,
8389                           comm_block_tree->n.common->binding_label);
8390       if (binding_label_gsym == NULL)
8391         {
8392           /* Need to make a global symbol for the binding label to prevent
8393              it from colliding with another.  */
8394           binding_label_gsym =
8395             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
8396           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
8397           binding_label_gsym->type = GSYM_COMMON;
8398         }
8399       else
8400         {
8401           /* If comm_name_gsym is NULL, the name common block is use
8402              associated and the name could be colliding.  */
8403           if (binding_label_gsym->type != GSYM_COMMON)
8404             gfc_error ("Binding label '%s' for common block '%s' at %L "
8405                        "collides with the global entity '%s' at %L",
8406                        comm_block_tree->n.common->binding_label,
8407                        comm_block_tree->n.common->name,
8408                        &(comm_block_tree->n.common->where),
8409                        binding_label_gsym->name,
8410                        &(binding_label_gsym->where));
8411           else if (comm_name_gsym != NULL
8412                    && (strcmp (binding_label_gsym->name,
8413                                comm_name_gsym->binding_label) != 0)
8414                    && (strcmp (binding_label_gsym->sym_name,
8415                                comm_name_gsym->name) != 0))
8416             gfc_error ("Binding label '%s' for common block '%s' at %L "
8417                        "collides with global entity '%s' at %L",
8418                        binding_label_gsym->name, binding_label_gsym->sym_name,
8419                        &(comm_block_tree->n.common->where),
8420                        comm_name_gsym->name, &(comm_name_gsym->where));
8421         }
8422     }
8423   
8424   return;
8425 }
8426
8427
8428 /* Verify any BIND(C) derived types in the namespace so we can report errors
8429    for them once, rather than for each variable declared of that type.  */
8430
8431 static void
8432 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
8433 {
8434   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
8435       && derived_sym->attr.is_bind_c == 1)
8436     verify_bind_c_derived_type (derived_sym);
8437   
8438   return;
8439 }
8440
8441
8442 /* Verify that any binding labels used in a given namespace do not collide 
8443    with the names or binding labels of any global symbols.  */
8444
8445 static void
8446 gfc_verify_binding_labels (gfc_symbol *sym)
8447 {
8448   int has_error = 0;
8449   
8450   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
8451       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
8452     {
8453       gfc_gsymbol *bind_c_sym;
8454
8455       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
8456       if (bind_c_sym != NULL 
8457           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
8458         {
8459           if (sym->attr.if_source == IFSRC_DECL 
8460               && (bind_c_sym->type != GSYM_SUBROUTINE 
8461                   && bind_c_sym->type != GSYM_FUNCTION) 
8462               && ((sym->attr.contained == 1 
8463                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
8464                   || (sym->attr.use_assoc == 1 
8465                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
8466             {
8467               /* Make sure global procedures don't collide with anything.  */
8468               gfc_error ("Binding label '%s' at %L collides with the global "
8469                          "entity '%s' at %L", sym->binding_label,
8470                          &(sym->declared_at), bind_c_sym->name,
8471                          &(bind_c_sym->where));
8472               has_error = 1;
8473             }
8474           else if (sym->attr.contained == 0 
8475                    && (sym->attr.if_source == IFSRC_IFBODY 
8476                        && sym->attr.flavor == FL_PROCEDURE) 
8477                    && (bind_c_sym->sym_name != NULL 
8478                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
8479             {
8480               /* Make sure procedures in interface bodies don't collide.  */
8481               gfc_error ("Binding label '%s' in interface body at %L collides "
8482                          "with the global entity '%s' at %L",
8483                          sym->binding_label,
8484                          &(sym->declared_at), bind_c_sym->name,
8485                          &(bind_c_sym->where));
8486               has_error = 1;
8487             }
8488           else if (sym->attr.contained == 0 
8489                    && sym->attr.if_source == IFSRC_UNKNOWN)
8490             if ((sym->attr.use_assoc && bind_c_sym->mod_name
8491                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
8492                 || sym->attr.use_assoc == 0)
8493               {
8494                 gfc_error ("Binding label '%s' at %L collides with global "
8495                            "entity '%s' at %L", sym->binding_label,
8496                            &(sym->declared_at), bind_c_sym->name,
8497                            &(bind_c_sym->where));
8498                 has_error = 1;
8499               }
8500
8501           if (has_error != 0)
8502             /* Clear the binding label to prevent checking multiple times.  */
8503             sym->binding_label[0] = '\0';
8504         }
8505       else if (bind_c_sym == NULL)
8506         {
8507           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
8508           bind_c_sym->where = sym->declared_at;
8509           bind_c_sym->sym_name = sym->name;
8510
8511           if (sym->attr.use_assoc == 1)
8512             bind_c_sym->mod_name = sym->module;
8513           else
8514             if (sym->ns->proc_name != NULL)
8515               bind_c_sym->mod_name = sym->ns->proc_name->name;
8516
8517           if (sym->attr.contained == 0)
8518             {
8519               if (sym->attr.subroutine)
8520                 bind_c_sym->type = GSYM_SUBROUTINE;
8521               else if (sym->attr.function)
8522                 bind_c_sym->type = GSYM_FUNCTION;
8523             }
8524         }
8525     }
8526   return;
8527 }
8528
8529
8530 /* Resolve an index expression.  */
8531
8532 static gfc_try
8533 resolve_index_expr (gfc_expr *e)
8534 {
8535   if (gfc_resolve_expr (e) == FAILURE)
8536     return FAILURE;
8537
8538   if (gfc_simplify_expr (e, 0) == FAILURE)
8539     return FAILURE;
8540
8541   if (gfc_specification_expr (e) == FAILURE)
8542     return FAILURE;
8543
8544   return SUCCESS;
8545 }
8546
8547 /* Resolve a charlen structure.  */
8548
8549 static gfc_try
8550 resolve_charlen (gfc_charlen *cl)
8551 {
8552   int i, k;
8553
8554   if (cl->resolved)
8555     return SUCCESS;
8556
8557   cl->resolved = 1;
8558
8559   specification_expr = 1;
8560
8561   if (resolve_index_expr (cl->length) == FAILURE)
8562     {
8563       specification_expr = 0;
8564       return FAILURE;
8565     }
8566
8567   /* "If the character length parameter value evaluates to a negative
8568      value, the length of character entities declared is zero."  */
8569   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
8570     {
8571       if (gfc_option.warn_surprising)
8572         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
8573                          " the length has been set to zero",
8574                          &cl->length->where, i);
8575       gfc_replace_expr (cl->length, gfc_int_expr (0));
8576     }
8577
8578   /* Check that the character length is not too large.  */
8579   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
8580   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
8581       && cl->length->ts.type == BT_INTEGER
8582       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
8583     {
8584       gfc_error ("String length at %L is too large", &cl->length->where);
8585       return FAILURE;
8586     }
8587
8588   return SUCCESS;
8589 }
8590
8591
8592 /* Test for non-constant shape arrays.  */
8593
8594 static bool
8595 is_non_constant_shape_array (gfc_symbol *sym)
8596 {
8597   gfc_expr *e;
8598   int i;
8599   bool not_constant;
8600
8601   not_constant = false;
8602   if (sym->as != NULL)
8603     {
8604       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
8605          has not been simplified; parameter array references.  Do the
8606          simplification now.  */
8607       for (i = 0; i < sym->as->rank; i++)
8608         {
8609           e = sym->as->lower[i];
8610           if (e && (resolve_index_expr (e) == FAILURE
8611                     || !gfc_is_constant_expr (e)))
8612             not_constant = true;
8613
8614           e = sym->as->upper[i];
8615           if (e && (resolve_index_expr (e) == FAILURE
8616                     || !gfc_is_constant_expr (e)))
8617             not_constant = true;
8618         }
8619     }
8620   return not_constant;
8621 }
8622
8623 /* Given a symbol and an initialization expression, add code to initialize
8624    the symbol to the function entry.  */
8625 static void
8626 build_init_assign (gfc_symbol *sym, gfc_expr *init)
8627 {
8628   gfc_expr *lval;
8629   gfc_code *init_st;
8630   gfc_namespace *ns = sym->ns;
8631
8632   /* Search for the function namespace if this is a contained
8633      function without an explicit result.  */
8634   if (sym->attr.function && sym == sym->result
8635       && sym->name != sym->ns->proc_name->name)
8636     {
8637       ns = ns->contained;
8638       for (;ns; ns = ns->sibling)
8639         if (strcmp (ns->proc_name->name, sym->name) == 0)
8640           break;
8641     }
8642
8643   if (ns == NULL)
8644     {
8645       gfc_free_expr (init);
8646       return;
8647     }
8648
8649   /* Build an l-value expression for the result.  */
8650   lval = gfc_lval_expr_from_sym (sym);
8651
8652   /* Add the code at scope entry.  */
8653   init_st = gfc_get_code ();
8654   init_st->next = ns->code;
8655   ns->code = init_st;
8656
8657   /* Assign the default initializer to the l-value.  */
8658   init_st->loc = sym->declared_at;
8659   init_st->op = EXEC_INIT_ASSIGN;
8660   init_st->expr1 = lval;
8661   init_st->expr2 = init;
8662 }
8663
8664 /* Assign the default initializer to a derived type variable or result.  */
8665
8666 static void
8667 apply_default_init (gfc_symbol *sym)
8668 {
8669   gfc_expr *init = NULL;
8670
8671   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
8672     return;
8673
8674   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
8675     init = gfc_default_initializer (&sym->ts);
8676
8677   if (init == NULL)
8678     return;
8679
8680   build_init_assign (sym, init);
8681 }
8682
8683 /* Build an initializer for a local integer, real, complex, logical, or
8684    character variable, based on the command line flags finit-local-zero,
8685    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
8686    null if the symbol should not have a default initialization.  */
8687 static gfc_expr *
8688 build_default_init_expr (gfc_symbol *sym)
8689 {
8690   int char_len;
8691   gfc_expr *init_expr;
8692   int i;
8693
8694   /* These symbols should never have a default initialization.  */
8695   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
8696       || sym->attr.external
8697       || sym->attr.dummy
8698       || sym->attr.pointer
8699       || sym->attr.in_equivalence
8700       || sym->attr.in_common
8701       || sym->attr.data
8702       || sym->module
8703       || sym->attr.cray_pointee
8704       || sym->attr.cray_pointer)
8705     return NULL;
8706
8707   /* Now we'll try to build an initializer expression.  */
8708   init_expr = gfc_get_expr ();
8709   init_expr->expr_type = EXPR_CONSTANT;
8710   init_expr->ts.type = sym->ts.type;
8711   init_expr->ts.kind = sym->ts.kind;
8712   init_expr->where = sym->declared_at;
8713   
8714   /* We will only initialize integers, reals, complex, logicals, and
8715      characters, and only if the corresponding command-line flags
8716      were set.  Otherwise, we free init_expr and return null.  */
8717   switch (sym->ts.type)
8718     {    
8719     case BT_INTEGER:
8720       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
8721         mpz_init_set_si (init_expr->value.integer, 
8722                          gfc_option.flag_init_integer_value);
8723       else
8724         {
8725           gfc_free_expr (init_expr);
8726           init_expr = NULL;
8727         }
8728       break;
8729
8730     case BT_REAL:
8731       mpfr_init (init_expr->value.real);
8732       switch (gfc_option.flag_init_real)
8733         {
8734         case GFC_INIT_REAL_SNAN:
8735           init_expr->is_snan = 1;
8736           /* Fall through.  */
8737         case GFC_INIT_REAL_NAN:
8738           mpfr_set_nan (init_expr->value.real);
8739           break;
8740
8741         case GFC_INIT_REAL_INF:
8742           mpfr_set_inf (init_expr->value.real, 1);
8743           break;
8744
8745         case GFC_INIT_REAL_NEG_INF:
8746           mpfr_set_inf (init_expr->value.real, -1);
8747           break;
8748
8749         case GFC_INIT_REAL_ZERO:
8750           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
8751           break;
8752
8753         default:
8754           gfc_free_expr (init_expr);
8755           init_expr = NULL;
8756           break;
8757         }
8758       break;
8759           
8760     case BT_COMPLEX:
8761       mpc_init2 (init_expr->value.complex, mpfr_get_default_prec());
8762       switch (gfc_option.flag_init_real)
8763         {
8764         case GFC_INIT_REAL_SNAN:
8765           init_expr->is_snan = 1;
8766           /* Fall through.  */
8767         case GFC_INIT_REAL_NAN:
8768           mpfr_set_nan (mpc_realref (init_expr->value.complex));
8769           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
8770           break;
8771
8772         case GFC_INIT_REAL_INF:
8773           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
8774           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
8775           break;
8776
8777         case GFC_INIT_REAL_NEG_INF:
8778           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
8779           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
8780           break;
8781
8782         case GFC_INIT_REAL_ZERO:
8783           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
8784           break;
8785
8786         default:
8787           gfc_free_expr (init_expr);
8788           init_expr = NULL;
8789           break;
8790         }
8791       break;
8792           
8793     case BT_LOGICAL:
8794       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
8795         init_expr->value.logical = 0;
8796       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
8797         init_expr->value.logical = 1;
8798       else
8799         {
8800           gfc_free_expr (init_expr);
8801           init_expr = NULL;
8802         }
8803       break;
8804           
8805     case BT_CHARACTER:
8806       /* For characters, the length must be constant in order to 
8807          create a default initializer.  */
8808       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
8809           && sym->ts.u.cl->length
8810           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8811         {
8812           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
8813           init_expr->value.character.length = char_len;
8814           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
8815           for (i = 0; i < char_len; i++)
8816             init_expr->value.character.string[i]
8817               = (unsigned char) gfc_option.flag_init_character_value;
8818         }
8819       else
8820         {
8821           gfc_free_expr (init_expr);
8822           init_expr = NULL;
8823         }
8824       break;
8825           
8826     default:
8827      gfc_free_expr (init_expr);
8828      init_expr = NULL;
8829     }
8830   return init_expr;
8831 }
8832
8833 /* Add an initialization expression to a local variable.  */
8834 static void
8835 apply_default_init_local (gfc_symbol *sym)
8836 {
8837   gfc_expr *init = NULL;
8838
8839   /* The symbol should be a variable or a function return value.  */
8840   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
8841       || (sym->attr.function && sym->result != sym))
8842     return;
8843
8844   /* Try to build the initializer expression.  If we can't initialize
8845      this symbol, then init will be NULL.  */
8846   init = build_default_init_expr (sym);
8847   if (init == NULL)
8848     return;
8849
8850   /* For saved variables, we don't want to add an initializer at 
8851      function entry, so we just add a static initializer.  */
8852   if (sym->attr.save || sym->ns->save_all 
8853       || gfc_option.flag_max_stack_var_size == 0)
8854     {
8855       /* Don't clobber an existing initializer!  */
8856       gcc_assert (sym->value == NULL);
8857       sym->value = init;
8858       return;
8859     }
8860
8861   build_init_assign (sym, init);
8862 }
8863
8864 /* Resolution of common features of flavors variable and procedure.  */
8865
8866 static gfc_try
8867 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
8868 {
8869   /* Constraints on deferred shape variable.  */
8870   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
8871     {
8872       if (sym->attr.allocatable)
8873         {
8874           if (sym->attr.dimension)
8875             {
8876               gfc_error ("Allocatable array '%s' at %L must have "
8877                          "a deferred shape", sym->name, &sym->declared_at);
8878               return FAILURE;
8879             }
8880           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
8881                                    "may not be ALLOCATABLE", sym->name,
8882                                    &sym->declared_at) == FAILURE)
8883             return FAILURE;
8884         }
8885
8886       if (sym->attr.pointer && sym->attr.dimension)
8887         {
8888           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
8889                      sym->name, &sym->declared_at);
8890           return FAILURE;
8891         }
8892
8893     }
8894   else
8895     {
8896       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
8897           && !sym->attr.dummy && sym->ts.type != BT_CLASS)
8898         {
8899           gfc_error ("Array '%s' at %L cannot have a deferred shape",
8900                      sym->name, &sym->declared_at);
8901           return FAILURE;
8902          }
8903     }
8904   return SUCCESS;
8905 }
8906
8907
8908 /* Additional checks for symbols with flavor variable and derived
8909    type.  To be called from resolve_fl_variable.  */
8910
8911 static gfc_try
8912 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
8913 {
8914   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
8915
8916   /* Check to see if a derived type is blocked from being host
8917      associated by the presence of another class I symbol in the same
8918      namespace.  14.6.1.3 of the standard and the discussion on
8919      comp.lang.fortran.  */
8920   if (sym->ns != sym->ts.u.derived->ns
8921       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
8922     {
8923       gfc_symbol *s;
8924       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
8925       if (s && s->attr.flavor != FL_DERIVED)
8926         {
8927           gfc_error ("The type '%s' cannot be host associated at %L "
8928                      "because it is blocked by an incompatible object "
8929                      "of the same name declared at %L",
8930                      sym->ts.u.derived->name, &sym->declared_at,
8931                      &s->declared_at);
8932           return FAILURE;
8933         }
8934     }
8935
8936   /* 4th constraint in section 11.3: "If an object of a type for which
8937      component-initialization is specified (R429) appears in the
8938      specification-part of a module and does not have the ALLOCATABLE
8939      or POINTER attribute, the object shall have the SAVE attribute."
8940
8941      The check for initializers is performed with
8942      has_default_initializer because gfc_default_initializer generates
8943      a hidden default for allocatable components.  */
8944   if (!(sym->value || no_init_flag) && sym->ns->proc_name
8945       && sym->ns->proc_name->attr.flavor == FL_MODULE
8946       && !sym->ns->save_all && !sym->attr.save
8947       && !sym->attr.pointer && !sym->attr.allocatable
8948       && has_default_initializer (sym->ts.u.derived)
8949       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
8950                          "module variable '%s' at %L, needed due to "
8951                          "the default initialization", sym->name,
8952                          &sym->declared_at) == FAILURE)
8953     return FAILURE;
8954
8955   if (sym->ts.type == BT_CLASS)
8956     {
8957       /* C502.  */
8958       if (!gfc_type_is_extensible (sym->ts.u.derived->components->ts.u.derived))
8959         {
8960           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
8961                      sym->ts.u.derived->components->ts.u.derived->name,
8962                      sym->name, &sym->declared_at);
8963           return FAILURE;
8964         }
8965
8966       /* C509.  */
8967       /* Assume that use associated symbols were checked in the module ns.  */ 
8968       if (!sym->attr.class_ok && !sym->attr.use_assoc)
8969         {
8970           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
8971                      "or pointer", sym->name, &sym->declared_at);
8972           return FAILURE;
8973         }
8974     }
8975
8976   /* Assign default initializer.  */
8977   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
8978       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
8979     {
8980       sym->value = gfc_default_initializer (&sym->ts);
8981     }
8982
8983   return SUCCESS;
8984 }
8985
8986
8987 /* Resolve symbols with flavor variable.  */
8988
8989 static gfc_try
8990 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
8991 {
8992   int no_init_flag, automatic_flag;
8993   gfc_expr *e;
8994   const char *auto_save_msg;
8995
8996   auto_save_msg = "Automatic object '%s' at %L cannot have the "
8997                   "SAVE attribute";
8998
8999   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9000     return FAILURE;
9001
9002   /* Set this flag to check that variables are parameters of all entries.
9003      This check is effected by the call to gfc_resolve_expr through
9004      is_non_constant_shape_array.  */
9005   specification_expr = 1;
9006
9007   if (sym->ns->proc_name
9008       && (sym->ns->proc_name->attr.flavor == FL_MODULE
9009           || sym->ns->proc_name->attr.is_main_program)
9010       && !sym->attr.use_assoc
9011       && !sym->attr.allocatable
9012       && !sym->attr.pointer
9013       && is_non_constant_shape_array (sym))
9014     {
9015       /* The shape of a main program or module array needs to be
9016          constant.  */
9017       gfc_error ("The module or main program array '%s' at %L must "
9018                  "have constant shape", sym->name, &sym->declared_at);
9019       specification_expr = 0;
9020       return FAILURE;
9021     }
9022
9023   if (sym->ts.type == BT_CHARACTER)
9024     {
9025       /* Make sure that character string variables with assumed length are
9026          dummy arguments.  */
9027       e = sym->ts.u.cl->length;
9028       if (e == NULL && !sym->attr.dummy && !sym->attr.result)
9029         {
9030           gfc_error ("Entity with assumed character length at %L must be a "
9031                      "dummy argument or a PARAMETER", &sym->declared_at);
9032           return FAILURE;
9033         }
9034
9035       if (e && sym->attr.save && !gfc_is_constant_expr (e))
9036         {
9037           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9038           return FAILURE;
9039         }
9040
9041       if (!gfc_is_constant_expr (e)
9042           && !(e->expr_type == EXPR_VARIABLE
9043                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
9044           && sym->ns->proc_name
9045           && (sym->ns->proc_name->attr.flavor == FL_MODULE
9046               || sym->ns->proc_name->attr.is_main_program)
9047           && !sym->attr.use_assoc)
9048         {
9049           gfc_error ("'%s' at %L must have constant character length "
9050                      "in this context", sym->name, &sym->declared_at);
9051           return FAILURE;
9052         }
9053     }
9054
9055   if (sym->value == NULL && sym->attr.referenced)
9056     apply_default_init_local (sym); /* Try to apply a default initialization.  */
9057
9058   /* Determine if the symbol may not have an initializer.  */
9059   no_init_flag = automatic_flag = 0;
9060   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
9061       || sym->attr.intrinsic || sym->attr.result)
9062     no_init_flag = 1;
9063   else if (sym->attr.dimension && !sym->attr.pointer
9064            && is_non_constant_shape_array (sym))
9065     {
9066       no_init_flag = automatic_flag = 1;
9067
9068       /* Also, they must not have the SAVE attribute.
9069          SAVE_IMPLICIT is checked below.  */
9070       if (sym->attr.save == SAVE_EXPLICIT)
9071         {
9072           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9073           return FAILURE;
9074         }
9075     }
9076
9077   /* Ensure that any initializer is simplified.  */
9078   if (sym->value)
9079     gfc_simplify_expr (sym->value, 1);
9080
9081   /* Reject illegal initializers.  */
9082   if (!sym->mark && sym->value)
9083     {
9084       if (sym->attr.allocatable)
9085         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
9086                    sym->name, &sym->declared_at);
9087       else if (sym->attr.external)
9088         gfc_error ("External '%s' at %L cannot have an initializer",
9089                    sym->name, &sym->declared_at);
9090       else if (sym->attr.dummy
9091         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
9092         gfc_error ("Dummy '%s' at %L cannot have an initializer",
9093                    sym->name, &sym->declared_at);
9094       else if (sym->attr.intrinsic)
9095         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
9096                    sym->name, &sym->declared_at);
9097       else if (sym->attr.result)
9098         gfc_error ("Function result '%s' at %L cannot have an initializer",
9099                    sym->name, &sym->declared_at);
9100       else if (automatic_flag)
9101         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
9102                    sym->name, &sym->declared_at);
9103       else
9104         goto no_init_error;
9105       return FAILURE;
9106     }
9107
9108 no_init_error:
9109   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
9110     return resolve_fl_variable_derived (sym, no_init_flag);
9111
9112   return SUCCESS;
9113 }
9114
9115
9116 /* Resolve a procedure.  */
9117
9118 static gfc_try
9119 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
9120 {
9121   gfc_formal_arglist *arg;
9122
9123   if (sym->attr.function
9124       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9125     return FAILURE;
9126
9127   if (sym->ts.type == BT_CHARACTER)
9128     {
9129       gfc_charlen *cl = sym->ts.u.cl;
9130
9131       if (cl && cl->length && gfc_is_constant_expr (cl->length)
9132              && resolve_charlen (cl) == FAILURE)
9133         return FAILURE;
9134
9135       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
9136           && sym->attr.proc == PROC_ST_FUNCTION)
9137         {
9138           gfc_error ("Character-valued statement function '%s' at %L must "
9139                      "have constant length", sym->name, &sym->declared_at);
9140           return FAILURE;
9141         }
9142     }
9143
9144   /* Ensure that derived type for are not of a private type.  Internal
9145      module procedures are excluded by 2.2.3.3 - i.e., they are not
9146      externally accessible and can access all the objects accessible in
9147      the host.  */
9148   if (!(sym->ns->parent
9149         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
9150       && gfc_check_access(sym->attr.access, sym->ns->default_access))
9151     {
9152       gfc_interface *iface;
9153
9154       for (arg = sym->formal; arg; arg = arg->next)
9155         {
9156           if (arg->sym
9157               && arg->sym->ts.type == BT_DERIVED
9158               && !arg->sym->ts.u.derived->attr.use_assoc
9159               && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9160                                     arg->sym->ts.u.derived->ns->default_access)
9161               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
9162                                  "PRIVATE type and cannot be a dummy argument"
9163                                  " of '%s', which is PUBLIC at %L",
9164                                  arg->sym->name, sym->name, &sym->declared_at)
9165                  == FAILURE)
9166             {
9167               /* Stop this message from recurring.  */
9168               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9169               return FAILURE;
9170             }
9171         }
9172
9173       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9174          PRIVATE to the containing module.  */
9175       for (iface = sym->generic; iface; iface = iface->next)
9176         {
9177           for (arg = iface->sym->formal; arg; arg = arg->next)
9178             {
9179               if (arg->sym
9180                   && arg->sym->ts.type == BT_DERIVED
9181                   && !arg->sym->ts.u.derived->attr.use_assoc
9182                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9183                                         arg->sym->ts.u.derived->ns->default_access)
9184                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9185                                      "'%s' in PUBLIC interface '%s' at %L "
9186                                      "takes dummy arguments of '%s' which is "
9187                                      "PRIVATE", iface->sym->name, sym->name,
9188                                      &iface->sym->declared_at,
9189                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9190                 {
9191                   /* Stop this message from recurring.  */
9192                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9193                   return FAILURE;
9194                 }
9195              }
9196         }
9197
9198       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9199          PRIVATE to the containing module.  */
9200       for (iface = sym->generic; iface; iface = iface->next)
9201         {
9202           for (arg = iface->sym->formal; arg; arg = arg->next)
9203             {
9204               if (arg->sym
9205                   && arg->sym->ts.type == BT_DERIVED
9206                   && !arg->sym->ts.u.derived->attr.use_assoc
9207                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9208                                         arg->sym->ts.u.derived->ns->default_access)
9209                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9210                                      "'%s' in PUBLIC interface '%s' at %L "
9211                                      "takes dummy arguments of '%s' which is "
9212                                      "PRIVATE", iface->sym->name, sym->name,
9213                                      &iface->sym->declared_at,
9214                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9215                 {
9216                   /* Stop this message from recurring.  */
9217                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9218                   return FAILURE;
9219                 }
9220              }
9221         }
9222     }
9223
9224   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
9225       && !sym->attr.proc_pointer)
9226     {
9227       gfc_error ("Function '%s' at %L cannot have an initializer",
9228                  sym->name, &sym->declared_at);
9229       return FAILURE;
9230     }
9231
9232   /* An external symbol may not have an initializer because it is taken to be
9233      a procedure. Exception: Procedure Pointers.  */
9234   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
9235     {
9236       gfc_error ("External object '%s' at %L may not have an initializer",
9237                  sym->name, &sym->declared_at);
9238       return FAILURE;
9239     }
9240
9241   /* An elemental function is required to return a scalar 12.7.1  */
9242   if (sym->attr.elemental && sym->attr.function && sym->as)
9243     {
9244       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
9245                  "result", sym->name, &sym->declared_at);
9246       /* Reset so that the error only occurs once.  */
9247       sym->attr.elemental = 0;
9248       return FAILURE;
9249     }
9250
9251   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
9252      char-len-param shall not be array-valued, pointer-valued, recursive
9253      or pure.  ....snip... A character value of * may only be used in the
9254      following ways: (i) Dummy arg of procedure - dummy associates with
9255      actual length; (ii) To declare a named constant; or (iii) External
9256      function - but length must be declared in calling scoping unit.  */
9257   if (sym->attr.function
9258       && sym->ts.type == BT_CHARACTER
9259       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
9260     {
9261       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
9262           || (sym->attr.recursive) || (sym->attr.pure))
9263         {
9264           if (sym->as && sym->as->rank)
9265             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9266                        "array-valued", sym->name, &sym->declared_at);
9267
9268           if (sym->attr.pointer)
9269             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9270                        "pointer-valued", sym->name, &sym->declared_at);
9271
9272           if (sym->attr.pure)
9273             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9274                        "pure", sym->name, &sym->declared_at);
9275
9276           if (sym->attr.recursive)
9277             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9278                        "recursive", sym->name, &sym->declared_at);
9279
9280           return FAILURE;
9281         }
9282
9283       /* Appendix B.2 of the standard.  Contained functions give an
9284          error anyway.  Fixed-form is likely to be F77/legacy.  */
9285       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
9286         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
9287                         "CHARACTER(*) function '%s' at %L",
9288                         sym->name, &sym->declared_at);
9289     }
9290
9291   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
9292     {
9293       gfc_formal_arglist *curr_arg;
9294       int has_non_interop_arg = 0;
9295
9296       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
9297                              sym->common_block) == FAILURE)
9298         {
9299           /* Clear these to prevent looking at them again if there was an
9300              error.  */
9301           sym->attr.is_bind_c = 0;
9302           sym->attr.is_c_interop = 0;
9303           sym->ts.is_c_interop = 0;
9304         }
9305       else
9306         {
9307           /* So far, no errors have been found.  */
9308           sym->attr.is_c_interop = 1;
9309           sym->ts.is_c_interop = 1;
9310         }
9311       
9312       curr_arg = sym->formal;
9313       while (curr_arg != NULL)
9314         {
9315           /* Skip implicitly typed dummy args here.  */
9316           if (curr_arg->sym->attr.implicit_type == 0)
9317             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
9318               /* If something is found to fail, record the fact so we
9319                  can mark the symbol for the procedure as not being
9320                  BIND(C) to try and prevent multiple errors being
9321                  reported.  */
9322               has_non_interop_arg = 1;
9323           
9324           curr_arg = curr_arg->next;
9325         }
9326
9327       /* See if any of the arguments were not interoperable and if so, clear
9328          the procedure symbol to prevent duplicate error messages.  */
9329       if (has_non_interop_arg != 0)
9330         {
9331           sym->attr.is_c_interop = 0;
9332           sym->ts.is_c_interop = 0;
9333           sym->attr.is_bind_c = 0;
9334         }
9335     }
9336   
9337   if (!sym->attr.proc_pointer)
9338     {
9339       if (sym->attr.save == SAVE_EXPLICIT)
9340         {
9341           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
9342                      "in '%s' at %L", sym->name, &sym->declared_at);
9343           return FAILURE;
9344         }
9345       if (sym->attr.intent)
9346         {
9347           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
9348                      "in '%s' at %L", sym->name, &sym->declared_at);
9349           return FAILURE;
9350         }
9351       if (sym->attr.subroutine && sym->attr.result)
9352         {
9353           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
9354                      "in '%s' at %L", sym->name, &sym->declared_at);
9355           return FAILURE;
9356         }
9357       if (sym->attr.external && sym->attr.function
9358           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
9359               || sym->attr.contained))
9360         {
9361           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
9362                      "in '%s' at %L", sym->name, &sym->declared_at);
9363           return FAILURE;
9364         }
9365       if (strcmp ("ppr@", sym->name) == 0)
9366         {
9367           gfc_error ("Procedure pointer result '%s' at %L "
9368                      "is missing the pointer attribute",
9369                      sym->ns->proc_name->name, &sym->declared_at);
9370           return FAILURE;
9371         }
9372     }
9373
9374   return SUCCESS;
9375 }
9376
9377
9378 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
9379    been defined and we now know their defined arguments, check that they fulfill
9380    the requirements of the standard for procedures used as finalizers.  */
9381
9382 static gfc_try
9383 gfc_resolve_finalizers (gfc_symbol* derived)
9384 {
9385   gfc_finalizer* list;
9386   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
9387   gfc_try result = SUCCESS;
9388   bool seen_scalar = false;
9389
9390   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
9391     return SUCCESS;
9392
9393   /* Walk over the list of finalizer-procedures, check them, and if any one
9394      does not fit in with the standard's definition, print an error and remove
9395      it from the list.  */
9396   prev_link = &derived->f2k_derived->finalizers;
9397   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
9398     {
9399       gfc_symbol* arg;
9400       gfc_finalizer* i;
9401       int my_rank;
9402
9403       /* Skip this finalizer if we already resolved it.  */
9404       if (list->proc_tree)
9405         {
9406           prev_link = &(list->next);
9407           continue;
9408         }
9409
9410       /* Check this exists and is a SUBROUTINE.  */
9411       if (!list->proc_sym->attr.subroutine)
9412         {
9413           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
9414                      list->proc_sym->name, &list->where);
9415           goto error;
9416         }
9417
9418       /* We should have exactly one argument.  */
9419       if (!list->proc_sym->formal || list->proc_sym->formal->next)
9420         {
9421           gfc_error ("FINAL procedure at %L must have exactly one argument",
9422                      &list->where);
9423           goto error;
9424         }
9425       arg = list->proc_sym->formal->sym;
9426
9427       /* This argument must be of our type.  */
9428       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
9429         {
9430           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
9431                      &arg->declared_at, derived->name);
9432           goto error;
9433         }
9434
9435       /* It must neither be a pointer nor allocatable nor optional.  */
9436       if (arg->attr.pointer)
9437         {
9438           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
9439                      &arg->declared_at);
9440           goto error;
9441         }
9442       if (arg->attr.allocatable)
9443         {
9444           gfc_error ("Argument of FINAL procedure at %L must not be"
9445                      " ALLOCATABLE", &arg->declared_at);
9446           goto error;
9447         }
9448       if (arg->attr.optional)
9449         {
9450           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
9451                      &arg->declared_at);
9452           goto error;
9453         }
9454
9455       /* It must not be INTENT(OUT).  */
9456       if (arg->attr.intent == INTENT_OUT)
9457         {
9458           gfc_error ("Argument of FINAL procedure at %L must not be"
9459                      " INTENT(OUT)", &arg->declared_at);
9460           goto error;
9461         }
9462
9463       /* Warn if the procedure is non-scalar and not assumed shape.  */
9464       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
9465           && arg->as->type != AS_ASSUMED_SHAPE)
9466         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
9467                      " shape argument", &arg->declared_at);
9468
9469       /* Check that it does not match in kind and rank with a FINAL procedure
9470          defined earlier.  To really loop over the *earlier* declarations,
9471          we need to walk the tail of the list as new ones were pushed at the
9472          front.  */
9473       /* TODO: Handle kind parameters once they are implemented.  */
9474       my_rank = (arg->as ? arg->as->rank : 0);
9475       for (i = list->next; i; i = i->next)
9476         {
9477           /* Argument list might be empty; that is an error signalled earlier,
9478              but we nevertheless continued resolving.  */
9479           if (i->proc_sym->formal)
9480             {
9481               gfc_symbol* i_arg = i->proc_sym->formal->sym;
9482               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
9483               if (i_rank == my_rank)
9484                 {
9485                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
9486                              " rank (%d) as '%s'",
9487                              list->proc_sym->name, &list->where, my_rank, 
9488                              i->proc_sym->name);
9489                   goto error;
9490                 }
9491             }
9492         }
9493
9494         /* Is this the/a scalar finalizer procedure?  */
9495         if (!arg->as || arg->as->rank == 0)
9496           seen_scalar = true;
9497
9498         /* Find the symtree for this procedure.  */
9499         gcc_assert (!list->proc_tree);
9500         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
9501
9502         prev_link = &list->next;
9503         continue;
9504
9505         /* Remove wrong nodes immediately from the list so we don't risk any
9506            troubles in the future when they might fail later expectations.  */
9507 error:
9508         result = FAILURE;
9509         i = list;
9510         *prev_link = list->next;
9511         gfc_free_finalizer (i);
9512     }
9513
9514   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
9515      were nodes in the list, must have been for arrays.  It is surely a good
9516      idea to have a scalar version there if there's something to finalize.  */
9517   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
9518     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
9519                  " defined at %L, suggest also scalar one",
9520                  derived->name, &derived->declared_at);
9521
9522   /* TODO:  Remove this error when finalization is finished.  */
9523   gfc_error ("Finalization at %L is not yet implemented",
9524              &derived->declared_at);
9525
9526   return result;
9527 }
9528
9529
9530 /* Check that it is ok for the typebound procedure proc to override the
9531    procedure old.  */
9532
9533 static gfc_try
9534 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
9535 {
9536   locus where;
9537   const gfc_symbol* proc_target;
9538   const gfc_symbol* old_target;
9539   unsigned proc_pass_arg, old_pass_arg, argpos;
9540   gfc_formal_arglist* proc_formal;
9541   gfc_formal_arglist* old_formal;
9542
9543   /* This procedure should only be called for non-GENERIC proc.  */
9544   gcc_assert (!proc->n.tb->is_generic);
9545
9546   /* If the overwritten procedure is GENERIC, this is an error.  */
9547   if (old->n.tb->is_generic)
9548     {
9549       gfc_error ("Can't overwrite GENERIC '%s' at %L",
9550                  old->name, &proc->n.tb->where);
9551       return FAILURE;
9552     }
9553
9554   where = proc->n.tb->where;
9555   proc_target = proc->n.tb->u.specific->n.sym;
9556   old_target = old->n.tb->u.specific->n.sym;
9557
9558   /* Check that overridden binding is not NON_OVERRIDABLE.  */
9559   if (old->n.tb->non_overridable)
9560     {
9561       gfc_error ("'%s' at %L overrides a procedure binding declared"
9562                  " NON_OVERRIDABLE", proc->name, &where);
9563       return FAILURE;
9564     }
9565
9566   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
9567   if (!old->n.tb->deferred && proc->n.tb->deferred)
9568     {
9569       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
9570                  " non-DEFERRED binding", proc->name, &where);
9571       return FAILURE;
9572     }
9573
9574   /* If the overridden binding is PURE, the overriding must be, too.  */
9575   if (old_target->attr.pure && !proc_target->attr.pure)
9576     {
9577       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
9578                  proc->name, &where);
9579       return FAILURE;
9580     }
9581
9582   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
9583      is not, the overriding must not be either.  */
9584   if (old_target->attr.elemental && !proc_target->attr.elemental)
9585     {
9586       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
9587                  " ELEMENTAL", proc->name, &where);
9588       return FAILURE;
9589     }
9590   if (!old_target->attr.elemental && proc_target->attr.elemental)
9591     {
9592       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
9593                  " be ELEMENTAL, either", proc->name, &where);
9594       return FAILURE;
9595     }
9596
9597   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
9598      SUBROUTINE.  */
9599   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
9600     {
9601       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
9602                  " SUBROUTINE", proc->name, &where);
9603       return FAILURE;
9604     }
9605
9606   /* If the overridden binding is a FUNCTION, the overriding must also be a
9607      FUNCTION and have the same characteristics.  */
9608   if (old_target->attr.function)
9609     {
9610       if (!proc_target->attr.function)
9611         {
9612           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
9613                      " FUNCTION", proc->name, &where);
9614           return FAILURE;
9615         }
9616
9617       /* FIXME:  Do more comprehensive checking (including, for instance, the
9618          rank and array-shape).  */
9619       gcc_assert (proc_target->result && old_target->result);
9620       if (!gfc_compare_types (&proc_target->result->ts,
9621                               &old_target->result->ts))
9622         {
9623           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
9624                      " matching result types", proc->name, &where);
9625           return FAILURE;
9626         }
9627     }
9628
9629   /* If the overridden binding is PUBLIC, the overriding one must not be
9630      PRIVATE.  */
9631   if (old->n.tb->access == ACCESS_PUBLIC
9632       && proc->n.tb->access == ACCESS_PRIVATE)
9633     {
9634       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
9635                  " PRIVATE", proc->name, &where);
9636       return FAILURE;
9637     }
9638
9639   /* Compare the formal argument lists of both procedures.  This is also abused
9640      to find the position of the passed-object dummy arguments of both
9641      bindings as at least the overridden one might not yet be resolved and we
9642      need those positions in the check below.  */
9643   proc_pass_arg = old_pass_arg = 0;
9644   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
9645     proc_pass_arg = 1;
9646   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
9647     old_pass_arg = 1;
9648   argpos = 1;
9649   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
9650        proc_formal && old_formal;
9651        proc_formal = proc_formal->next, old_formal = old_formal->next)
9652     {
9653       if (proc->n.tb->pass_arg
9654           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
9655         proc_pass_arg = argpos;
9656       if (old->n.tb->pass_arg
9657           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
9658         old_pass_arg = argpos;
9659
9660       /* Check that the names correspond.  */
9661       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
9662         {
9663           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
9664                      " to match the corresponding argument of the overridden"
9665                      " procedure", proc_formal->sym->name, proc->name, &where,
9666                      old_formal->sym->name);
9667           return FAILURE;
9668         }
9669
9670       /* Check that the types correspond if neither is the passed-object
9671          argument.  */
9672       /* FIXME:  Do more comprehensive testing here.  */
9673       if (proc_pass_arg != argpos && old_pass_arg != argpos
9674           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
9675         {
9676           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L "
9677                      "in respect to the overridden procedure",
9678                      proc_formal->sym->name, proc->name, &where);
9679           return FAILURE;
9680         }
9681
9682       ++argpos;
9683     }
9684   if (proc_formal || old_formal)
9685     {
9686       gfc_error ("'%s' at %L must have the same number of formal arguments as"
9687                  " the overridden procedure", proc->name, &where);
9688       return FAILURE;
9689     }
9690
9691   /* If the overridden binding is NOPASS, the overriding one must also be
9692      NOPASS.  */
9693   if (old->n.tb->nopass && !proc->n.tb->nopass)
9694     {
9695       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
9696                  " NOPASS", proc->name, &where);
9697       return FAILURE;
9698     }
9699
9700   /* If the overridden binding is PASS(x), the overriding one must also be
9701      PASS and the passed-object dummy arguments must correspond.  */
9702   if (!old->n.tb->nopass)
9703     {
9704       if (proc->n.tb->nopass)
9705         {
9706           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
9707                      " PASS", proc->name, &where);
9708           return FAILURE;
9709         }
9710
9711       if (proc_pass_arg != old_pass_arg)
9712         {
9713           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
9714                      " the same position as the passed-object dummy argument of"
9715                      " the overridden procedure", proc->name, &where);
9716           return FAILURE;
9717         }
9718     }
9719
9720   return SUCCESS;
9721 }
9722
9723
9724 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
9725
9726 static gfc_try
9727 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
9728                              const char* generic_name, locus where)
9729 {
9730   gfc_symbol* sym1;
9731   gfc_symbol* sym2;
9732
9733   gcc_assert (t1->specific && t2->specific);
9734   gcc_assert (!t1->specific->is_generic);
9735   gcc_assert (!t2->specific->is_generic);
9736
9737   sym1 = t1->specific->u.specific->n.sym;
9738   sym2 = t2->specific->u.specific->n.sym;
9739
9740   if (sym1 == sym2)
9741     return SUCCESS;
9742
9743   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
9744   if (sym1->attr.subroutine != sym2->attr.subroutine
9745       || sym1->attr.function != sym2->attr.function)
9746     {
9747       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
9748                  " GENERIC '%s' at %L",
9749                  sym1->name, sym2->name, generic_name, &where);
9750       return FAILURE;
9751     }
9752
9753   /* Compare the interfaces.  */
9754   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
9755     {
9756       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
9757                  sym1->name, sym2->name, generic_name, &where);
9758       return FAILURE;
9759     }
9760
9761   return SUCCESS;
9762 }
9763
9764
9765 /* Worker function for resolving a generic procedure binding; this is used to
9766    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
9767
9768    The difference between those cases is finding possible inherited bindings
9769    that are overridden, as one has to look for them in tb_sym_root,
9770    tb_uop_root or tb_op, respectively.  Thus the caller must already find
9771    the super-type and set p->overridden correctly.  */
9772
9773 static gfc_try
9774 resolve_tb_generic_targets (gfc_symbol* super_type,
9775                             gfc_typebound_proc* p, const char* name)
9776 {
9777   gfc_tbp_generic* target;
9778   gfc_symtree* first_target;
9779   gfc_symtree* inherited;
9780
9781   gcc_assert (p && p->is_generic);
9782
9783   /* Try to find the specific bindings for the symtrees in our target-list.  */
9784   gcc_assert (p->u.generic);
9785   for (target = p->u.generic; target; target = target->next)
9786     if (!target->specific)
9787       {
9788         gfc_typebound_proc* overridden_tbp;
9789         gfc_tbp_generic* g;
9790         const char* target_name;
9791
9792         target_name = target->specific_st->name;
9793
9794         /* Defined for this type directly.  */
9795         if (target->specific_st->n.tb)
9796           {
9797             target->specific = target->specific_st->n.tb;
9798             goto specific_found;
9799           }
9800
9801         /* Look for an inherited specific binding.  */
9802         if (super_type)
9803           {
9804             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
9805                                                  true, NULL);
9806
9807             if (inherited)
9808               {
9809                 gcc_assert (inherited->n.tb);
9810                 target->specific = inherited->n.tb;
9811                 goto specific_found;
9812               }
9813           }
9814
9815         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
9816                    " at %L", target_name, name, &p->where);
9817         return FAILURE;
9818
9819         /* Once we've found the specific binding, check it is not ambiguous with
9820            other specifics already found or inherited for the same GENERIC.  */
9821 specific_found:
9822         gcc_assert (target->specific);
9823
9824         /* This must really be a specific binding!  */
9825         if (target->specific->is_generic)
9826           {
9827             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
9828                        " '%s' is GENERIC, too", name, &p->where, target_name);
9829             return FAILURE;
9830           }
9831
9832         /* Check those already resolved on this type directly.  */
9833         for (g = p->u.generic; g; g = g->next)
9834           if (g != target && g->specific
9835               && check_generic_tbp_ambiguity (target, g, name, p->where)
9836                   == FAILURE)
9837             return FAILURE;
9838
9839         /* Check for ambiguity with inherited specific targets.  */
9840         for (overridden_tbp = p->overridden; overridden_tbp;
9841              overridden_tbp = overridden_tbp->overridden)
9842           if (overridden_tbp->is_generic)
9843             {
9844               for (g = overridden_tbp->u.generic; g; g = g->next)
9845                 {
9846                   gcc_assert (g->specific);
9847                   if (check_generic_tbp_ambiguity (target, g,
9848                                                    name, p->where) == FAILURE)
9849                     return FAILURE;
9850                 }
9851             }
9852       }
9853
9854   /* If we attempt to "overwrite" a specific binding, this is an error.  */
9855   if (p->overridden && !p->overridden->is_generic)
9856     {
9857       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
9858                  " the same name", name, &p->where);
9859       return FAILURE;
9860     }
9861
9862   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
9863      all must have the same attributes here.  */
9864   first_target = p->u.generic->specific->u.specific;
9865   gcc_assert (first_target);
9866   p->subroutine = first_target->n.sym->attr.subroutine;
9867   p->function = first_target->n.sym->attr.function;
9868
9869   return SUCCESS;
9870 }
9871
9872
9873 /* Resolve a GENERIC procedure binding for a derived type.  */
9874
9875 static gfc_try
9876 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
9877 {
9878   gfc_symbol* super_type;
9879
9880   /* Find the overridden binding if any.  */
9881   st->n.tb->overridden = NULL;
9882   super_type = gfc_get_derived_super_type (derived);
9883   if (super_type)
9884     {
9885       gfc_symtree* overridden;
9886       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
9887                                             true, NULL);
9888
9889       if (overridden && overridden->n.tb)
9890         st->n.tb->overridden = overridden->n.tb;
9891     }
9892
9893   /* Resolve using worker function.  */
9894   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
9895 }
9896
9897
9898 /* Retrieve the target-procedure of an operator binding and do some checks in
9899    common for intrinsic and user-defined type-bound operators.  */
9900
9901 static gfc_symbol*
9902 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
9903 {
9904   gfc_symbol* target_proc;
9905
9906   gcc_assert (target->specific && !target->specific->is_generic);
9907   target_proc = target->specific->u.specific->n.sym;
9908   gcc_assert (target_proc);
9909
9910   /* All operator bindings must have a passed-object dummy argument.  */
9911   if (target->specific->nopass)
9912     {
9913       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
9914       return NULL;
9915     }
9916
9917   return target_proc;
9918 }
9919
9920
9921 /* Resolve a type-bound intrinsic operator.  */
9922
9923 static gfc_try
9924 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
9925                                 gfc_typebound_proc* p)
9926 {
9927   gfc_symbol* super_type;
9928   gfc_tbp_generic* target;
9929   
9930   /* If there's already an error here, do nothing (but don't fail again).  */
9931   if (p->error)
9932     return SUCCESS;
9933
9934   /* Operators should always be GENERIC bindings.  */
9935   gcc_assert (p->is_generic);
9936
9937   /* Look for an overridden binding.  */
9938   super_type = gfc_get_derived_super_type (derived);
9939   if (super_type && super_type->f2k_derived)
9940     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
9941                                                      op, true, NULL);
9942   else
9943     p->overridden = NULL;
9944
9945   /* Resolve general GENERIC properties using worker function.  */
9946   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
9947     goto error;
9948
9949   /* Check the targets to be procedures of correct interface.  */
9950   for (target = p->u.generic; target; target = target->next)
9951     {
9952       gfc_symbol* target_proc;
9953
9954       target_proc = get_checked_tb_operator_target (target, p->where);
9955       if (!target_proc)
9956         goto error;
9957
9958       if (!gfc_check_operator_interface (target_proc, op, p->where))
9959         goto error;
9960     }
9961
9962   return SUCCESS;
9963
9964 error:
9965   p->error = 1;
9966   return FAILURE;
9967 }
9968
9969
9970 /* Resolve a type-bound user operator (tree-walker callback).  */
9971
9972 static gfc_symbol* resolve_bindings_derived;
9973 static gfc_try resolve_bindings_result;
9974
9975 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
9976
9977 static void
9978 resolve_typebound_user_op (gfc_symtree* stree)
9979 {
9980   gfc_symbol* super_type;
9981   gfc_tbp_generic* target;
9982
9983   gcc_assert (stree && stree->n.tb);
9984
9985   if (stree->n.tb->error)
9986     return;
9987
9988   /* Operators should always be GENERIC bindings.  */
9989   gcc_assert (stree->n.tb->is_generic);
9990
9991   /* Find overridden procedure, if any.  */
9992   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
9993   if (super_type && super_type->f2k_derived)
9994     {
9995       gfc_symtree* overridden;
9996       overridden = gfc_find_typebound_user_op (super_type, NULL,
9997                                                stree->name, true, NULL);
9998
9999       if (overridden && overridden->n.tb)
10000         stree->n.tb->overridden = overridden->n.tb;
10001     }
10002   else
10003     stree->n.tb->overridden = NULL;
10004
10005   /* Resolve basically using worker function.  */
10006   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
10007         == FAILURE)
10008     goto error;
10009
10010   /* Check the targets to be functions of correct interface.  */
10011   for (target = stree->n.tb->u.generic; target; target = target->next)
10012     {
10013       gfc_symbol* target_proc;
10014
10015       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
10016       if (!target_proc)
10017         goto error;
10018
10019       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
10020         goto error;
10021     }
10022
10023   return;
10024
10025 error:
10026   resolve_bindings_result = FAILURE;
10027   stree->n.tb->error = 1;
10028 }
10029
10030
10031 /* Resolve the type-bound procedures for a derived type.  */
10032
10033 static void
10034 resolve_typebound_procedure (gfc_symtree* stree)
10035 {
10036   gfc_symbol* proc;
10037   locus where;
10038   gfc_symbol* me_arg;
10039   gfc_symbol* super_type;
10040   gfc_component* comp;
10041
10042   gcc_assert (stree);
10043
10044   /* Undefined specific symbol from GENERIC target definition.  */
10045   if (!stree->n.tb)
10046     return;
10047
10048   if (stree->n.tb->error)
10049     return;
10050
10051   /* If this is a GENERIC binding, use that routine.  */
10052   if (stree->n.tb->is_generic)
10053     {
10054       if (resolve_typebound_generic (resolve_bindings_derived, stree)
10055             == FAILURE)
10056         goto error;
10057       return;
10058     }
10059
10060   /* Get the target-procedure to check it.  */
10061   gcc_assert (!stree->n.tb->is_generic);
10062   gcc_assert (stree->n.tb->u.specific);
10063   proc = stree->n.tb->u.specific->n.sym;
10064   where = stree->n.tb->where;
10065
10066   /* Default access should already be resolved from the parser.  */
10067   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
10068
10069   /* It should be a module procedure or an external procedure with explicit
10070      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
10071   if ((!proc->attr.subroutine && !proc->attr.function)
10072       || (proc->attr.proc != PROC_MODULE
10073           && proc->attr.if_source != IFSRC_IFBODY)
10074       || (proc->attr.abstract && !stree->n.tb->deferred))
10075     {
10076       gfc_error ("'%s' must be a module procedure or an external procedure with"
10077                  " an explicit interface at %L", proc->name, &where);
10078       goto error;
10079     }
10080   stree->n.tb->subroutine = proc->attr.subroutine;
10081   stree->n.tb->function = proc->attr.function;
10082
10083   /* Find the super-type of the current derived type.  We could do this once and
10084      store in a global if speed is needed, but as long as not I believe this is
10085      more readable and clearer.  */
10086   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10087
10088   /* If PASS, resolve and check arguments if not already resolved / loaded
10089      from a .mod file.  */
10090   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
10091     {
10092       if (stree->n.tb->pass_arg)
10093         {
10094           gfc_formal_arglist* i;
10095
10096           /* If an explicit passing argument name is given, walk the arg-list
10097              and look for it.  */
10098
10099           me_arg = NULL;
10100           stree->n.tb->pass_arg_num = 1;
10101           for (i = proc->formal; i; i = i->next)
10102             {
10103               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
10104                 {
10105                   me_arg = i->sym;
10106                   break;
10107                 }
10108               ++stree->n.tb->pass_arg_num;
10109             }
10110
10111           if (!me_arg)
10112             {
10113               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
10114                          " argument '%s'",
10115                          proc->name, stree->n.tb->pass_arg, &where,
10116                          stree->n.tb->pass_arg);
10117               goto error;
10118             }
10119         }
10120       else
10121         {
10122           /* Otherwise, take the first one; there should in fact be at least
10123              one.  */
10124           stree->n.tb->pass_arg_num = 1;
10125           if (!proc->formal)
10126             {
10127               gfc_error ("Procedure '%s' with PASS at %L must have at"
10128                          " least one argument", proc->name, &where);
10129               goto error;
10130             }
10131           me_arg = proc->formal->sym;
10132         }
10133
10134       /* Now check that the argument-type matches and the passed-object
10135          dummy argument is generally fine.  */
10136
10137       gcc_assert (me_arg);
10138
10139       if (me_arg->ts.type != BT_CLASS)
10140         {
10141           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10142                      " at %L", proc->name, &where);
10143           goto error;
10144         }
10145
10146       if (me_arg->ts.u.derived->components->ts.u.derived
10147           != resolve_bindings_derived)
10148         {
10149           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10150                      " the derived-type '%s'", me_arg->name, proc->name,
10151                      me_arg->name, &where, resolve_bindings_derived->name);
10152           goto error;
10153         }
10154   
10155       gcc_assert (me_arg->ts.type == BT_CLASS);
10156       if (me_arg->ts.u.derived->components->as
10157           && me_arg->ts.u.derived->components->as->rank > 0)
10158         {
10159           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
10160                      " scalar", proc->name, &where);
10161           goto error;
10162         }
10163       if (me_arg->ts.u.derived->components->attr.allocatable)
10164         {
10165           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10166                      " be ALLOCATABLE", proc->name, &where);
10167           goto error;
10168         }
10169       if (me_arg->ts.u.derived->components->attr.class_pointer)
10170         {
10171           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10172                      " be POINTER", proc->name, &where);
10173           goto error;
10174         }
10175     }
10176
10177   /* If we are extending some type, check that we don't override a procedure
10178      flagged NON_OVERRIDABLE.  */
10179   stree->n.tb->overridden = NULL;
10180   if (super_type)
10181     {
10182       gfc_symtree* overridden;
10183       overridden = gfc_find_typebound_proc (super_type, NULL,
10184                                             stree->name, true, NULL);
10185
10186       if (overridden && overridden->n.tb)
10187         stree->n.tb->overridden = overridden->n.tb;
10188
10189       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
10190         goto error;
10191     }
10192
10193   /* See if there's a name collision with a component directly in this type.  */
10194   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
10195     if (!strcmp (comp->name, stree->name))
10196       {
10197         gfc_error ("Procedure '%s' at %L has the same name as a component of"
10198                    " '%s'",
10199                    stree->name, &where, resolve_bindings_derived->name);
10200         goto error;
10201       }
10202
10203   /* Try to find a name collision with an inherited component.  */
10204   if (super_type && gfc_find_component (super_type, stree->name, true, true))
10205     {
10206       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
10207                  " component of '%s'",
10208                  stree->name, &where, resolve_bindings_derived->name);
10209       goto error;
10210     }
10211
10212   stree->n.tb->error = 0;
10213   return;
10214
10215 error:
10216   resolve_bindings_result = FAILURE;
10217   stree->n.tb->error = 1;
10218 }
10219
10220 static gfc_try
10221 resolve_typebound_procedures (gfc_symbol* derived)
10222 {
10223   int op;
10224
10225   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
10226     return SUCCESS;
10227
10228   resolve_bindings_derived = derived;
10229   resolve_bindings_result = SUCCESS;
10230
10231   if (derived->f2k_derived->tb_sym_root)
10232     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
10233                           &resolve_typebound_procedure);
10234
10235   if (derived->f2k_derived->tb_uop_root)
10236     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
10237                           &resolve_typebound_user_op);
10238
10239   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
10240     {
10241       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
10242       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
10243                                                p) == FAILURE)
10244         resolve_bindings_result = FAILURE;
10245     }
10246
10247   return resolve_bindings_result;
10248 }
10249
10250
10251 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
10252    to give all identical derived types the same backend_decl.  */
10253 static void
10254 add_dt_to_dt_list (gfc_symbol *derived)
10255 {
10256   gfc_dt_list *dt_list;
10257
10258   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
10259     if (derived == dt_list->derived)
10260       break;
10261
10262   if (dt_list == NULL)
10263     {
10264       dt_list = gfc_get_dt_list ();
10265       dt_list->next = gfc_derived_types;
10266       dt_list->derived = derived;
10267       gfc_derived_types = dt_list;
10268     }
10269 }
10270
10271
10272 /* Ensure that a derived-type is really not abstract, meaning that every
10273    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
10274
10275 static gfc_try
10276 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
10277 {
10278   if (!st)
10279     return SUCCESS;
10280
10281   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
10282     return FAILURE;
10283   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
10284     return FAILURE;
10285
10286   if (st->n.tb && st->n.tb->deferred)
10287     {
10288       gfc_symtree* overriding;
10289       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
10290       gcc_assert (overriding && overriding->n.tb);
10291       if (overriding->n.tb->deferred)
10292         {
10293           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
10294                      " '%s' is DEFERRED and not overridden",
10295                      sub->name, &sub->declared_at, st->name);
10296           return FAILURE;
10297         }
10298     }
10299
10300   return SUCCESS;
10301 }
10302
10303 static gfc_try
10304 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
10305 {
10306   /* The algorithm used here is to recursively travel up the ancestry of sub
10307      and for each ancestor-type, check all bindings.  If any of them is
10308      DEFERRED, look it up starting from sub and see if the found (overriding)
10309      binding is not DEFERRED.
10310      This is not the most efficient way to do this, but it should be ok and is
10311      clearer than something sophisticated.  */
10312
10313   gcc_assert (ancestor && ancestor->attr.abstract && !sub->attr.abstract);
10314
10315   /* Walk bindings of this ancestor.  */
10316   if (ancestor->f2k_derived)
10317     {
10318       gfc_try t;
10319       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
10320       if (t == FAILURE)
10321         return FAILURE;
10322     }
10323
10324   /* Find next ancestor type and recurse on it.  */
10325   ancestor = gfc_get_derived_super_type (ancestor);
10326   if (ancestor)
10327     return ensure_not_abstract (sub, ancestor);
10328
10329   return SUCCESS;
10330 }
10331
10332
10333 static void resolve_symbol (gfc_symbol *sym);
10334
10335
10336 /* Resolve the components of a derived type.  */
10337
10338 static gfc_try
10339 resolve_fl_derived (gfc_symbol *sym)
10340 {
10341   gfc_symbol* super_type;
10342   gfc_component *c;
10343   int i;
10344
10345   super_type = gfc_get_derived_super_type (sym);
10346
10347   /* Ensure the extended type gets resolved before we do.  */
10348   if (super_type && resolve_fl_derived (super_type) == FAILURE)
10349     return FAILURE;
10350
10351   /* An ABSTRACT type must be extensible.  */
10352   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
10353     {
10354       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
10355                  sym->name, &sym->declared_at);
10356       return FAILURE;
10357     }
10358
10359   for (c = sym->components; c != NULL; c = c->next)
10360     {
10361       if (c->attr.proc_pointer && c->ts.interface)
10362         {
10363           if (c->ts.interface->attr.procedure)
10364             gfc_error ("Interface '%s', used by procedure pointer component "
10365                        "'%s' at %L, is declared in a later PROCEDURE statement",
10366                        c->ts.interface->name, c->name, &c->loc);
10367
10368           /* Get the attributes from the interface (now resolved).  */
10369           if (c->ts.interface->attr.if_source
10370               || c->ts.interface->attr.intrinsic)
10371             {
10372               gfc_symbol *ifc = c->ts.interface;
10373
10374               if (ifc->formal && !ifc->formal_ns)
10375                 resolve_symbol (ifc);
10376
10377               if (ifc->attr.intrinsic)
10378                 resolve_intrinsic (ifc, &ifc->declared_at);
10379
10380               if (ifc->result)
10381                 {
10382                   c->ts = ifc->result->ts;
10383                   c->attr.allocatable = ifc->result->attr.allocatable;
10384                   c->attr.pointer = ifc->result->attr.pointer;
10385                   c->attr.dimension = ifc->result->attr.dimension;
10386                   c->as = gfc_copy_array_spec (ifc->result->as);
10387                 }
10388               else
10389                 {   
10390                   c->ts = ifc->ts;
10391                   c->attr.allocatable = ifc->attr.allocatable;
10392                   c->attr.pointer = ifc->attr.pointer;
10393                   c->attr.dimension = ifc->attr.dimension;
10394                   c->as = gfc_copy_array_spec (ifc->as);
10395                 }
10396               c->ts.interface = ifc;
10397               c->attr.function = ifc->attr.function;
10398               c->attr.subroutine = ifc->attr.subroutine;
10399               gfc_copy_formal_args_ppc (c, ifc);
10400
10401               c->attr.pure = ifc->attr.pure;
10402               c->attr.elemental = ifc->attr.elemental;
10403               c->attr.recursive = ifc->attr.recursive;
10404               c->attr.always_explicit = ifc->attr.always_explicit;
10405               c->attr.ext_attr |= ifc->attr.ext_attr;
10406               /* Replace symbols in array spec.  */
10407               if (c->as)
10408                 {
10409                   int i;
10410                   for (i = 0; i < c->as->rank; i++)
10411                     {
10412                       gfc_expr_replace_comp (c->as->lower[i], c);
10413                       gfc_expr_replace_comp (c->as->upper[i], c);
10414                     }
10415                 }
10416               /* Copy char length.  */
10417               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
10418                 {
10419                   c->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
10420                   gfc_expr_replace_comp (c->ts.u.cl->length, c);
10421                 }
10422             }
10423           else if (c->ts.interface->name[0] != '\0')
10424             {
10425               gfc_error ("Interface '%s' of procedure pointer component "
10426                          "'%s' at %L must be explicit", c->ts.interface->name,
10427                          c->name, &c->loc);
10428               return FAILURE;
10429             }
10430         }
10431       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
10432         {
10433           /* Since PPCs are not implicitly typed, a PPC without an explicit
10434              interface must be a subroutine.  */
10435           gfc_add_subroutine (&c->attr, c->name, &c->loc);
10436         }
10437
10438       /* Procedure pointer components: Check PASS arg.  */
10439       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0)
10440         {
10441           gfc_symbol* me_arg;
10442
10443           if (c->tb->pass_arg)
10444             {
10445               gfc_formal_arglist* i;
10446
10447               /* If an explicit passing argument name is given, walk the arg-list
10448                 and look for it.  */
10449
10450               me_arg = NULL;
10451               c->tb->pass_arg_num = 1;
10452               for (i = c->formal; i; i = i->next)
10453                 {
10454                   if (!strcmp (i->sym->name, c->tb->pass_arg))
10455                     {
10456                       me_arg = i->sym;
10457                       break;
10458                     }
10459                   c->tb->pass_arg_num++;
10460                 }
10461
10462               if (!me_arg)
10463                 {
10464                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
10465                              "at %L has no argument '%s'", c->name,
10466                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
10467                   c->tb->error = 1;
10468                   return FAILURE;
10469                 }
10470             }
10471           else
10472             {
10473               /* Otherwise, take the first one; there should in fact be at least
10474                 one.  */
10475               c->tb->pass_arg_num = 1;
10476               if (!c->formal)
10477                 {
10478                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
10479                              "must have at least one argument",
10480                              c->name, &c->loc);
10481                   c->tb->error = 1;
10482                   return FAILURE;
10483                 }
10484               me_arg = c->formal->sym;
10485             }
10486
10487           /* Now check that the argument-type matches.  */
10488           gcc_assert (me_arg);
10489           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
10490               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
10491               || (me_arg->ts.type == BT_CLASS
10492                   && me_arg->ts.u.derived->components->ts.u.derived != sym))
10493             {
10494               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10495                          " the derived type '%s'", me_arg->name, c->name,
10496                          me_arg->name, &c->loc, sym->name);
10497               c->tb->error = 1;
10498               return FAILURE;
10499             }
10500
10501           /* Check for C453.  */
10502           if (me_arg->attr.dimension)
10503             {
10504               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10505                          "must be scalar", me_arg->name, c->name, me_arg->name,
10506                          &c->loc);
10507               c->tb->error = 1;
10508               return FAILURE;
10509             }
10510
10511           if (me_arg->attr.pointer)
10512             {
10513               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10514                          "may not have the POINTER attribute", me_arg->name,
10515                          c->name, me_arg->name, &c->loc);
10516               c->tb->error = 1;
10517               return FAILURE;
10518             }
10519
10520           if (me_arg->attr.allocatable)
10521             {
10522               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10523                          "may not be ALLOCATABLE", me_arg->name, c->name,
10524                          me_arg->name, &c->loc);
10525               c->tb->error = 1;
10526               return FAILURE;
10527             }
10528
10529           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
10530             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10531                        " at %L", c->name, &c->loc);
10532
10533         }
10534
10535       /* Check type-spec if this is not the parent-type component.  */
10536       if ((!sym->attr.extension || c != sym->components)
10537           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
10538         return FAILURE;
10539
10540       /* If this type is an extension, set the accessibility of the parent
10541          component.  */
10542       if (super_type && c == sym->components
10543           && strcmp (super_type->name, c->name) == 0)
10544         c->attr.access = super_type->attr.access;
10545       
10546       /* If this type is an extension, see if this component has the same name
10547          as an inherited type-bound procedure.  */
10548       if (super_type
10549           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
10550         {
10551           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
10552                      " inherited type-bound procedure",
10553                      c->name, sym->name, &c->loc);
10554           return FAILURE;
10555         }
10556
10557       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer)
10558         {
10559          if (c->ts.u.cl->length == NULL
10560              || (resolve_charlen (c->ts.u.cl) == FAILURE)
10561              || !gfc_is_constant_expr (c->ts.u.cl->length))
10562            {
10563              gfc_error ("Character length of component '%s' needs to "
10564                         "be a constant specification expression at %L",
10565                         c->name,
10566                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
10567              return FAILURE;
10568            }
10569         }
10570
10571       if (c->ts.type == BT_DERIVED
10572           && sym->component_access != ACCESS_PRIVATE
10573           && gfc_check_access (sym->attr.access, sym->ns->default_access)
10574           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
10575           && !c->ts.u.derived->attr.use_assoc
10576           && !gfc_check_access (c->ts.u.derived->attr.access,
10577                                 c->ts.u.derived->ns->default_access)
10578           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
10579                              "is a PRIVATE type and cannot be a component of "
10580                              "'%s', which is PUBLIC at %L", c->name,
10581                              sym->name, &sym->declared_at) == FAILURE)
10582         return FAILURE;
10583
10584       if (sym->attr.sequence)
10585         {
10586           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
10587             {
10588               gfc_error ("Component %s of SEQUENCE type declared at %L does "
10589                          "not have the SEQUENCE attribute",
10590                          c->ts.u.derived->name, &sym->declared_at);
10591               return FAILURE;
10592             }
10593         }
10594
10595       if (c->ts.type == BT_DERIVED && c->attr.pointer
10596           && c->ts.u.derived->components == NULL
10597           && !c->ts.u.derived->attr.zero_comp)
10598         {
10599           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
10600                      "that has not been declared", c->name, sym->name,
10601                      &c->loc);
10602           return FAILURE;
10603         }
10604
10605       /* C437.  */
10606       if (c->ts.type == BT_CLASS
10607           && !(c->ts.u.derived->components->attr.pointer
10608                || c->ts.u.derived->components->attr.allocatable))
10609         {
10610           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
10611                      "or pointer", c->name, &c->loc);
10612           return FAILURE;
10613         }
10614
10615       /* Ensure that all the derived type components are put on the
10616          derived type list; even in formal namespaces, where derived type
10617          pointer components might not have been declared.  */
10618       if (c->ts.type == BT_DERIVED
10619             && c->ts.u.derived
10620             && c->ts.u.derived->components
10621             && c->attr.pointer
10622             && sym != c->ts.u.derived)
10623         add_dt_to_dt_list (c->ts.u.derived);
10624
10625       if (c->attr.pointer || c->attr.proc_pointer || c->attr.allocatable
10626           || c->as == NULL)
10627         continue;
10628
10629       for (i = 0; i < c->as->rank; i++)
10630         {
10631           if (c->as->lower[i] == NULL
10632               || (resolve_index_expr (c->as->lower[i]) == FAILURE)
10633               || !gfc_is_constant_expr (c->as->lower[i])
10634               || c->as->upper[i] == NULL
10635               || (resolve_index_expr (c->as->upper[i]) == FAILURE)
10636               || !gfc_is_constant_expr (c->as->upper[i]))
10637             {
10638               gfc_error ("Component '%s' of '%s' at %L must have "
10639                          "constant array bounds",
10640                          c->name, sym->name, &c->loc);
10641               return FAILURE;
10642             }
10643         }
10644     }
10645
10646   /* Resolve the type-bound procedures.  */
10647   if (resolve_typebound_procedures (sym) == FAILURE)
10648     return FAILURE;
10649
10650   /* Resolve the finalizer procedures.  */
10651   if (gfc_resolve_finalizers (sym) == FAILURE)
10652     return FAILURE;
10653
10654   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
10655      all DEFERRED bindings are overridden.  */
10656   if (super_type && super_type->attr.abstract && !sym->attr.abstract
10657       && ensure_not_abstract (sym, super_type) == FAILURE)
10658     return FAILURE;
10659
10660   /* Add derived type to the derived type list.  */
10661   add_dt_to_dt_list (sym);
10662
10663   return SUCCESS;
10664 }
10665
10666
10667 static gfc_try
10668 resolve_fl_namelist (gfc_symbol *sym)
10669 {
10670   gfc_namelist *nl;
10671   gfc_symbol *nlsym;
10672
10673   /* Reject PRIVATE objects in a PUBLIC namelist.  */
10674   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
10675     {
10676       for (nl = sym->namelist; nl; nl = nl->next)
10677         {
10678           if (!nl->sym->attr.use_assoc
10679               && !is_sym_host_assoc (nl->sym, sym->ns)
10680               && !gfc_check_access(nl->sym->attr.access,
10681                                 nl->sym->ns->default_access))
10682             {
10683               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
10684                          "cannot be member of PUBLIC namelist '%s' at %L",
10685                          nl->sym->name, sym->name, &sym->declared_at);
10686               return FAILURE;
10687             }
10688
10689           /* Types with private components that came here by USE-association.  */
10690           if (nl->sym->ts.type == BT_DERIVED
10691               && derived_inaccessible (nl->sym->ts.u.derived))
10692             {
10693               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
10694                          "components and cannot be member of namelist '%s' at %L",
10695                          nl->sym->name, sym->name, &sym->declared_at);
10696               return FAILURE;
10697             }
10698
10699           /* Types with private components that are defined in the same module.  */
10700           if (nl->sym->ts.type == BT_DERIVED
10701               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
10702               && !gfc_check_access (nl->sym->ts.u.derived->attr.private_comp
10703                                         ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
10704                                         nl->sym->ns->default_access))
10705             {
10706               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
10707                          "cannot be a member of PUBLIC namelist '%s' at %L",
10708                          nl->sym->name, sym->name, &sym->declared_at);
10709               return FAILURE;
10710             }
10711         }
10712     }
10713
10714   for (nl = sym->namelist; nl; nl = nl->next)
10715     {
10716       /* Reject namelist arrays of assumed shape.  */
10717       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
10718           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
10719                              "must not have assumed shape in namelist "
10720                              "'%s' at %L", nl->sym->name, sym->name,
10721                              &sym->declared_at) == FAILURE)
10722             return FAILURE;
10723
10724       /* Reject namelist arrays that are not constant shape.  */
10725       if (is_non_constant_shape_array (nl->sym))
10726         {
10727           gfc_error ("NAMELIST array object '%s' must have constant "
10728                      "shape in namelist '%s' at %L", nl->sym->name,
10729                      sym->name, &sym->declared_at);
10730           return FAILURE;
10731         }
10732
10733       /* Namelist objects cannot have allocatable or pointer components.  */
10734       if (nl->sym->ts.type != BT_DERIVED)
10735         continue;
10736
10737       if (nl->sym->ts.u.derived->attr.alloc_comp)
10738         {
10739           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
10740                      "have ALLOCATABLE components",
10741                      nl->sym->name, sym->name, &sym->declared_at);
10742           return FAILURE;
10743         }
10744
10745       if (nl->sym->ts.u.derived->attr.pointer_comp)
10746         {
10747           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
10748                      "have POINTER components", 
10749                      nl->sym->name, sym->name, &sym->declared_at);
10750           return FAILURE;
10751         }
10752     }
10753
10754
10755   /* 14.1.2 A module or internal procedure represent local entities
10756      of the same type as a namelist member and so are not allowed.  */
10757   for (nl = sym->namelist; nl; nl = nl->next)
10758     {
10759       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
10760         continue;
10761
10762       if (nl->sym->attr.function && nl->sym == nl->sym->result)
10763         if ((nl->sym == sym->ns->proc_name)
10764                ||
10765             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
10766           continue;
10767
10768       nlsym = NULL;
10769       if (nl->sym && nl->sym->name)
10770         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
10771       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
10772         {
10773           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
10774                      "attribute in '%s' at %L", nlsym->name,
10775                      &sym->declared_at);
10776           return FAILURE;
10777         }
10778     }
10779
10780   return SUCCESS;
10781 }
10782
10783
10784 static gfc_try
10785 resolve_fl_parameter (gfc_symbol *sym)
10786 {
10787   /* A parameter array's shape needs to be constant.  */
10788   if (sym->as != NULL 
10789       && (sym->as->type == AS_DEFERRED
10790           || is_non_constant_shape_array (sym)))
10791     {
10792       gfc_error ("Parameter array '%s' at %L cannot be automatic "
10793                  "or of deferred shape", sym->name, &sym->declared_at);
10794       return FAILURE;
10795     }
10796
10797   /* Make sure a parameter that has been implicitly typed still
10798      matches the implicit type, since PARAMETER statements can precede
10799      IMPLICIT statements.  */
10800   if (sym->attr.implicit_type
10801       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
10802                                                              sym->ns)))
10803     {
10804       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
10805                  "later IMPLICIT type", sym->name, &sym->declared_at);
10806       return FAILURE;
10807     }
10808
10809   /* Make sure the types of derived parameters are consistent.  This
10810      type checking is deferred until resolution because the type may
10811      refer to a derived type from the host.  */
10812   if (sym->ts.type == BT_DERIVED
10813       && !gfc_compare_types (&sym->ts, &sym->value->ts))
10814     {
10815       gfc_error ("Incompatible derived type in PARAMETER at %L",
10816                  &sym->value->where);
10817       return FAILURE;
10818     }
10819   return SUCCESS;
10820 }
10821
10822
10823 /* Do anything necessary to resolve a symbol.  Right now, we just
10824    assume that an otherwise unknown symbol is a variable.  This sort
10825    of thing commonly happens for symbols in module.  */
10826
10827 static void
10828 resolve_symbol (gfc_symbol *sym)
10829 {
10830   int check_constant, mp_flag;
10831   gfc_symtree *symtree;
10832   gfc_symtree *this_symtree;
10833   gfc_namespace *ns;
10834   gfc_component *c;
10835
10836   if (sym->attr.flavor == FL_UNKNOWN)
10837     {
10838
10839     /* If we find that a flavorless symbol is an interface in one of the
10840        parent namespaces, find its symtree in this namespace, free the
10841        symbol and set the symtree to point to the interface symbol.  */
10842       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
10843         {
10844           symtree = gfc_find_symtree (ns->sym_root, sym->name);
10845           if (symtree && symtree->n.sym->generic)
10846             {
10847               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
10848                                                sym->name);
10849               sym->refs--;
10850               if (!sym->refs)
10851                 gfc_free_symbol (sym);
10852               symtree->n.sym->refs++;
10853               this_symtree->n.sym = symtree->n.sym;
10854               return;
10855             }
10856         }
10857
10858       /* Otherwise give it a flavor according to such attributes as
10859          it has.  */
10860       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
10861         sym->attr.flavor = FL_VARIABLE;
10862       else
10863         {
10864           sym->attr.flavor = FL_PROCEDURE;
10865           if (sym->attr.dimension)
10866             sym->attr.function = 1;
10867         }
10868     }
10869
10870   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
10871     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
10872
10873   if (sym->attr.procedure && sym->ts.interface
10874       && sym->attr.if_source != IFSRC_DECL)
10875     {
10876       if (sym->ts.interface == sym)
10877         {
10878           gfc_error ("PROCEDURE '%s' at %L may not be used as its own "
10879                      "interface", sym->name, &sym->declared_at);
10880           return;
10881         }
10882       if (sym->ts.interface->attr.procedure)
10883         {
10884           gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared"
10885                      " in a later PROCEDURE statement", sym->ts.interface->name,
10886                      sym->name,&sym->declared_at);
10887           return;
10888         }
10889
10890       /* Get the attributes from the interface (now resolved).  */
10891       if (sym->ts.interface->attr.if_source
10892           || sym->ts.interface->attr.intrinsic)
10893         {
10894           gfc_symbol *ifc = sym->ts.interface;
10895           resolve_symbol (ifc);
10896
10897           if (ifc->attr.intrinsic)
10898             resolve_intrinsic (ifc, &ifc->declared_at);
10899
10900           if (ifc->result)
10901             sym->ts = ifc->result->ts;
10902           else   
10903             sym->ts = ifc->ts;
10904           sym->ts.interface = ifc;
10905           sym->attr.function = ifc->attr.function;
10906           sym->attr.subroutine = ifc->attr.subroutine;
10907           gfc_copy_formal_args (sym, ifc);
10908
10909           sym->attr.allocatable = ifc->attr.allocatable;
10910           sym->attr.pointer = ifc->attr.pointer;
10911           sym->attr.pure = ifc->attr.pure;
10912           sym->attr.elemental = ifc->attr.elemental;
10913           sym->attr.dimension = ifc->attr.dimension;
10914           sym->attr.recursive = ifc->attr.recursive;
10915           sym->attr.always_explicit = ifc->attr.always_explicit;
10916           sym->attr.ext_attr |= ifc->attr.ext_attr;
10917           /* Copy array spec.  */
10918           sym->as = gfc_copy_array_spec (ifc->as);
10919           if (sym->as)
10920             {
10921               int i;
10922               for (i = 0; i < sym->as->rank; i++)
10923                 {
10924                   gfc_expr_replace_symbols (sym->as->lower[i], sym);
10925                   gfc_expr_replace_symbols (sym->as->upper[i], sym);
10926                 }
10927             }
10928           /* Copy char length.  */
10929           if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
10930             {
10931               sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
10932               gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
10933             }
10934         }
10935       else if (sym->ts.interface->name[0] != '\0')
10936         {
10937           gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
10938                     sym->ts.interface->name, sym->name, &sym->declared_at);
10939           return;
10940         }
10941     }
10942
10943   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
10944     return;
10945
10946   /* Symbols that are module procedures with results (functions) have
10947      the types and array specification copied for type checking in
10948      procedures that call them, as well as for saving to a module
10949      file.  These symbols can't stand the scrutiny that their results
10950      can.  */
10951   mp_flag = (sym->result != NULL && sym->result != sym);
10952
10953
10954   /* Make sure that the intrinsic is consistent with its internal 
10955      representation. This needs to be done before assigning a default 
10956      type to avoid spurious warnings.  */
10957   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
10958       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
10959     return;
10960
10961   /* Assign default type to symbols that need one and don't have one.  */
10962   if (sym->ts.type == BT_UNKNOWN)
10963     {
10964       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
10965         gfc_set_default_type (sym, 1, NULL);
10966
10967       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
10968           && !sym->attr.function && !sym->attr.subroutine
10969           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
10970         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
10971
10972       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
10973         {
10974           /* The specific case of an external procedure should emit an error
10975              in the case that there is no implicit type.  */
10976           if (!mp_flag)
10977             gfc_set_default_type (sym, sym->attr.external, NULL);
10978           else
10979             {
10980               /* Result may be in another namespace.  */
10981               resolve_symbol (sym->result);
10982
10983               if (!sym->result->attr.proc_pointer)
10984                 {
10985                   sym->ts = sym->result->ts;
10986                   sym->as = gfc_copy_array_spec (sym->result->as);
10987                   sym->attr.dimension = sym->result->attr.dimension;
10988                   sym->attr.pointer = sym->result->attr.pointer;
10989                   sym->attr.allocatable = sym->result->attr.allocatable;
10990                 }
10991             }
10992         }
10993     }
10994
10995   /* Assumed size arrays and assumed shape arrays must be dummy
10996      arguments.  */
10997
10998   if (sym->as != NULL
10999       && (sym->as->type == AS_ASSUMED_SIZE
11000           || sym->as->type == AS_ASSUMED_SHAPE)
11001       && sym->attr.dummy == 0)
11002     {
11003       if (sym->as->type == AS_ASSUMED_SIZE)
11004         gfc_error ("Assumed size array at %L must be a dummy argument",
11005                    &sym->declared_at);
11006       else
11007         gfc_error ("Assumed shape array at %L must be a dummy argument",
11008                    &sym->declared_at);
11009       return;
11010     }
11011
11012   /* Make sure symbols with known intent or optional are really dummy
11013      variable.  Because of ENTRY statement, this has to be deferred
11014      until resolution time.  */
11015
11016   if (!sym->attr.dummy
11017       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
11018     {
11019       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
11020       return;
11021     }
11022
11023   if (sym->attr.value && !sym->attr.dummy)
11024     {
11025       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
11026                  "it is not a dummy argument", sym->name, &sym->declared_at);
11027       return;
11028     }
11029
11030   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
11031     {
11032       gfc_charlen *cl = sym->ts.u.cl;
11033       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
11034         {
11035           gfc_error ("Character dummy variable '%s' at %L with VALUE "
11036                      "attribute must have constant length",
11037                      sym->name, &sym->declared_at);
11038           return;
11039         }
11040
11041       if (sym->ts.is_c_interop
11042           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
11043         {
11044           gfc_error ("C interoperable character dummy variable '%s' at %L "
11045                      "with VALUE attribute must have length one",
11046                      sym->name, &sym->declared_at);
11047           return;
11048         }
11049     }
11050
11051   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
11052      do this for something that was implicitly typed because that is handled
11053      in gfc_set_default_type.  Handle dummy arguments and procedure
11054      definitions separately.  Also, anything that is use associated is not
11055      handled here but instead is handled in the module it is declared in.
11056      Finally, derived type definitions are allowed to be BIND(C) since that
11057      only implies that they're interoperable, and they are checked fully for
11058      interoperability when a variable is declared of that type.  */
11059   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
11060       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
11061       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
11062     {
11063       gfc_try t = SUCCESS;
11064       
11065       /* First, make sure the variable is declared at the
11066          module-level scope (J3/04-007, Section 15.3).  */
11067       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
11068           sym->attr.in_common == 0)
11069         {
11070           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
11071                      "is neither a COMMON block nor declared at the "
11072                      "module level scope", sym->name, &(sym->declared_at));
11073           t = FAILURE;
11074         }
11075       else if (sym->common_head != NULL)
11076         {
11077           t = verify_com_block_vars_c_interop (sym->common_head);
11078         }
11079       else
11080         {
11081           /* If type() declaration, we need to verify that the components
11082              of the given type are all C interoperable, etc.  */
11083           if (sym->ts.type == BT_DERIVED &&
11084               sym->ts.u.derived->attr.is_c_interop != 1)
11085             {
11086               /* Make sure the user marked the derived type as BIND(C).  If
11087                  not, call the verify routine.  This could print an error
11088                  for the derived type more than once if multiple variables
11089                  of that type are declared.  */
11090               if (sym->ts.u.derived->attr.is_bind_c != 1)
11091                 verify_bind_c_derived_type (sym->ts.u.derived);
11092               t = FAILURE;
11093             }
11094           
11095           /* Verify the variable itself as C interoperable if it
11096              is BIND(C).  It is not possible for this to succeed if
11097              the verify_bind_c_derived_type failed, so don't have to handle
11098              any error returned by verify_bind_c_derived_type.  */
11099           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
11100                                  sym->common_block);
11101         }
11102
11103       if (t == FAILURE)
11104         {
11105           /* clear the is_bind_c flag to prevent reporting errors more than
11106              once if something failed.  */
11107           sym->attr.is_bind_c = 0;
11108           return;
11109         }
11110     }
11111
11112   /* If a derived type symbol has reached this point, without its
11113      type being declared, we have an error.  Notice that most
11114      conditions that produce undefined derived types have already
11115      been dealt with.  However, the likes of:
11116      implicit type(t) (t) ..... call foo (t) will get us here if
11117      the type is not declared in the scope of the implicit
11118      statement. Change the type to BT_UNKNOWN, both because it is so
11119      and to prevent an ICE.  */
11120   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
11121       && !sym->ts.u.derived->attr.zero_comp)
11122     {
11123       gfc_error ("The derived type '%s' at %L is of type '%s', "
11124                  "which has not been defined", sym->name,
11125                   &sym->declared_at, sym->ts.u.derived->name);
11126       sym->ts.type = BT_UNKNOWN;
11127       return;
11128     }
11129
11130   /* Make sure that the derived type has been resolved and that the
11131      derived type is visible in the symbol's namespace, if it is a
11132      module function and is not PRIVATE.  */
11133   if (sym->ts.type == BT_DERIVED
11134         && sym->ts.u.derived->attr.use_assoc
11135         && sym->ns->proc_name
11136         && sym->ns->proc_name->attr.flavor == FL_MODULE)
11137     {
11138       gfc_symbol *ds;
11139
11140       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
11141         return;
11142
11143       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
11144       if (!ds && sym->attr.function
11145             && gfc_check_access (sym->attr.access, sym->ns->default_access))
11146         {
11147           symtree = gfc_new_symtree (&sym->ns->sym_root,
11148                                      sym->ts.u.derived->name);
11149           symtree->n.sym = sym->ts.u.derived;
11150           sym->ts.u.derived->refs++;
11151         }
11152     }
11153
11154   /* Unless the derived-type declaration is use associated, Fortran 95
11155      does not allow public entries of private derived types.
11156      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
11157      161 in 95-006r3.  */
11158   if (sym->ts.type == BT_DERIVED
11159       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
11160       && !sym->ts.u.derived->attr.use_assoc
11161       && gfc_check_access (sym->attr.access, sym->ns->default_access)
11162       && !gfc_check_access (sym->ts.u.derived->attr.access,
11163                             sym->ts.u.derived->ns->default_access)
11164       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
11165                          "of PRIVATE derived type '%s'",
11166                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
11167                          : "variable", sym->name, &sym->declared_at,
11168                          sym->ts.u.derived->name) == FAILURE)
11169     return;
11170
11171   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
11172      default initialization is defined (5.1.2.4.4).  */
11173   if (sym->ts.type == BT_DERIVED
11174       && sym->attr.dummy
11175       && sym->attr.intent == INTENT_OUT
11176       && sym->as
11177       && sym->as->type == AS_ASSUMED_SIZE)
11178     {
11179       for (c = sym->ts.u.derived->components; c; c = c->next)
11180         {
11181           if (c->initializer)
11182             {
11183               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
11184                          "ASSUMED SIZE and so cannot have a default initializer",
11185                          sym->name, &sym->declared_at);
11186               return;
11187             }
11188         }
11189     }
11190
11191   switch (sym->attr.flavor)
11192     {
11193     case FL_VARIABLE:
11194       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
11195         return;
11196       break;
11197
11198     case FL_PROCEDURE:
11199       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
11200         return;
11201       break;
11202
11203     case FL_NAMELIST:
11204       if (resolve_fl_namelist (sym) == FAILURE)
11205         return;
11206       break;
11207
11208     case FL_PARAMETER:
11209       if (resolve_fl_parameter (sym) == FAILURE)
11210         return;
11211       break;
11212
11213     default:
11214       break;
11215     }
11216
11217   /* Resolve array specifier. Check as well some constraints
11218      on COMMON blocks.  */
11219
11220   check_constant = sym->attr.in_common && !sym->attr.pointer;
11221
11222   /* Set the formal_arg_flag so that check_conflict will not throw
11223      an error for host associated variables in the specification
11224      expression for an array_valued function.  */
11225   if (sym->attr.function && sym->as)
11226     formal_arg_flag = 1;
11227
11228   gfc_resolve_array_spec (sym->as, check_constant);
11229
11230   formal_arg_flag = 0;
11231
11232   /* Resolve formal namespaces.  */
11233   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
11234       && !sym->attr.contained && !sym->attr.intrinsic)
11235     gfc_resolve (sym->formal_ns);
11236
11237   /* Make sure the formal namespace is present.  */
11238   if (sym->formal && !sym->formal_ns)
11239     {
11240       gfc_formal_arglist *formal = sym->formal;
11241       while (formal && !formal->sym)
11242         formal = formal->next;
11243
11244       if (formal)
11245         {
11246           sym->formal_ns = formal->sym->ns;
11247           sym->formal_ns->refs++;
11248         }
11249     }
11250
11251   /* Check threadprivate restrictions.  */
11252   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
11253       && (!sym->attr.in_common
11254           && sym->module == NULL
11255           && (sym->ns->proc_name == NULL
11256               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
11257     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
11258
11259   /* If we have come this far we can apply default-initializers, as
11260      described in 14.7.5, to those variables that have not already
11261      been assigned one.  */
11262   if (sym->ts.type == BT_DERIVED
11263       && sym->attr.referenced
11264       && sym->ns == gfc_current_ns
11265       && !sym->value
11266       && !sym->attr.allocatable
11267       && !sym->attr.alloc_comp)
11268     {
11269       symbol_attribute *a = &sym->attr;
11270
11271       if ((!a->save && !a->dummy && !a->pointer
11272            && !a->in_common && !a->use_assoc
11273            && !(a->function && sym != sym->result))
11274           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
11275         apply_default_init (sym);
11276     }
11277
11278   /* If this symbol has a type-spec, check it.  */
11279   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
11280       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
11281     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
11282           == FAILURE)
11283       return;
11284 }
11285
11286
11287 /************* Resolve DATA statements *************/
11288
11289 static struct
11290 {
11291   gfc_data_value *vnode;
11292   mpz_t left;
11293 }
11294 values;
11295
11296
11297 /* Advance the values structure to point to the next value in the data list.  */
11298
11299 static gfc_try
11300 next_data_value (void)
11301 {
11302   while (mpz_cmp_ui (values.left, 0) == 0)
11303     {
11304
11305       if (values.vnode->next == NULL)
11306         return FAILURE;
11307
11308       values.vnode = values.vnode->next;
11309       mpz_set (values.left, values.vnode->repeat);
11310     }
11311
11312   return SUCCESS;
11313 }
11314
11315
11316 static gfc_try
11317 check_data_variable (gfc_data_variable *var, locus *where)
11318 {
11319   gfc_expr *e;
11320   mpz_t size;
11321   mpz_t offset;
11322   gfc_try t;
11323   ar_type mark = AR_UNKNOWN;
11324   int i;
11325   mpz_t section_index[GFC_MAX_DIMENSIONS];
11326   gfc_ref *ref;
11327   gfc_array_ref *ar;
11328   gfc_symbol *sym;
11329   int has_pointer;
11330
11331   if (gfc_resolve_expr (var->expr) == FAILURE)
11332     return FAILURE;
11333
11334   ar = NULL;
11335   mpz_init_set_si (offset, 0);
11336   e = var->expr;
11337
11338   if (e->expr_type != EXPR_VARIABLE)
11339     gfc_internal_error ("check_data_variable(): Bad expression");
11340
11341   sym = e->symtree->n.sym;
11342
11343   if (sym->ns->is_block_data && !sym->attr.in_common)
11344     {
11345       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
11346                  sym->name, &sym->declared_at);
11347     }
11348
11349   if (e->ref == NULL && sym->as)
11350     {
11351       gfc_error ("DATA array '%s' at %L must be specified in a previous"
11352                  " declaration", sym->name, where);
11353       return FAILURE;
11354     }
11355
11356   has_pointer = sym->attr.pointer;
11357
11358   for (ref = e->ref; ref; ref = ref->next)
11359     {
11360       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
11361         has_pointer = 1;
11362
11363       if (has_pointer
11364             && ref->type == REF_ARRAY
11365             && ref->u.ar.type != AR_FULL)
11366           {
11367             gfc_error ("DATA element '%s' at %L is a pointer and so must "
11368                         "be a full array", sym->name, where);
11369             return FAILURE;
11370           }
11371     }
11372
11373   if (e->rank == 0 || has_pointer)
11374     {
11375       mpz_init_set_ui (size, 1);
11376       ref = NULL;
11377     }
11378   else
11379     {
11380       ref = e->ref;
11381
11382       /* Find the array section reference.  */
11383       for (ref = e->ref; ref; ref = ref->next)
11384         {
11385           if (ref->type != REF_ARRAY)
11386             continue;
11387           if (ref->u.ar.type == AR_ELEMENT)
11388             continue;
11389           break;
11390         }
11391       gcc_assert (ref);
11392
11393       /* Set marks according to the reference pattern.  */
11394       switch (ref->u.ar.type)
11395         {
11396         case AR_FULL:
11397           mark = AR_FULL;
11398           break;
11399
11400         case AR_SECTION:
11401           ar = &ref->u.ar;
11402           /* Get the start position of array section.  */
11403           gfc_get_section_index (ar, section_index, &offset);
11404           mark = AR_SECTION;
11405           break;
11406
11407         default:
11408           gcc_unreachable ();
11409         }
11410
11411       if (gfc_array_size (e, &size) == FAILURE)
11412         {
11413           gfc_error ("Nonconstant array section at %L in DATA statement",
11414                      &e->where);
11415           mpz_clear (offset);
11416           return FAILURE;
11417         }
11418     }
11419
11420   t = SUCCESS;
11421
11422   while (mpz_cmp_ui (size, 0) > 0)
11423     {
11424       if (next_data_value () == FAILURE)
11425         {
11426           gfc_error ("DATA statement at %L has more variables than values",
11427                      where);
11428           t = FAILURE;
11429           break;
11430         }
11431
11432       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
11433       if (t == FAILURE)
11434         break;
11435
11436       /* If we have more than one element left in the repeat count,
11437          and we have more than one element left in the target variable,
11438          then create a range assignment.  */
11439       /* FIXME: Only done for full arrays for now, since array sections
11440          seem tricky.  */
11441       if (mark == AR_FULL && ref && ref->next == NULL
11442           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
11443         {
11444           mpz_t range;
11445
11446           if (mpz_cmp (size, values.left) >= 0)
11447             {
11448               mpz_init_set (range, values.left);
11449               mpz_sub (size, size, values.left);
11450               mpz_set_ui (values.left, 0);
11451             }
11452           else
11453             {
11454               mpz_init_set (range, size);
11455               mpz_sub (values.left, values.left, size);
11456               mpz_set_ui (size, 0);
11457             }
11458
11459           gfc_assign_data_value_range (var->expr, values.vnode->expr,
11460                                        offset, range);
11461
11462           mpz_add (offset, offset, range);
11463           mpz_clear (range);
11464         }
11465
11466       /* Assign initial value to symbol.  */
11467       else
11468         {
11469           mpz_sub_ui (values.left, values.left, 1);
11470           mpz_sub_ui (size, size, 1);
11471
11472           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
11473           if (t == FAILURE)
11474             break;
11475
11476           if (mark == AR_FULL)
11477             mpz_add_ui (offset, offset, 1);
11478
11479           /* Modify the array section indexes and recalculate the offset
11480              for next element.  */
11481           else if (mark == AR_SECTION)
11482             gfc_advance_section (section_index, ar, &offset);
11483         }
11484     }
11485
11486   if (mark == AR_SECTION)
11487     {
11488       for (i = 0; i < ar->dimen; i++)
11489         mpz_clear (section_index[i]);
11490     }
11491
11492   mpz_clear (size);
11493   mpz_clear (offset);
11494
11495   return t;
11496 }
11497
11498
11499 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
11500
11501 /* Iterate over a list of elements in a DATA statement.  */
11502
11503 static gfc_try
11504 traverse_data_list (gfc_data_variable *var, locus *where)
11505 {
11506   mpz_t trip;
11507   iterator_stack frame;
11508   gfc_expr *e, *start, *end, *step;
11509   gfc_try retval = SUCCESS;
11510
11511   mpz_init (frame.value);
11512
11513   start = gfc_copy_expr (var->iter.start);
11514   end = gfc_copy_expr (var->iter.end);
11515   step = gfc_copy_expr (var->iter.step);
11516
11517   if (gfc_simplify_expr (start, 1) == FAILURE
11518       || start->expr_type != EXPR_CONSTANT)
11519     {
11520       gfc_error ("iterator start at %L does not simplify", &start->where);
11521       retval = FAILURE;
11522       goto cleanup;
11523     }
11524   if (gfc_simplify_expr (end, 1) == FAILURE
11525       || end->expr_type != EXPR_CONSTANT)
11526     {
11527       gfc_error ("iterator end at %L does not simplify", &end->where);
11528       retval = FAILURE;
11529       goto cleanup;
11530     }
11531   if (gfc_simplify_expr (step, 1) == FAILURE
11532       || step->expr_type != EXPR_CONSTANT)
11533     {
11534       gfc_error ("iterator step at %L does not simplify", &step->where);
11535       retval = FAILURE;
11536       goto cleanup;
11537     }
11538
11539   mpz_init_set (trip, end->value.integer);
11540   mpz_sub (trip, trip, start->value.integer);
11541   mpz_add (trip, trip, step->value.integer);
11542
11543   mpz_div (trip, trip, step->value.integer);
11544
11545   mpz_set (frame.value, start->value.integer);
11546
11547   frame.prev = iter_stack;
11548   frame.variable = var->iter.var->symtree;
11549   iter_stack = &frame;
11550
11551   while (mpz_cmp_ui (trip, 0) > 0)
11552     {
11553       if (traverse_data_var (var->list, where) == FAILURE)
11554         {
11555           mpz_clear (trip);
11556           retval = FAILURE;
11557           goto cleanup;
11558         }
11559
11560       e = gfc_copy_expr (var->expr);
11561       if (gfc_simplify_expr (e, 1) == FAILURE)
11562         {
11563           gfc_free_expr (e);
11564           mpz_clear (trip);
11565           retval = FAILURE;
11566           goto cleanup;
11567         }
11568
11569       mpz_add (frame.value, frame.value, step->value.integer);
11570
11571       mpz_sub_ui (trip, trip, 1);
11572     }
11573
11574   mpz_clear (trip);
11575 cleanup:
11576   mpz_clear (frame.value);
11577
11578   gfc_free_expr (start);
11579   gfc_free_expr (end);
11580   gfc_free_expr (step);
11581
11582   iter_stack = frame.prev;
11583   return retval;
11584 }
11585
11586
11587 /* Type resolve variables in the variable list of a DATA statement.  */
11588
11589 static gfc_try
11590 traverse_data_var (gfc_data_variable *var, locus *where)
11591 {
11592   gfc_try t;
11593
11594   for (; var; var = var->next)
11595     {
11596       if (var->expr == NULL)
11597         t = traverse_data_list (var, where);
11598       else
11599         t = check_data_variable (var, where);
11600
11601       if (t == FAILURE)
11602         return FAILURE;
11603     }
11604
11605   return SUCCESS;
11606 }
11607
11608
11609 /* Resolve the expressions and iterators associated with a data statement.
11610    This is separate from the assignment checking because data lists should
11611    only be resolved once.  */
11612
11613 static gfc_try
11614 resolve_data_variables (gfc_data_variable *d)
11615 {
11616   for (; d; d = d->next)
11617     {
11618       if (d->list == NULL)
11619         {
11620           if (gfc_resolve_expr (d->expr) == FAILURE)
11621             return FAILURE;
11622         }
11623       else
11624         {
11625           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
11626             return FAILURE;
11627
11628           if (resolve_data_variables (d->list) == FAILURE)
11629             return FAILURE;
11630         }
11631     }
11632
11633   return SUCCESS;
11634 }
11635
11636
11637 /* Resolve a single DATA statement.  We implement this by storing a pointer to
11638    the value list into static variables, and then recursively traversing the
11639    variables list, expanding iterators and such.  */
11640
11641 static void
11642 resolve_data (gfc_data *d)
11643 {
11644
11645   if (resolve_data_variables (d->var) == FAILURE)
11646     return;
11647
11648   values.vnode = d->value;
11649   if (d->value == NULL)
11650     mpz_set_ui (values.left, 0);
11651   else
11652     mpz_set (values.left, d->value->repeat);
11653
11654   if (traverse_data_var (d->var, &d->where) == FAILURE)
11655     return;
11656
11657   /* At this point, we better not have any values left.  */
11658
11659   if (next_data_value () == SUCCESS)
11660     gfc_error ("DATA statement at %L has more values than variables",
11661                &d->where);
11662 }
11663
11664
11665 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
11666    accessed by host or use association, is a dummy argument to a pure function,
11667    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
11668    is storage associated with any such variable, shall not be used in the
11669    following contexts: (clients of this function).  */
11670
11671 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
11672    procedure.  Returns zero if assignment is OK, nonzero if there is a
11673    problem.  */
11674 int
11675 gfc_impure_variable (gfc_symbol *sym)
11676 {
11677   gfc_symbol *proc;
11678   gfc_namespace *ns;
11679
11680   if (sym->attr.use_assoc || sym->attr.in_common)
11681     return 1;
11682
11683   /* Check if the symbol's ns is inside the pure procedure.  */
11684   for (ns = gfc_current_ns; ns; ns = ns->parent)
11685     {
11686       if (ns == sym->ns)
11687         break;
11688       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
11689         return 1;
11690     }
11691
11692   proc = sym->ns->proc_name;
11693   if (sym->attr.dummy && gfc_pure (proc)
11694         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
11695                 ||
11696              proc->attr.function))
11697     return 1;
11698
11699   /* TODO: Sort out what can be storage associated, if anything, and include
11700      it here.  In principle equivalences should be scanned but it does not
11701      seem to be possible to storage associate an impure variable this way.  */
11702   return 0;
11703 }
11704
11705
11706 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
11707    current namespace is inside a pure procedure.  */
11708
11709 int
11710 gfc_pure (gfc_symbol *sym)
11711 {
11712   symbol_attribute attr;
11713   gfc_namespace *ns;
11714
11715   if (sym == NULL)
11716     {
11717       /* Check if the current namespace or one of its parents
11718         belongs to a pure procedure.  */
11719       for (ns = gfc_current_ns; ns; ns = ns->parent)
11720         {
11721           sym = ns->proc_name;
11722           if (sym == NULL)
11723             return 0;
11724           attr = sym->attr;
11725           if (attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental))
11726             return 1;
11727         }
11728       return 0;
11729     }
11730
11731   attr = sym->attr;
11732
11733   return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
11734 }
11735
11736
11737 /* Test whether the current procedure is elemental or not.  */
11738
11739 int
11740 gfc_elemental (gfc_symbol *sym)
11741 {
11742   symbol_attribute attr;
11743
11744   if (sym == NULL)
11745     sym = gfc_current_ns->proc_name;
11746   if (sym == NULL)
11747     return 0;
11748   attr = sym->attr;
11749
11750   return attr.flavor == FL_PROCEDURE && attr.elemental;
11751 }
11752
11753
11754 /* Warn about unused labels.  */
11755
11756 static void
11757 warn_unused_fortran_label (gfc_st_label *label)
11758 {
11759   if (label == NULL)
11760     return;
11761
11762   warn_unused_fortran_label (label->left);
11763
11764   if (label->defined == ST_LABEL_UNKNOWN)
11765     return;
11766
11767   switch (label->referenced)
11768     {
11769     case ST_LABEL_UNKNOWN:
11770       gfc_warning ("Label %d at %L defined but not used", label->value,
11771                    &label->where);
11772       break;
11773
11774     case ST_LABEL_BAD_TARGET:
11775       gfc_warning ("Label %d at %L defined but cannot be used",
11776                    label->value, &label->where);
11777       break;
11778
11779     default:
11780       break;
11781     }
11782
11783   warn_unused_fortran_label (label->right);
11784 }
11785
11786
11787 /* Returns the sequence type of a symbol or sequence.  */
11788
11789 static seq_type
11790 sequence_type (gfc_typespec ts)
11791 {
11792   seq_type result;
11793   gfc_component *c;
11794
11795   switch (ts.type)
11796   {
11797     case BT_DERIVED:
11798
11799       if (ts.u.derived->components == NULL)
11800         return SEQ_NONDEFAULT;
11801
11802       result = sequence_type (ts.u.derived->components->ts);
11803       for (c = ts.u.derived->components->next; c; c = c->next)
11804         if (sequence_type (c->ts) != result)
11805           return SEQ_MIXED;
11806
11807       return result;
11808
11809     case BT_CHARACTER:
11810       if (ts.kind != gfc_default_character_kind)
11811           return SEQ_NONDEFAULT;
11812
11813       return SEQ_CHARACTER;
11814
11815     case BT_INTEGER:
11816       if (ts.kind != gfc_default_integer_kind)
11817           return SEQ_NONDEFAULT;
11818
11819       return SEQ_NUMERIC;
11820
11821     case BT_REAL:
11822       if (!(ts.kind == gfc_default_real_kind
11823             || ts.kind == gfc_default_double_kind))
11824           return SEQ_NONDEFAULT;
11825
11826       return SEQ_NUMERIC;
11827
11828     case BT_COMPLEX:
11829       if (ts.kind != gfc_default_complex_kind)
11830           return SEQ_NONDEFAULT;
11831
11832       return SEQ_NUMERIC;
11833
11834     case BT_LOGICAL:
11835       if (ts.kind != gfc_default_logical_kind)
11836           return SEQ_NONDEFAULT;
11837
11838       return SEQ_NUMERIC;
11839
11840     default:
11841       return SEQ_NONDEFAULT;
11842   }
11843 }
11844
11845
11846 /* Resolve derived type EQUIVALENCE object.  */
11847
11848 static gfc_try
11849 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
11850 {
11851   gfc_component *c = derived->components;
11852
11853   if (!derived)
11854     return SUCCESS;
11855
11856   /* Shall not be an object of nonsequence derived type.  */
11857   if (!derived->attr.sequence)
11858     {
11859       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
11860                  "attribute to be an EQUIVALENCE object", sym->name,
11861                  &e->where);
11862       return FAILURE;
11863     }
11864
11865   /* Shall not have allocatable components.  */
11866   if (derived->attr.alloc_comp)
11867     {
11868       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
11869                  "components to be an EQUIVALENCE object",sym->name,
11870                  &e->where);
11871       return FAILURE;
11872     }
11873
11874   if (sym->attr.in_common && has_default_initializer (sym->ts.u.derived))
11875     {
11876       gfc_error ("Derived type variable '%s' at %L with default "
11877                  "initialization cannot be in EQUIVALENCE with a variable "
11878                  "in COMMON", sym->name, &e->where);
11879       return FAILURE;
11880     }
11881
11882   for (; c ; c = c->next)
11883     {
11884       if (c->ts.type == BT_DERIVED
11885           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
11886         return FAILURE;
11887
11888       /* Shall not be an object of sequence derived type containing a pointer
11889          in the structure.  */
11890       if (c->attr.pointer)
11891         {
11892           gfc_error ("Derived type variable '%s' at %L with pointer "
11893                      "component(s) cannot be an EQUIVALENCE object",
11894                      sym->name, &e->where);
11895           return FAILURE;
11896         }
11897     }
11898   return SUCCESS;
11899 }
11900
11901
11902 /* Resolve equivalence object. 
11903    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
11904    an allocatable array, an object of nonsequence derived type, an object of
11905    sequence derived type containing a pointer at any level of component
11906    selection, an automatic object, a function name, an entry name, a result
11907    name, a named constant, a structure component, or a subobject of any of
11908    the preceding objects.  A substring shall not have length zero.  A
11909    derived type shall not have components with default initialization nor
11910    shall two objects of an equivalence group be initialized.
11911    Either all or none of the objects shall have an protected attribute.
11912    The simple constraints are done in symbol.c(check_conflict) and the rest
11913    are implemented here.  */
11914
11915 static void
11916 resolve_equivalence (gfc_equiv *eq)
11917 {
11918   gfc_symbol *sym;
11919   gfc_symbol *first_sym;
11920   gfc_expr *e;
11921   gfc_ref *r;
11922   locus *last_where = NULL;
11923   seq_type eq_type, last_eq_type;
11924   gfc_typespec *last_ts;
11925   int object, cnt_protected;
11926   const char *msg;
11927
11928   last_ts = &eq->expr->symtree->n.sym->ts;
11929
11930   first_sym = eq->expr->symtree->n.sym;
11931
11932   cnt_protected = 0;
11933
11934   for (object = 1; eq; eq = eq->eq, object++)
11935     {
11936       e = eq->expr;
11937
11938       e->ts = e->symtree->n.sym->ts;
11939       /* match_varspec might not know yet if it is seeing
11940          array reference or substring reference, as it doesn't
11941          know the types.  */
11942       if (e->ref && e->ref->type == REF_ARRAY)
11943         {
11944           gfc_ref *ref = e->ref;
11945           sym = e->symtree->n.sym;
11946
11947           if (sym->attr.dimension)
11948             {
11949               ref->u.ar.as = sym->as;
11950               ref = ref->next;
11951             }
11952
11953           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
11954           if (e->ts.type == BT_CHARACTER
11955               && ref
11956               && ref->type == REF_ARRAY
11957               && ref->u.ar.dimen == 1
11958               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
11959               && ref->u.ar.stride[0] == NULL)
11960             {
11961               gfc_expr *start = ref->u.ar.start[0];
11962               gfc_expr *end = ref->u.ar.end[0];
11963               void *mem = NULL;
11964
11965               /* Optimize away the (:) reference.  */
11966               if (start == NULL && end == NULL)
11967                 {
11968                   if (e->ref == ref)
11969                     e->ref = ref->next;
11970                   else
11971                     e->ref->next = ref->next;
11972                   mem = ref;
11973                 }
11974               else
11975                 {
11976                   ref->type = REF_SUBSTRING;
11977                   if (start == NULL)
11978                     start = gfc_int_expr (1);
11979                   ref->u.ss.start = start;
11980                   if (end == NULL && e->ts.u.cl)
11981                     end = gfc_copy_expr (e->ts.u.cl->length);
11982                   ref->u.ss.end = end;
11983                   ref->u.ss.length = e->ts.u.cl;
11984                   e->ts.u.cl = NULL;
11985                 }
11986               ref = ref->next;
11987               gfc_free (mem);
11988             }
11989
11990           /* Any further ref is an error.  */
11991           if (ref)
11992             {
11993               gcc_assert (ref->type == REF_ARRAY);
11994               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
11995                          &ref->u.ar.where);
11996               continue;
11997             }
11998         }
11999
12000       if (gfc_resolve_expr (e) == FAILURE)
12001         continue;
12002
12003       sym = e->symtree->n.sym;
12004
12005       if (sym->attr.is_protected)
12006         cnt_protected++;
12007       if (cnt_protected > 0 && cnt_protected != object)
12008         {
12009               gfc_error ("Either all or none of the objects in the "
12010                          "EQUIVALENCE set at %L shall have the "
12011                          "PROTECTED attribute",
12012                          &e->where);
12013               break;
12014         }
12015
12016       /* Shall not equivalence common block variables in a PURE procedure.  */
12017       if (sym->ns->proc_name
12018           && sym->ns->proc_name->attr.pure
12019           && sym->attr.in_common)
12020         {
12021           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
12022                      "object in the pure procedure '%s'",
12023                      sym->name, &e->where, sym->ns->proc_name->name);
12024           break;
12025         }
12026
12027       /* Shall not be a named constant.  */
12028       if (e->expr_type == EXPR_CONSTANT)
12029         {
12030           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
12031                      "object", sym->name, &e->where);
12032           continue;
12033         }
12034
12035       if (e->ts.type == BT_DERIVED
12036           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
12037         continue;
12038
12039       /* Check that the types correspond correctly:
12040          Note 5.28:
12041          A numeric sequence structure may be equivalenced to another sequence
12042          structure, an object of default integer type, default real type, double
12043          precision real type, default logical type such that components of the
12044          structure ultimately only become associated to objects of the same
12045          kind. A character sequence structure may be equivalenced to an object
12046          of default character kind or another character sequence structure.
12047          Other objects may be equivalenced only to objects of the same type and
12048          kind parameters.  */
12049
12050       /* Identical types are unconditionally OK.  */
12051       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
12052         goto identical_types;
12053
12054       last_eq_type = sequence_type (*last_ts);
12055       eq_type = sequence_type (sym->ts);
12056
12057       /* Since the pair of objects is not of the same type, mixed or
12058          non-default sequences can be rejected.  */
12059
12060       msg = "Sequence %s with mixed components in EQUIVALENCE "
12061             "statement at %L with different type objects";
12062       if ((object ==2
12063            && last_eq_type == SEQ_MIXED
12064            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
12065               == FAILURE)
12066           || (eq_type == SEQ_MIXED
12067               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12068                                  &e->where) == FAILURE))
12069         continue;
12070
12071       msg = "Non-default type object or sequence %s in EQUIVALENCE "
12072             "statement at %L with objects of different type";
12073       if ((object ==2
12074            && last_eq_type == SEQ_NONDEFAULT
12075            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
12076                               last_where) == FAILURE)
12077           || (eq_type == SEQ_NONDEFAULT
12078               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12079                                  &e->where) == FAILURE))
12080         continue;
12081
12082       msg ="Non-CHARACTER object '%s' in default CHARACTER "
12083            "EQUIVALENCE statement at %L";
12084       if (last_eq_type == SEQ_CHARACTER
12085           && eq_type != SEQ_CHARACTER
12086           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12087                              &e->where) == FAILURE)
12088                 continue;
12089
12090       msg ="Non-NUMERIC object '%s' in default NUMERIC "
12091            "EQUIVALENCE statement at %L";
12092       if (last_eq_type == SEQ_NUMERIC
12093           && eq_type != SEQ_NUMERIC
12094           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12095                              &e->where) == FAILURE)
12096                 continue;
12097
12098   identical_types:
12099       last_ts =&sym->ts;
12100       last_where = &e->where;
12101
12102       if (!e->ref)
12103         continue;
12104
12105       /* Shall not be an automatic array.  */
12106       if (e->ref->type == REF_ARRAY
12107           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
12108         {
12109           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
12110                      "an EQUIVALENCE object", sym->name, &e->where);
12111           continue;
12112         }
12113
12114       r = e->ref;
12115       while (r)
12116         {
12117           /* Shall not be a structure component.  */
12118           if (r->type == REF_COMPONENT)
12119             {
12120               gfc_error ("Structure component '%s' at %L cannot be an "
12121                          "EQUIVALENCE object",
12122                          r->u.c.component->name, &e->where);
12123               break;
12124             }
12125
12126           /* A substring shall not have length zero.  */
12127           if (r->type == REF_SUBSTRING)
12128             {
12129               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
12130                 {
12131                   gfc_error ("Substring at %L has length zero",
12132                              &r->u.ss.start->where);
12133                   break;
12134                 }
12135             }
12136           r = r->next;
12137         }
12138     }
12139 }
12140
12141
12142 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
12143
12144 static void
12145 resolve_fntype (gfc_namespace *ns)
12146 {
12147   gfc_entry_list *el;
12148   gfc_symbol *sym;
12149
12150   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
12151     return;
12152
12153   /* If there are any entries, ns->proc_name is the entry master
12154      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
12155   if (ns->entries)
12156     sym = ns->entries->sym;
12157   else
12158     sym = ns->proc_name;
12159   if (sym->result == sym
12160       && sym->ts.type == BT_UNKNOWN
12161       && gfc_set_default_type (sym, 0, NULL) == FAILURE
12162       && !sym->attr.untyped)
12163     {
12164       gfc_error ("Function '%s' at %L has no IMPLICIT type",
12165                  sym->name, &sym->declared_at);
12166       sym->attr.untyped = 1;
12167     }
12168
12169   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
12170       && !sym->attr.contained
12171       && !gfc_check_access (sym->ts.u.derived->attr.access,
12172                             sym->ts.u.derived->ns->default_access)
12173       && gfc_check_access (sym->attr.access, sym->ns->default_access))
12174     {
12175       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
12176                       "%L of PRIVATE type '%s'", sym->name,
12177                       &sym->declared_at, sym->ts.u.derived->name);
12178     }
12179
12180     if (ns->entries)
12181     for (el = ns->entries->next; el; el = el->next)
12182       {
12183         if (el->sym->result == el->sym
12184             && el->sym->ts.type == BT_UNKNOWN
12185             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
12186             && !el->sym->attr.untyped)
12187           {
12188             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
12189                        el->sym->name, &el->sym->declared_at);
12190             el->sym->attr.untyped = 1;
12191           }
12192       }
12193 }
12194
12195
12196 /* 12.3.2.1.1 Defined operators.  */
12197
12198 static gfc_try
12199 check_uop_procedure (gfc_symbol *sym, locus where)
12200 {
12201   gfc_formal_arglist *formal;
12202
12203   if (!sym->attr.function)
12204     {
12205       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
12206                  sym->name, &where);
12207       return FAILURE;
12208     }
12209
12210   if (sym->ts.type == BT_CHARACTER
12211       && !(sym->ts.u.cl && sym->ts.u.cl->length)
12212       && !(sym->result && sym->result->ts.u.cl
12213            && sym->result->ts.u.cl->length))
12214     {
12215       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
12216                  "character length", sym->name, &where);
12217       return FAILURE;
12218     }
12219
12220   formal = sym->formal;
12221   if (!formal || !formal->sym)
12222     {
12223       gfc_error ("User operator procedure '%s' at %L must have at least "
12224                  "one argument", sym->name, &where);
12225       return FAILURE;
12226     }
12227
12228   if (formal->sym->attr.intent != INTENT_IN)
12229     {
12230       gfc_error ("First argument of operator interface at %L must be "
12231                  "INTENT(IN)", &where);
12232       return FAILURE;
12233     }
12234
12235   if (formal->sym->attr.optional)
12236     {
12237       gfc_error ("First argument of operator interface at %L cannot be "
12238                  "optional", &where);
12239       return FAILURE;
12240     }
12241
12242   formal = formal->next;
12243   if (!formal || !formal->sym)
12244     return SUCCESS;
12245
12246   if (formal->sym->attr.intent != INTENT_IN)
12247     {
12248       gfc_error ("Second argument of operator interface at %L must be "
12249                  "INTENT(IN)", &where);
12250       return FAILURE;
12251     }
12252
12253   if (formal->sym->attr.optional)
12254     {
12255       gfc_error ("Second argument of operator interface at %L cannot be "
12256                  "optional", &where);
12257       return FAILURE;
12258     }
12259
12260   if (formal->next)
12261     {
12262       gfc_error ("Operator interface at %L must have, at most, two "
12263                  "arguments", &where);
12264       return FAILURE;
12265     }
12266
12267   return SUCCESS;
12268 }
12269
12270 static void
12271 gfc_resolve_uops (gfc_symtree *symtree)
12272 {
12273   gfc_interface *itr;
12274
12275   if (symtree == NULL)
12276     return;
12277
12278   gfc_resolve_uops (symtree->left);
12279   gfc_resolve_uops (symtree->right);
12280
12281   for (itr = symtree->n.uop->op; itr; itr = itr->next)
12282     check_uop_procedure (itr->sym, itr->sym->declared_at);
12283 }
12284
12285
12286 /* Examine all of the expressions associated with a program unit,
12287    assign types to all intermediate expressions, make sure that all
12288    assignments are to compatible types and figure out which names
12289    refer to which functions or subroutines.  It doesn't check code
12290    block, which is handled by resolve_code.  */
12291
12292 static void
12293 resolve_types (gfc_namespace *ns)
12294 {
12295   gfc_namespace *n;
12296   gfc_charlen *cl;
12297   gfc_data *d;
12298   gfc_equiv *eq;
12299   gfc_namespace* old_ns = gfc_current_ns;
12300
12301   /* Check that all IMPLICIT types are ok.  */
12302   if (!ns->seen_implicit_none)
12303     {
12304       unsigned letter;
12305       for (letter = 0; letter != GFC_LETTERS; ++letter)
12306         if (ns->set_flag[letter]
12307             && resolve_typespec_used (&ns->default_type[letter],
12308                                       &ns->implicit_loc[letter],
12309                                       NULL) == FAILURE)
12310           return;
12311     }
12312
12313   gfc_current_ns = ns;
12314
12315   resolve_entries (ns);
12316
12317   resolve_common_vars (ns->blank_common.head, false);
12318   resolve_common_blocks (ns->common_root);
12319
12320   resolve_contained_functions (ns);
12321
12322   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
12323
12324   for (cl = ns->cl_list; cl; cl = cl->next)
12325     resolve_charlen (cl);
12326
12327   gfc_traverse_ns (ns, resolve_symbol);
12328
12329   resolve_fntype (ns);
12330
12331   for (n = ns->contained; n; n = n->sibling)
12332     {
12333       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
12334         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
12335                    "also be PURE", n->proc_name->name,
12336                    &n->proc_name->declared_at);
12337
12338       resolve_types (n);
12339     }
12340
12341   forall_flag = 0;
12342   gfc_check_interfaces (ns);
12343
12344   gfc_traverse_ns (ns, resolve_values);
12345
12346   if (ns->save_all)
12347     gfc_save_all (ns);
12348
12349   iter_stack = NULL;
12350   for (d = ns->data; d; d = d->next)
12351     resolve_data (d);
12352
12353   iter_stack = NULL;
12354   gfc_traverse_ns (ns, gfc_formalize_init_value);
12355
12356   gfc_traverse_ns (ns, gfc_verify_binding_labels);
12357
12358   if (ns->common_root != NULL)
12359     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
12360
12361   for (eq = ns->equiv; eq; eq = eq->next)
12362     resolve_equivalence (eq);
12363
12364   /* Warn about unused labels.  */
12365   if (warn_unused_label)
12366     warn_unused_fortran_label (ns->st_labels);
12367
12368   gfc_resolve_uops (ns->uop_root);
12369
12370   gfc_current_ns = old_ns;
12371 }
12372
12373
12374 /* Call resolve_code recursively.  */
12375
12376 static void
12377 resolve_codes (gfc_namespace *ns)
12378 {
12379   gfc_namespace *n;
12380   bitmap_obstack old_obstack;
12381
12382   for (n = ns->contained; n; n = n->sibling)
12383     resolve_codes (n);
12384
12385   gfc_current_ns = ns;
12386
12387   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
12388   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
12389     cs_base = NULL;
12390
12391   /* Set to an out of range value.  */
12392   current_entry_id = -1;
12393
12394   old_obstack = labels_obstack;
12395   bitmap_obstack_initialize (&labels_obstack);
12396
12397   resolve_code (ns->code, ns);
12398
12399   bitmap_obstack_release (&labels_obstack);
12400   labels_obstack = old_obstack;
12401 }
12402
12403
12404 /* This function is called after a complete program unit has been compiled.
12405    Its purpose is to examine all of the expressions associated with a program
12406    unit, assign types to all intermediate expressions, make sure that all
12407    assignments are to compatible types and figure out which names refer to
12408    which functions or subroutines.  */
12409
12410 void
12411 gfc_resolve (gfc_namespace *ns)
12412 {
12413   gfc_namespace *old_ns;
12414   code_stack *old_cs_base;
12415
12416   if (ns->resolved)
12417     return;
12418
12419   ns->resolved = -1;
12420   old_ns = gfc_current_ns;
12421   old_cs_base = cs_base;
12422
12423   resolve_types (ns);
12424   resolve_codes (ns);
12425
12426   gfc_current_ns = old_ns;
12427   cs_base = old_cs_base;
12428   ns->resolved = 1;
12429 }