OSDN Git Service

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