re PR fortran/45366 (Problem with procedure pointer dummy in PURE function)
[platform/upstream/gcc.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010
3    Free Software Foundation, Inc.
4    Contributed by Andy Vaught
5
6 This file is part of GCC.
7
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 3, or (at your option) any later
11 version.
12
13 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
14 WARRANTY; without even the implied warranty of MERCHANTABILITY or
15 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
16 for more details.
17
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING3.  If not see
20 <http://www.gnu.org/licenses/>.  */
21
22 #include "config.h"
23 #include "system.h"
24 #include "flags.h"
25 #include "gfortran.h"
26 #include "obstack.h"
27 #include "bitmap.h"
28 #include "arith.h"  /* For gfc_compare_expr().  */
29 #include "dependency.h"
30 #include "data.h"
31 #include "target-memory.h" /* for gfc_simplify_transfer */
32 #include "constructor.h"
33
34 /* Types used in equivalence statements.  */
35
36 typedef enum seq_type
37 {
38   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
39 }
40 seq_type;
41
42 /* Stack to keep track of the nesting of blocks as we move through the
43    code.  See resolve_branch() and resolve_code().  */
44
45 typedef struct code_stack
46 {
47   struct gfc_code *head, *current;
48   struct code_stack *prev;
49
50   /* This bitmap keeps track of the targets valid for a branch from
51      inside this block except for END {IF|SELECT}s of enclosing
52      blocks.  */
53   bitmap reachable_labels;
54 }
55 code_stack;
56
57 static code_stack *cs_base = NULL;
58
59
60 /* Nonzero if we're inside a FORALL block.  */
61
62 static int forall_flag;
63
64 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
65
66 static int omp_workshare_flag;
67
68 /* Nonzero if we are processing a formal arglist. The corresponding function
69    resets the flag each time that it is read.  */
70 static int formal_arg_flag = 0;
71
72 /* True if we are resolving a specification expression.  */
73 static int specification_expr = 0;
74
75 /* The id of the last entry seen.  */
76 static int current_entry_id;
77
78 /* We use bitmaps to determine if a branch target is valid.  */
79 static bitmap_obstack labels_obstack;
80
81 /* True when simplifying a EXPR_VARIABLE argument to an inquiry function.  */
82 static bool inquiry_argument = false;
83
84 int
85 gfc_is_formal_arg (void)
86 {
87   return formal_arg_flag;
88 }
89
90 /* Is the symbol host associated?  */
91 static bool
92 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
93 {
94   for (ns = ns->parent; ns; ns = ns->parent)
95     {      
96       if (sym->ns == ns)
97         return true;
98     }
99
100   return false;
101 }
102
103 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
104    an ABSTRACT derived-type.  If where is not NULL, an error message with that
105    locus is printed, optionally using name.  */
106
107 static gfc_try
108 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
109 {
110   if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
111     {
112       if (where)
113         {
114           if (name)
115             gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
116                        name, where, ts->u.derived->name);
117           else
118             gfc_error ("ABSTRACT type '%s' used at %L",
119                        ts->u.derived->name, where);
120         }
121
122       return FAILURE;
123     }
124
125   return SUCCESS;
126 }
127
128
129 static void resolve_symbol (gfc_symbol *sym);
130 static gfc_try resolve_intrinsic (gfc_symbol *sym, locus *loc);
131
132
133 /* Resolve the interface for a PROCEDURE declaration or procedure pointer.  */
134
135 static gfc_try
136 resolve_procedure_interface (gfc_symbol *sym)
137 {
138   if (sym->ts.interface == sym)
139     {
140       gfc_error ("PROCEDURE '%s' at %L may not be used as its own interface",
141                  sym->name, &sym->declared_at);
142       return FAILURE;
143     }
144   if (sym->ts.interface->attr.procedure)
145     {
146       gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared "
147                  "in a later PROCEDURE statement", sym->ts.interface->name,
148                  sym->name, &sym->declared_at);
149       return FAILURE;
150     }
151
152   /* Get the attributes from the interface (now resolved).  */
153   if (sym->ts.interface->attr.if_source || sym->ts.interface->attr.intrinsic)
154     {
155       gfc_symbol *ifc = sym->ts.interface;
156       resolve_symbol (ifc);
157
158       if (ifc->attr.intrinsic)
159         resolve_intrinsic (ifc, &ifc->declared_at);
160
161       if (ifc->result)
162         sym->ts = ifc->result->ts;
163       else   
164         sym->ts = ifc->ts;
165       sym->ts.interface = ifc;
166       sym->attr.function = ifc->attr.function;
167       sym->attr.subroutine = ifc->attr.subroutine;
168       gfc_copy_formal_args (sym, ifc);
169
170       sym->attr.allocatable = ifc->attr.allocatable;
171       sym->attr.pointer = ifc->attr.pointer;
172       sym->attr.pure = ifc->attr.pure;
173       sym->attr.elemental = ifc->attr.elemental;
174       sym->attr.dimension = ifc->attr.dimension;
175       sym->attr.contiguous = ifc->attr.contiguous;
176       sym->attr.recursive = ifc->attr.recursive;
177       sym->attr.always_explicit = ifc->attr.always_explicit;
178       sym->attr.ext_attr |= ifc->attr.ext_attr;
179       /* Copy array spec.  */
180       sym->as = gfc_copy_array_spec (ifc->as);
181       if (sym->as)
182         {
183           int i;
184           for (i = 0; i < sym->as->rank; i++)
185             {
186               gfc_expr_replace_symbols (sym->as->lower[i], sym);
187               gfc_expr_replace_symbols (sym->as->upper[i], sym);
188             }
189         }
190       /* Copy char length.  */
191       if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
192         {
193           sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
194           gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
195           if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
196               && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
197             return FAILURE;
198         }
199     }
200   else if (sym->ts.interface->name[0] != '\0')
201     {
202       gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
203                  sym->ts.interface->name, sym->name, &sym->declared_at);
204       return FAILURE;
205     }
206
207   return SUCCESS;
208 }
209
210
211 /* Resolve types of formal argument lists.  These have to be done early so that
212    the formal argument lists of module procedures can be copied to the
213    containing module before the individual procedures are resolved
214    individually.  We also resolve argument lists of procedures in interface
215    blocks because they are self-contained scoping units.
216
217    Since a dummy argument cannot be a non-dummy procedure, the only
218    resort left for untyped names are the IMPLICIT types.  */
219
220 static void
221 resolve_formal_arglist (gfc_symbol *proc)
222 {
223   gfc_formal_arglist *f;
224   gfc_symbol *sym;
225   int i;
226
227   if (proc->result != NULL)
228     sym = proc->result;
229   else
230     sym = proc;
231
232   if (gfc_elemental (proc)
233       || sym->attr.pointer || sym->attr.allocatable
234       || (sym->as && sym->as->rank > 0))
235     {
236       proc->attr.always_explicit = 1;
237       sym->attr.always_explicit = 1;
238     }
239
240   formal_arg_flag = 1;
241
242   for (f = proc->formal; f; f = f->next)
243     {
244       sym = f->sym;
245
246       if (sym == NULL)
247         {
248           /* Alternate return placeholder.  */
249           if (gfc_elemental (proc))
250             gfc_error ("Alternate return specifier in elemental subroutine "
251                        "'%s' at %L is not allowed", proc->name,
252                        &proc->declared_at);
253           if (proc->attr.function)
254             gfc_error ("Alternate return specifier in function "
255                        "'%s' at %L is not allowed", proc->name,
256                        &proc->declared_at);
257           continue;
258         }
259       else if (sym->attr.procedure && sym->ts.interface
260                && sym->attr.if_source != IFSRC_DECL)
261         resolve_procedure_interface (sym);
262
263       if (sym->attr.if_source != IFSRC_UNKNOWN)
264         resolve_formal_arglist (sym);
265
266       if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
267         {
268           if (gfc_pure (proc) && !gfc_pure (sym))
269             {
270               gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
271                          "also be PURE", sym->name, &sym->declared_at);
272               continue;
273             }
274
275           if (gfc_elemental (proc))
276             {
277               gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
278                          "procedure", &sym->declared_at);
279               continue;
280             }
281
282           if (sym->attr.function
283                 && sym->ts.type == BT_UNKNOWN
284                 && sym->attr.intrinsic)
285             {
286               gfc_intrinsic_sym *isym;
287               isym = gfc_find_function (sym->name);
288               if (isym == NULL || !isym->specific)
289                 {
290                   gfc_error ("Unable to find a specific INTRINSIC procedure "
291                              "for the reference '%s' at %L", sym->name,
292                              &sym->declared_at);
293                 }
294               sym->ts = isym->ts;
295             }
296
297           continue;
298         }
299
300       if (sym->ts.type == BT_UNKNOWN)
301         {
302           if (!sym->attr.function || sym->result == sym)
303             gfc_set_default_type (sym, 1, sym->ns);
304         }
305
306       gfc_resolve_array_spec (sym->as, 0);
307
308       /* We can't tell if an array with dimension (:) is assumed or deferred
309          shape until we know if it has the pointer or allocatable attributes.
310       */
311       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
312           && !(sym->attr.pointer || sym->attr.allocatable))
313         {
314           sym->as->type = AS_ASSUMED_SHAPE;
315           for (i = 0; i < sym->as->rank; i++)
316             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
317                                                   NULL, 1);
318         }
319
320       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
321           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
322           || sym->attr.optional)
323         {
324           proc->attr.always_explicit = 1;
325           if (proc->result)
326             proc->result->attr.always_explicit = 1;
327         }
328
329       /* If the flavor is unknown at this point, it has to be a variable.
330          A procedure specification would have already set the type.  */
331
332       if (sym->attr.flavor == FL_UNKNOWN)
333         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
334
335       if (gfc_pure (proc) && !sym->attr.pointer
336           && sym->attr.flavor != FL_PROCEDURE)
337         {
338           if (proc->attr.function && sym->attr.intent != INTENT_IN)
339             gfc_error ("Argument '%s' of pure function '%s' at %L must be "
340                        "INTENT(IN)", sym->name, proc->name,
341                        &sym->declared_at);
342
343           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
344             gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
345                        "have its INTENT specified", sym->name, proc->name,
346                        &sym->declared_at);
347         }
348
349       if (gfc_elemental (proc))
350         {
351           /* F2008, C1289.  */
352           if (sym->attr.codimension)
353             {
354               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
355                          "procedure", sym->name, &sym->declared_at);
356               continue;
357             }
358
359           if (sym->as != NULL)
360             {
361               gfc_error ("Argument '%s' of elemental procedure at %L must "
362                          "be scalar", sym->name, &sym->declared_at);
363               continue;
364             }
365
366           if (sym->attr.allocatable)
367             {
368               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
369                          "have the ALLOCATABLE attribute", sym->name,
370                          &sym->declared_at);
371               continue;
372             }
373
374           if (sym->attr.pointer)
375             {
376               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
377                          "have the POINTER attribute", sym->name,
378                          &sym->declared_at);
379               continue;
380             }
381
382           if (sym->attr.flavor == FL_PROCEDURE)
383             {
384               gfc_error ("Dummy procedure '%s' not allowed in elemental "
385                          "procedure '%s' at %L", sym->name, proc->name,
386                          &sym->declared_at);
387               continue;
388             }
389
390           if (sym->attr.intent == INTENT_UNKNOWN)
391             {
392               gfc_error ("Argument '%s' of elemental procedure '%s' at %L must "
393                          "have its INTENT specified", sym->name, proc->name,
394                          &sym->declared_at);
395               continue;
396             }
397         }
398
399       /* Each dummy shall be specified to be scalar.  */
400       if (proc->attr.proc == PROC_ST_FUNCTION)
401         {
402           if (sym->as != NULL)
403             {
404               gfc_error ("Argument '%s' of statement function at %L must "
405                          "be scalar", sym->name, &sym->declared_at);
406               continue;
407             }
408
409           if (sym->ts.type == BT_CHARACTER)
410             {
411               gfc_charlen *cl = sym->ts.u.cl;
412               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
413                 {
414                   gfc_error ("Character-valued argument '%s' of statement "
415                              "function at %L must have constant length",
416                              sym->name, &sym->declared_at);
417                   continue;
418                 }
419             }
420         }
421     }
422   formal_arg_flag = 0;
423 }
424
425
426 /* Work function called when searching for symbols that have argument lists
427    associated with them.  */
428
429 static void
430 find_arglists (gfc_symbol *sym)
431 {
432   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
433     return;
434
435   resolve_formal_arglist (sym);
436 }
437
438
439 /* Given a namespace, resolve all formal argument lists within the namespace.
440  */
441
442 static void
443 resolve_formal_arglists (gfc_namespace *ns)
444 {
445   if (ns == NULL)
446     return;
447
448   gfc_traverse_ns (ns, find_arglists);
449 }
450
451
452 static void
453 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
454 {
455   gfc_try t;
456
457   /* If this namespace is not a function or an entry master function,
458      ignore it.  */
459   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
460       || sym->attr.entry_master)
461     return;
462
463   /* Try to find out of what the return type is.  */
464   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
465     {
466       t = gfc_set_default_type (sym->result, 0, ns);
467
468       if (t == FAILURE && !sym->result->attr.untyped)
469         {
470           if (sym->result == sym)
471             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
472                        sym->name, &sym->declared_at);
473           else if (!sym->result->attr.proc_pointer)
474             gfc_error ("Result '%s' of contained function '%s' at %L has "
475                        "no IMPLICIT type", sym->result->name, sym->name,
476                        &sym->result->declared_at);
477           sym->result->attr.untyped = 1;
478         }
479     }
480
481   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
482      type, lists the only ways a character length value of * can be used:
483      dummy arguments of procedures, named constants, and function results
484      in external functions.  Internal function results and results of module
485      procedures are not on this list, ergo, not permitted.  */
486
487   if (sym->result->ts.type == BT_CHARACTER)
488     {
489       gfc_charlen *cl = sym->result->ts.u.cl;
490       if (!cl || !cl->length)
491         {
492           /* See if this is a module-procedure and adapt error message
493              accordingly.  */
494           bool module_proc;
495           gcc_assert (ns->parent && ns->parent->proc_name);
496           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
497
498           gfc_error ("Character-valued %s '%s' at %L must not be"
499                      " assumed length",
500                      module_proc ? _("module procedure")
501                                  : _("internal function"),
502                      sym->name, &sym->declared_at);
503         }
504     }
505 }
506
507
508 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
509    introduce duplicates.  */
510
511 static void
512 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
513 {
514   gfc_formal_arglist *f, *new_arglist;
515   gfc_symbol *new_sym;
516
517   for (; new_args != NULL; new_args = new_args->next)
518     {
519       new_sym = new_args->sym;
520       /* See if this arg is already in the formal argument list.  */
521       for (f = proc->formal; f; f = f->next)
522         {
523           if (new_sym == f->sym)
524             break;
525         }
526
527       if (f)
528         continue;
529
530       /* Add a new argument.  Argument order is not important.  */
531       new_arglist = gfc_get_formal_arglist ();
532       new_arglist->sym = new_sym;
533       new_arglist->next = proc->formal;
534       proc->formal  = new_arglist;
535     }
536 }
537
538
539 /* Flag the arguments that are not present in all entries.  */
540
541 static void
542 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
543 {
544   gfc_formal_arglist *f, *head;
545   head = new_args;
546
547   for (f = proc->formal; f; f = f->next)
548     {
549       if (f->sym == NULL)
550         continue;
551
552       for (new_args = head; new_args; new_args = new_args->next)
553         {
554           if (new_args->sym == f->sym)
555             break;
556         }
557
558       if (new_args)
559         continue;
560
561       f->sym->attr.not_always_present = 1;
562     }
563 }
564
565
566 /* Resolve alternate entry points.  If a symbol has multiple entry points we
567    create a new master symbol for the main routine, and turn the existing
568    symbol into an entry point.  */
569
570 static void
571 resolve_entries (gfc_namespace *ns)
572 {
573   gfc_namespace *old_ns;
574   gfc_code *c;
575   gfc_symbol *proc;
576   gfc_entry_list *el;
577   char name[GFC_MAX_SYMBOL_LEN + 1];
578   static int master_count = 0;
579
580   if (ns->proc_name == NULL)
581     return;
582
583   /* No need to do anything if this procedure doesn't have alternate entry
584      points.  */
585   if (!ns->entries)
586     return;
587
588   /* We may already have resolved alternate entry points.  */
589   if (ns->proc_name->attr.entry_master)
590     return;
591
592   /* If this isn't a procedure something has gone horribly wrong.  */
593   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
594
595   /* Remember the current namespace.  */
596   old_ns = gfc_current_ns;
597
598   gfc_current_ns = ns;
599
600   /* Add the main entry point to the list of entry points.  */
601   el = gfc_get_entry_list ();
602   el->sym = ns->proc_name;
603   el->id = 0;
604   el->next = ns->entries;
605   ns->entries = el;
606   ns->proc_name->attr.entry = 1;
607
608   /* If it is a module function, it needs to be in the right namespace
609      so that gfc_get_fake_result_decl can gather up the results. The
610      need for this arose in get_proc_name, where these beasts were
611      left in their own namespace, to keep prior references linked to
612      the entry declaration.*/
613   if (ns->proc_name->attr.function
614       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
615     el->sym->ns = ns;
616
617   /* Do the same for entries where the master is not a module
618      procedure.  These are retained in the module namespace because
619      of the module procedure declaration.  */
620   for (el = el->next; el; el = el->next)
621     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
622           && el->sym->attr.mod_proc)
623       el->sym->ns = ns;
624   el = ns->entries;
625
626   /* Add an entry statement for it.  */
627   c = gfc_get_code ();
628   c->op = EXEC_ENTRY;
629   c->ext.entry = el;
630   c->next = ns->code;
631   ns->code = c;
632
633   /* Create a new symbol for the master function.  */
634   /* Give the internal function a unique name (within this file).
635      Also include the function name so the user has some hope of figuring
636      out what is going on.  */
637   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
638             master_count++, ns->proc_name->name);
639   gfc_get_ha_symbol (name, &proc);
640   gcc_assert (proc != NULL);
641
642   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
643   if (ns->proc_name->attr.subroutine)
644     gfc_add_subroutine (&proc->attr, proc->name, NULL);
645   else
646     {
647       gfc_symbol *sym;
648       gfc_typespec *ts, *fts;
649       gfc_array_spec *as, *fas;
650       gfc_add_function (&proc->attr, proc->name, NULL);
651       proc->result = proc;
652       fas = ns->entries->sym->as;
653       fas = fas ? fas : ns->entries->sym->result->as;
654       fts = &ns->entries->sym->result->ts;
655       if (fts->type == BT_UNKNOWN)
656         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
657       for (el = ns->entries->next; el; el = el->next)
658         {
659           ts = &el->sym->result->ts;
660           as = el->sym->as;
661           as = as ? as : el->sym->result->as;
662           if (ts->type == BT_UNKNOWN)
663             ts = gfc_get_default_type (el->sym->result->name, NULL);
664
665           if (! gfc_compare_types (ts, fts)
666               || (el->sym->result->attr.dimension
667                   != ns->entries->sym->result->attr.dimension)
668               || (el->sym->result->attr.pointer
669                   != ns->entries->sym->result->attr.pointer))
670             break;
671           else if (as && fas && ns->entries->sym->result != el->sym->result
672                       && gfc_compare_array_spec (as, fas) == 0)
673             gfc_error ("Function %s at %L has entries with mismatched "
674                        "array specifications", ns->entries->sym->name,
675                        &ns->entries->sym->declared_at);
676           /* The characteristics need to match and thus both need to have
677              the same string length, i.e. both len=*, or both len=4.
678              Having both len=<variable> is also possible, but difficult to
679              check at compile time.  */
680           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
681                    && (((ts->u.cl->length && !fts->u.cl->length)
682                         ||(!ts->u.cl->length && fts->u.cl->length))
683                        || (ts->u.cl->length
684                            && ts->u.cl->length->expr_type
685                               != fts->u.cl->length->expr_type)
686                        || (ts->u.cl->length
687                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
688                            && mpz_cmp (ts->u.cl->length->value.integer,
689                                        fts->u.cl->length->value.integer) != 0)))
690             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
691                             "entries returning variables of different "
692                             "string lengths", ns->entries->sym->name,
693                             &ns->entries->sym->declared_at);
694         }
695
696       if (el == NULL)
697         {
698           sym = ns->entries->sym->result;
699           /* All result types the same.  */
700           proc->ts = *fts;
701           if (sym->attr.dimension)
702             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
703           if (sym->attr.pointer)
704             gfc_add_pointer (&proc->attr, NULL);
705         }
706       else
707         {
708           /* Otherwise the result will be passed through a union by
709              reference.  */
710           proc->attr.mixed_entry_master = 1;
711           for (el = ns->entries; el; el = el->next)
712             {
713               sym = el->sym->result;
714               if (sym->attr.dimension)
715                 {
716                   if (el == ns->entries)
717                     gfc_error ("FUNCTION result %s can't be an array in "
718                                "FUNCTION %s at %L", sym->name,
719                                ns->entries->sym->name, &sym->declared_at);
720                   else
721                     gfc_error ("ENTRY result %s can't be an array in "
722                                "FUNCTION %s at %L", sym->name,
723                                ns->entries->sym->name, &sym->declared_at);
724                 }
725               else if (sym->attr.pointer)
726                 {
727                   if (el == ns->entries)
728                     gfc_error ("FUNCTION result %s can't be a POINTER in "
729                                "FUNCTION %s at %L", sym->name,
730                                ns->entries->sym->name, &sym->declared_at);
731                   else
732                     gfc_error ("ENTRY result %s can't be a POINTER in "
733                                "FUNCTION %s at %L", sym->name,
734                                ns->entries->sym->name, &sym->declared_at);
735                 }
736               else
737                 {
738                   ts = &sym->ts;
739                   if (ts->type == BT_UNKNOWN)
740                     ts = gfc_get_default_type (sym->name, NULL);
741                   switch (ts->type)
742                     {
743                     case BT_INTEGER:
744                       if (ts->kind == gfc_default_integer_kind)
745                         sym = NULL;
746                       break;
747                     case BT_REAL:
748                       if (ts->kind == gfc_default_real_kind
749                           || ts->kind == gfc_default_double_kind)
750                         sym = NULL;
751                       break;
752                     case BT_COMPLEX:
753                       if (ts->kind == gfc_default_complex_kind)
754                         sym = NULL;
755                       break;
756                     case BT_LOGICAL:
757                       if (ts->kind == gfc_default_logical_kind)
758                         sym = NULL;
759                       break;
760                     case BT_UNKNOWN:
761                       /* We will issue error elsewhere.  */
762                       sym = NULL;
763                       break;
764                     default:
765                       break;
766                     }
767                   if (sym)
768                     {
769                       if (el == ns->entries)
770                         gfc_error ("FUNCTION result %s can't be of type %s "
771                                    "in FUNCTION %s at %L", sym->name,
772                                    gfc_typename (ts), ns->entries->sym->name,
773                                    &sym->declared_at);
774                       else
775                         gfc_error ("ENTRY result %s can't be of type %s "
776                                    "in FUNCTION %s at %L", sym->name,
777                                    gfc_typename (ts), ns->entries->sym->name,
778                                    &sym->declared_at);
779                     }
780                 }
781             }
782         }
783     }
784   proc->attr.access = ACCESS_PRIVATE;
785   proc->attr.entry_master = 1;
786
787   /* Merge all the entry point arguments.  */
788   for (el = ns->entries; el; el = el->next)
789     merge_argument_lists (proc, el->sym->formal);
790
791   /* Check the master formal arguments for any that are not
792      present in all entry points.  */
793   for (el = ns->entries; el; el = el->next)
794     check_argument_lists (proc, el->sym->formal);
795
796   /* Use the master function for the function body.  */
797   ns->proc_name = proc;
798
799   /* Finalize the new symbols.  */
800   gfc_commit_symbols ();
801
802   /* Restore the original namespace.  */
803   gfc_current_ns = old_ns;
804 }
805
806
807 /* Resolve common variables.  */
808 static void
809 resolve_common_vars (gfc_symbol *sym, bool named_common)
810 {
811   gfc_symbol *csym = sym;
812
813   for (; csym; csym = csym->common_next)
814     {
815       if (csym->value || csym->attr.data)
816         {
817           if (!csym->ns->is_block_data)
818             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
819                             "but only in BLOCK DATA initialization is "
820                             "allowed", csym->name, &csym->declared_at);
821           else if (!named_common)
822             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
823                             "in a blank COMMON but initialization is only "
824                             "allowed in named common blocks", csym->name,
825                             &csym->declared_at);
826         }
827
828       if (csym->ts.type != BT_DERIVED)
829         continue;
830
831       if (!(csym->ts.u.derived->attr.sequence
832             || csym->ts.u.derived->attr.is_bind_c))
833         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
834                        "has neither the SEQUENCE nor the BIND(C) "
835                        "attribute", csym->name, &csym->declared_at);
836       if (csym->ts.u.derived->attr.alloc_comp)
837         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
838                        "has an ultimate component that is "
839                        "allocatable", csym->name, &csym->declared_at);
840       if (gfc_has_default_initializer (csym->ts.u.derived))
841         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
842                        "may not have default initializer", csym->name,
843                        &csym->declared_at);
844
845       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
846         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
847     }
848 }
849
850 /* Resolve common blocks.  */
851 static void
852 resolve_common_blocks (gfc_symtree *common_root)
853 {
854   gfc_symbol *sym;
855
856   if (common_root == NULL)
857     return;
858
859   if (common_root->left)
860     resolve_common_blocks (common_root->left);
861   if (common_root->right)
862     resolve_common_blocks (common_root->right);
863
864   resolve_common_vars (common_root->n.common->head, true);
865
866   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
867   if (sym == NULL)
868     return;
869
870   if (sym->attr.flavor == FL_PARAMETER)
871     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
872                sym->name, &common_root->n.common->where, &sym->declared_at);
873
874   if (sym->attr.intrinsic)
875     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
876                sym->name, &common_root->n.common->where);
877   else if (sym->attr.result
878            || gfc_is_function_return_value (sym, gfc_current_ns))
879     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
880                     "that is also a function result", sym->name,
881                     &common_root->n.common->where);
882   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
883            && sym->attr.proc != PROC_ST_FUNCTION)
884     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
885                     "that is also a global procedure", sym->name,
886                     &common_root->n.common->where);
887 }
888
889
890 /* Resolve contained function types.  Because contained functions can call one
891    another, they have to be worked out before any of the contained procedures
892    can be resolved.
893
894    The good news is that if a function doesn't already have a type, the only
895    way it can get one is through an IMPLICIT type or a RESULT variable, because
896    by definition contained functions are contained namespace they're contained
897    in, not in a sibling or parent namespace.  */
898
899 static void
900 resolve_contained_functions (gfc_namespace *ns)
901 {
902   gfc_namespace *child;
903   gfc_entry_list *el;
904
905   resolve_formal_arglists (ns);
906
907   for (child = ns->contained; child; child = child->sibling)
908     {
909       /* Resolve alternate entry points first.  */
910       resolve_entries (child);
911
912       /* Then check function return types.  */
913       resolve_contained_fntype (child->proc_name, child);
914       for (el = child->entries; el; el = el->next)
915         resolve_contained_fntype (el->sym, child);
916     }
917 }
918
919
920 /* Resolve all of the elements of a structure constructor and make sure that
921    the types are correct. The 'init' flag indicates that the given
922    constructor is an initializer.  */
923
924 static gfc_try
925 resolve_structure_cons (gfc_expr *expr, int init)
926 {
927   gfc_constructor *cons;
928   gfc_component *comp;
929   gfc_try t;
930   symbol_attribute a;
931
932   t = SUCCESS;
933   cons = gfc_constructor_first (expr->value.constructor);
934   /* A constructor may have references if it is the result of substituting a
935      parameter variable.  In this case we just pull out the component we
936      want.  */
937   if (expr->ref)
938     comp = expr->ref->u.c.sym->components;
939   else
940     comp = expr->ts.u.derived->components;
941
942   /* See if the user is trying to invoke a structure constructor for one of
943      the iso_c_binding derived types.  */
944   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
945       && expr->ts.u.derived->ts.is_iso_c && cons
946       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
947     {
948       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
949                  expr->ts.u.derived->name, &(expr->where));
950       return FAILURE;
951     }
952
953   /* Return if structure constructor is c_null_(fun)prt.  */
954   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
955       && expr->ts.u.derived->ts.is_iso_c && cons
956       && cons->expr && cons->expr->expr_type == EXPR_NULL)
957     return SUCCESS;
958
959   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
960     {
961       int rank;
962
963       if (!cons->expr)
964         continue;
965
966       if (gfc_resolve_expr (cons->expr) == FAILURE)
967         {
968           t = FAILURE;
969           continue;
970         }
971
972       rank = comp->as ? comp->as->rank : 0;
973       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
974           && (comp->attr.allocatable || cons->expr->rank))
975         {
976           gfc_error ("The rank of the element in the derived type "
977                      "constructor at %L does not match that of the "
978                      "component (%d/%d)", &cons->expr->where,
979                      cons->expr->rank, rank);
980           t = FAILURE;
981         }
982
983       /* If we don't have the right type, try to convert it.  */
984
985       if (!comp->attr.proc_pointer &&
986           !gfc_compare_types (&cons->expr->ts, &comp->ts))
987         {
988           t = FAILURE;
989           if (strcmp (comp->name, "$extends") == 0)
990             {
991               /* Can afford to be brutal with the $extends initializer.
992                  The derived type can get lost because it is PRIVATE
993                  but it is not usage constrained by the standard.  */
994               cons->expr->ts = comp->ts;
995               t = SUCCESS;
996             }
997           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
998             gfc_error ("The element in the derived type constructor at %L, "
999                        "for pointer component '%s', is %s but should be %s",
1000                        &cons->expr->where, comp->name,
1001                        gfc_basic_typename (cons->expr->ts.type),
1002                        gfc_basic_typename (comp->ts.type));
1003           else
1004             t = gfc_convert_type (cons->expr, &comp->ts, 1);
1005         }
1006
1007       /* For strings, the length of the constructor should be the same as
1008          the one of the structure, ensure this if the lengths are known at
1009          compile time and when we are dealing with PARAMETER or structure
1010          constructors.  */
1011       if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1012           && comp->ts.u.cl->length
1013           && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1014           && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1015           && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1016           && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1017                       comp->ts.u.cl->length->value.integer) != 0)
1018         {
1019           if (cons->expr->expr_type == EXPR_VARIABLE
1020               && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1021             {
1022               /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1023                  to make use of the gfc_resolve_character_array_constructor
1024                  machinery.  The expression is later simplified away to
1025                  an array of string literals.  */
1026               gfc_expr *para = cons->expr;
1027               cons->expr = gfc_get_expr ();
1028               cons->expr->ts = para->ts;
1029               cons->expr->where = para->where;
1030               cons->expr->expr_type = EXPR_ARRAY;
1031               cons->expr->rank = para->rank;
1032               cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1033               gfc_constructor_append_expr (&cons->expr->value.constructor,
1034                                            para, &cons->expr->where);
1035             }
1036           if (cons->expr->expr_type == EXPR_ARRAY)
1037             {
1038               gfc_constructor *p;
1039               p = gfc_constructor_first (cons->expr->value.constructor);
1040               if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1041                 {
1042                   gfc_charlen *cl, *cl2;
1043
1044                   cl2 = NULL;
1045                   for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1046                     {
1047                       if (cl == cons->expr->ts.u.cl)
1048                         break;
1049                       cl2 = cl;
1050                     }
1051
1052                   gcc_assert (cl);
1053
1054                   if (cl2)
1055                     cl2->next = cl->next;
1056
1057                   gfc_free_expr (cl->length);
1058                   gfc_free (cl);
1059                 }
1060
1061               cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1062               cons->expr->ts.u.cl->length_from_typespec = true;
1063               cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1064               gfc_resolve_character_array_constructor (cons->expr);
1065             }
1066         }
1067
1068       if (cons->expr->expr_type == EXPR_NULL
1069           && !(comp->attr.pointer || comp->attr.allocatable
1070                || comp->attr.proc_pointer
1071                || (comp->ts.type == BT_CLASS
1072                    && (CLASS_DATA (comp)->attr.class_pointer
1073                        || CLASS_DATA (comp)->attr.allocatable))))
1074         {
1075           t = FAILURE;
1076           gfc_error ("The NULL in the derived type constructor at %L is "
1077                      "being applied to component '%s', which is neither "
1078                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
1079                      comp->name);
1080         }
1081
1082       if (!comp->attr.pointer || cons->expr->expr_type == EXPR_NULL)
1083         continue;
1084
1085       a = gfc_expr_attr (cons->expr);
1086
1087       if (!a.pointer && !a.target)
1088         {
1089           t = FAILURE;
1090           gfc_error ("The element in the derived type constructor at %L, "
1091                      "for pointer component '%s' should be a POINTER or "
1092                      "a TARGET", &cons->expr->where, comp->name);
1093         }
1094
1095       if (init)
1096         {
1097           /* F08:C461. Additional checks for pointer initialization.  */
1098           if (a.allocatable)
1099             {
1100               t = FAILURE;
1101               gfc_error ("Pointer initialization target at %L "
1102                          "must not be ALLOCATABLE ", &cons->expr->where);
1103             }
1104           if (!a.save)
1105             {
1106               t = FAILURE;
1107               gfc_error ("Pointer initialization target at %L "
1108                          "must have the SAVE attribute", &cons->expr->where);
1109             }
1110         }
1111
1112       /* F2003, C1272 (3).  */
1113       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
1114           && (gfc_impure_variable (cons->expr->symtree->n.sym)
1115               || gfc_is_coindexed (cons->expr)))
1116         {
1117           t = FAILURE;
1118           gfc_error ("Invalid expression in the derived type constructor for "
1119                      "pointer component '%s' at %L in PURE procedure",
1120                      comp->name, &cons->expr->where);
1121         }
1122
1123     }
1124
1125   return t;
1126 }
1127
1128
1129 /****************** Expression name resolution ******************/
1130
1131 /* Returns 0 if a symbol was not declared with a type or
1132    attribute declaration statement, nonzero otherwise.  */
1133
1134 static int
1135 was_declared (gfc_symbol *sym)
1136 {
1137   symbol_attribute a;
1138
1139   a = sym->attr;
1140
1141   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1142     return 1;
1143
1144   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1145       || a.optional || a.pointer || a.save || a.target || a.volatile_
1146       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1147       || a.asynchronous || a.codimension)
1148     return 1;
1149
1150   return 0;
1151 }
1152
1153
1154 /* Determine if a symbol is generic or not.  */
1155
1156 static int
1157 generic_sym (gfc_symbol *sym)
1158 {
1159   gfc_symbol *s;
1160
1161   if (sym->attr.generic ||
1162       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1163     return 1;
1164
1165   if (was_declared (sym) || sym->ns->parent == NULL)
1166     return 0;
1167
1168   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1169   
1170   if (s != NULL)
1171     {
1172       if (s == sym)
1173         return 0;
1174       else
1175         return generic_sym (s);
1176     }
1177
1178   return 0;
1179 }
1180
1181
1182 /* Determine if a symbol is specific or not.  */
1183
1184 static int
1185 specific_sym (gfc_symbol *sym)
1186 {
1187   gfc_symbol *s;
1188
1189   if (sym->attr.if_source == IFSRC_IFBODY
1190       || sym->attr.proc == PROC_MODULE
1191       || sym->attr.proc == PROC_INTERNAL
1192       || sym->attr.proc == PROC_ST_FUNCTION
1193       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1194       || sym->attr.external)
1195     return 1;
1196
1197   if (was_declared (sym) || sym->ns->parent == NULL)
1198     return 0;
1199
1200   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1201
1202   return (s == NULL) ? 0 : specific_sym (s);
1203 }
1204
1205
1206 /* Figure out if the procedure is specific, generic or unknown.  */
1207
1208 typedef enum
1209 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1210 proc_type;
1211
1212 static proc_type
1213 procedure_kind (gfc_symbol *sym)
1214 {
1215   if (generic_sym (sym))
1216     return PTYPE_GENERIC;
1217
1218   if (specific_sym (sym))
1219     return PTYPE_SPECIFIC;
1220
1221   return PTYPE_UNKNOWN;
1222 }
1223
1224 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1225    is nonzero when matching actual arguments.  */
1226
1227 static int need_full_assumed_size = 0;
1228
1229 static bool
1230 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1231 {
1232   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1233       return false;
1234
1235   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1236      What should it be?  */
1237   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1238           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1239                && (e->ref->u.ar.type == AR_FULL))
1240     {
1241       gfc_error ("The upper bound in the last dimension must "
1242                  "appear in the reference to the assumed size "
1243                  "array '%s' at %L", sym->name, &e->where);
1244       return true;
1245     }
1246   return false;
1247 }
1248
1249
1250 /* Look for bad assumed size array references in argument expressions
1251   of elemental and array valued intrinsic procedures.  Since this is
1252   called from procedure resolution functions, it only recurses at
1253   operators.  */
1254
1255 static bool
1256 resolve_assumed_size_actual (gfc_expr *e)
1257 {
1258   if (e == NULL)
1259    return false;
1260
1261   switch (e->expr_type)
1262     {
1263     case EXPR_VARIABLE:
1264       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1265         return true;
1266       break;
1267
1268     case EXPR_OP:
1269       if (resolve_assumed_size_actual (e->value.op.op1)
1270           || resolve_assumed_size_actual (e->value.op.op2))
1271         return true;
1272       break;
1273
1274     default:
1275       break;
1276     }
1277   return false;
1278 }
1279
1280
1281 /* Check a generic procedure, passed as an actual argument, to see if
1282    there is a matching specific name.  If none, it is an error, and if
1283    more than one, the reference is ambiguous.  */
1284 static int
1285 count_specific_procs (gfc_expr *e)
1286 {
1287   int n;
1288   gfc_interface *p;
1289   gfc_symbol *sym;
1290         
1291   n = 0;
1292   sym = e->symtree->n.sym;
1293
1294   for (p = sym->generic; p; p = p->next)
1295     if (strcmp (sym->name, p->sym->name) == 0)
1296       {
1297         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1298                                        sym->name);
1299         n++;
1300       }
1301
1302   if (n > 1)
1303     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1304                &e->where);
1305
1306   if (n == 0)
1307     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1308                "argument at %L", sym->name, &e->where);
1309
1310   return n;
1311 }
1312
1313
1314 /* See if a call to sym could possibly be a not allowed RECURSION because of
1315    a missing RECURIVE declaration.  This means that either sym is the current
1316    context itself, or sym is the parent of a contained procedure calling its
1317    non-RECURSIVE containing procedure.
1318    This also works if sym is an ENTRY.  */
1319
1320 static bool
1321 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1322 {
1323   gfc_symbol* proc_sym;
1324   gfc_symbol* context_proc;
1325   gfc_namespace* real_context;
1326
1327   if (sym->attr.flavor == FL_PROGRAM)
1328     return false;
1329
1330   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1331
1332   /* If we've got an ENTRY, find real procedure.  */
1333   if (sym->attr.entry && sym->ns->entries)
1334     proc_sym = sym->ns->entries->sym;
1335   else
1336     proc_sym = sym;
1337
1338   /* If sym is RECURSIVE, all is well of course.  */
1339   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1340     return false;
1341
1342   /* Find the context procedure's "real" symbol if it has entries.
1343      We look for a procedure symbol, so recurse on the parents if we don't
1344      find one (like in case of a BLOCK construct).  */
1345   for (real_context = context; ; real_context = real_context->parent)
1346     {
1347       /* We should find something, eventually!  */
1348       gcc_assert (real_context);
1349
1350       context_proc = (real_context->entries ? real_context->entries->sym
1351                                             : real_context->proc_name);
1352
1353       /* In some special cases, there may not be a proc_name, like for this
1354          invalid code:
1355          real(bad_kind()) function foo () ...
1356          when checking the call to bad_kind ().
1357          In these cases, we simply return here and assume that the
1358          call is ok.  */
1359       if (!context_proc)
1360         return false;
1361
1362       if (context_proc->attr.flavor != FL_LABEL)
1363         break;
1364     }
1365
1366   /* A call from sym's body to itself is recursion, of course.  */
1367   if (context_proc == proc_sym)
1368     return true;
1369
1370   /* The same is true if context is a contained procedure and sym the
1371      containing one.  */
1372   if (context_proc->attr.contained)
1373     {
1374       gfc_symbol* parent_proc;
1375
1376       gcc_assert (context->parent);
1377       parent_proc = (context->parent->entries ? context->parent->entries->sym
1378                                               : context->parent->proc_name);
1379
1380       if (parent_proc == proc_sym)
1381         return true;
1382     }
1383
1384   return false;
1385 }
1386
1387
1388 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1389    its typespec and formal argument list.  */
1390
1391 static gfc_try
1392 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1393 {
1394   gfc_intrinsic_sym* isym;
1395   const char* symstd;
1396
1397   if (sym->formal)
1398     return SUCCESS;
1399
1400   /* We already know this one is an intrinsic, so we don't call
1401      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1402      gfc_find_subroutine directly to check whether it is a function or
1403      subroutine.  */
1404
1405   if ((isym = gfc_find_function (sym->name)))
1406     {
1407       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1408           && !sym->attr.implicit_type)
1409         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1410                       " ignored", sym->name, &sym->declared_at);
1411
1412       if (!sym->attr.function &&
1413           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1414         return FAILURE;
1415
1416       sym->ts = isym->ts;
1417     }
1418   else if ((isym = gfc_find_subroutine (sym->name)))
1419     {
1420       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1421         {
1422           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1423                       " specifier", sym->name, &sym->declared_at);
1424           return FAILURE;
1425         }
1426
1427       if (!sym->attr.subroutine &&
1428           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1429         return FAILURE;
1430     }
1431   else
1432     {
1433       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1434                  &sym->declared_at);
1435       return FAILURE;
1436     }
1437
1438   gfc_copy_formal_args_intr (sym, isym);
1439
1440   /* Check it is actually available in the standard settings.  */
1441   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1442       == FAILURE)
1443     {
1444       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1445                  " available in the current standard settings but %s.  Use"
1446                  " an appropriate -std=* option or enable -fall-intrinsics"
1447                  " in order to use it.",
1448                  sym->name, &sym->declared_at, symstd);
1449       return FAILURE;
1450     }
1451
1452   return SUCCESS;
1453 }
1454
1455
1456 /* Resolve a procedure expression, like passing it to a called procedure or as
1457    RHS for a procedure pointer assignment.  */
1458
1459 static gfc_try
1460 resolve_procedure_expression (gfc_expr* expr)
1461 {
1462   gfc_symbol* sym;
1463
1464   if (expr->expr_type != EXPR_VARIABLE)
1465     return SUCCESS;
1466   gcc_assert (expr->symtree);
1467
1468   sym = expr->symtree->n.sym;
1469
1470   if (sym->attr.intrinsic)
1471     resolve_intrinsic (sym, &expr->where);
1472
1473   if (sym->attr.flavor != FL_PROCEDURE
1474       || (sym->attr.function && sym->result == sym))
1475     return SUCCESS;
1476
1477   /* A non-RECURSIVE procedure that is used as procedure expression within its
1478      own body is in danger of being called recursively.  */
1479   if (is_illegal_recursion (sym, gfc_current_ns))
1480     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1481                  " itself recursively.  Declare it RECURSIVE or use"
1482                  " -frecursive", sym->name, &expr->where);
1483   
1484   return SUCCESS;
1485 }
1486
1487
1488 /* Resolve an actual argument list.  Most of the time, this is just
1489    resolving the expressions in the list.
1490    The exception is that we sometimes have to decide whether arguments
1491    that look like procedure arguments are really simple variable
1492    references.  */
1493
1494 static gfc_try
1495 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1496                         bool no_formal_args)
1497 {
1498   gfc_symbol *sym;
1499   gfc_symtree *parent_st;
1500   gfc_expr *e;
1501   int save_need_full_assumed_size;
1502   gfc_component *comp;
1503
1504   for (; arg; arg = arg->next)
1505     {
1506       e = arg->expr;
1507       if (e == NULL)
1508         {
1509           /* Check the label is a valid branching target.  */
1510           if (arg->label)
1511             {
1512               if (arg->label->defined == ST_LABEL_UNKNOWN)
1513                 {
1514                   gfc_error ("Label %d referenced at %L is never defined",
1515                              arg->label->value, &arg->label->where);
1516                   return FAILURE;
1517                 }
1518             }
1519           continue;
1520         }
1521
1522       if (gfc_is_proc_ptr_comp (e, &comp))
1523         {
1524           e->ts = comp->ts;
1525           if (e->expr_type == EXPR_PPC)
1526             {
1527               if (comp->as != NULL)
1528                 e->rank = comp->as->rank;
1529               e->expr_type = EXPR_FUNCTION;
1530             }
1531           if (gfc_resolve_expr (e) == FAILURE)                          
1532             return FAILURE; 
1533           goto argument_list;
1534         }
1535
1536       if (e->expr_type == EXPR_VARIABLE
1537             && e->symtree->n.sym->attr.generic
1538             && no_formal_args
1539             && count_specific_procs (e) != 1)
1540         return FAILURE;
1541
1542       if (e->ts.type != BT_PROCEDURE)
1543         {
1544           save_need_full_assumed_size = need_full_assumed_size;
1545           if (e->expr_type != EXPR_VARIABLE)
1546             need_full_assumed_size = 0;
1547           if (gfc_resolve_expr (e) != SUCCESS)
1548             return FAILURE;
1549           need_full_assumed_size = save_need_full_assumed_size;
1550           goto argument_list;
1551         }
1552
1553       /* See if the expression node should really be a variable reference.  */
1554
1555       sym = e->symtree->n.sym;
1556
1557       if (sym->attr.flavor == FL_PROCEDURE
1558           || sym->attr.intrinsic
1559           || sym->attr.external)
1560         {
1561           int actual_ok;
1562
1563           /* If a procedure is not already determined to be something else
1564              check if it is intrinsic.  */
1565           if (!sym->attr.intrinsic
1566               && !(sym->attr.external || sym->attr.use_assoc
1567                    || sym->attr.if_source == IFSRC_IFBODY)
1568               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1569             sym->attr.intrinsic = 1;
1570
1571           if (sym->attr.proc == PROC_ST_FUNCTION)
1572             {
1573               gfc_error ("Statement function '%s' at %L is not allowed as an "
1574                          "actual argument", sym->name, &e->where);
1575             }
1576
1577           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1578                                                sym->attr.subroutine);
1579           if (sym->attr.intrinsic && actual_ok == 0)
1580             {
1581               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1582                          "actual argument", sym->name, &e->where);
1583             }
1584
1585           if (sym->attr.contained && !sym->attr.use_assoc
1586               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1587             {
1588               gfc_error ("Internal procedure '%s' is not allowed as an "
1589                          "actual argument at %L", sym->name, &e->where);
1590             }
1591
1592           if (sym->attr.elemental && !sym->attr.intrinsic)
1593             {
1594               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1595                          "allowed as an actual argument at %L", sym->name,
1596                          &e->where);
1597             }
1598
1599           /* Check if a generic interface has a specific procedure
1600             with the same name before emitting an error.  */
1601           if (sym->attr.generic && count_specific_procs (e) != 1)
1602             return FAILURE;
1603           
1604           /* Just in case a specific was found for the expression.  */
1605           sym = e->symtree->n.sym;
1606
1607           /* If the symbol is the function that names the current (or
1608              parent) scope, then we really have a variable reference.  */
1609
1610           if (gfc_is_function_return_value (sym, sym->ns))
1611             goto got_variable;
1612
1613           /* If all else fails, see if we have a specific intrinsic.  */
1614           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1615             {
1616               gfc_intrinsic_sym *isym;
1617
1618               isym = gfc_find_function (sym->name);
1619               if (isym == NULL || !isym->specific)
1620                 {
1621                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1622                              "for the reference '%s' at %L", sym->name,
1623                              &e->where);
1624                   return FAILURE;
1625                 }
1626               sym->ts = isym->ts;
1627               sym->attr.intrinsic = 1;
1628               sym->attr.function = 1;
1629             }
1630
1631           if (gfc_resolve_expr (e) == FAILURE)
1632             return FAILURE;
1633           goto argument_list;
1634         }
1635
1636       /* See if the name is a module procedure in a parent unit.  */
1637
1638       if (was_declared (sym) || sym->ns->parent == NULL)
1639         goto got_variable;
1640
1641       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1642         {
1643           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1644           return FAILURE;
1645         }
1646
1647       if (parent_st == NULL)
1648         goto got_variable;
1649
1650       sym = parent_st->n.sym;
1651       e->symtree = parent_st;           /* Point to the right thing.  */
1652
1653       if (sym->attr.flavor == FL_PROCEDURE
1654           || sym->attr.intrinsic
1655           || sym->attr.external)
1656         {
1657           if (gfc_resolve_expr (e) == FAILURE)
1658             return FAILURE;
1659           goto argument_list;
1660         }
1661
1662     got_variable:
1663       e->expr_type = EXPR_VARIABLE;
1664       e->ts = sym->ts;
1665       if (sym->as != NULL)
1666         {
1667           e->rank = sym->as->rank;
1668           e->ref = gfc_get_ref ();
1669           e->ref->type = REF_ARRAY;
1670           e->ref->u.ar.type = AR_FULL;
1671           e->ref->u.ar.as = sym->as;
1672         }
1673
1674       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1675          primary.c (match_actual_arg). If above code determines that it
1676          is a  variable instead, it needs to be resolved as it was not
1677          done at the beginning of this function.  */
1678       save_need_full_assumed_size = need_full_assumed_size;
1679       if (e->expr_type != EXPR_VARIABLE)
1680         need_full_assumed_size = 0;
1681       if (gfc_resolve_expr (e) != SUCCESS)
1682         return FAILURE;
1683       need_full_assumed_size = save_need_full_assumed_size;
1684
1685     argument_list:
1686       /* Check argument list functions %VAL, %LOC and %REF.  There is
1687          nothing to do for %REF.  */
1688       if (arg->name && arg->name[0] == '%')
1689         {
1690           if (strncmp ("%VAL", arg->name, 4) == 0)
1691             {
1692               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1693                 {
1694                   gfc_error ("By-value argument at %L is not of numeric "
1695                              "type", &e->where);
1696                   return FAILURE;
1697                 }
1698
1699               if (e->rank)
1700                 {
1701                   gfc_error ("By-value argument at %L cannot be an array or "
1702                              "an array section", &e->where);
1703                 return FAILURE;
1704                 }
1705
1706               /* Intrinsics are still PROC_UNKNOWN here.  However,
1707                  since same file external procedures are not resolvable
1708                  in gfortran, it is a good deal easier to leave them to
1709                  intrinsic.c.  */
1710               if (ptype != PROC_UNKNOWN
1711                   && ptype != PROC_DUMMY
1712                   && ptype != PROC_EXTERNAL
1713                   && ptype != PROC_MODULE)
1714                 {
1715                   gfc_error ("By-value argument at %L is not allowed "
1716                              "in this context", &e->where);
1717                   return FAILURE;
1718                 }
1719             }
1720
1721           /* Statement functions have already been excluded above.  */
1722           else if (strncmp ("%LOC", arg->name, 4) == 0
1723                    && e->ts.type == BT_PROCEDURE)
1724             {
1725               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1726                 {
1727                   gfc_error ("Passing internal procedure at %L by location "
1728                              "not allowed", &e->where);
1729                   return FAILURE;
1730                 }
1731             }
1732         }
1733
1734       /* Fortran 2008, C1237.  */
1735       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1736           && gfc_has_ultimate_pointer (e))
1737         {
1738           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1739                      "component", &e->where);
1740           return FAILURE;
1741         }
1742     }
1743
1744   return SUCCESS;
1745 }
1746
1747
1748 /* Do the checks of the actual argument list that are specific to elemental
1749    procedures.  If called with c == NULL, we have a function, otherwise if
1750    expr == NULL, we have a subroutine.  */
1751
1752 static gfc_try
1753 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1754 {
1755   gfc_actual_arglist *arg0;
1756   gfc_actual_arglist *arg;
1757   gfc_symbol *esym = NULL;
1758   gfc_intrinsic_sym *isym = NULL;
1759   gfc_expr *e = NULL;
1760   gfc_intrinsic_arg *iformal = NULL;
1761   gfc_formal_arglist *eformal = NULL;
1762   bool formal_optional = false;
1763   bool set_by_optional = false;
1764   int i;
1765   int rank = 0;
1766
1767   /* Is this an elemental procedure?  */
1768   if (expr && expr->value.function.actual != NULL)
1769     {
1770       if (expr->value.function.esym != NULL
1771           && expr->value.function.esym->attr.elemental)
1772         {
1773           arg0 = expr->value.function.actual;
1774           esym = expr->value.function.esym;
1775         }
1776       else if (expr->value.function.isym != NULL
1777                && expr->value.function.isym->elemental)
1778         {
1779           arg0 = expr->value.function.actual;
1780           isym = expr->value.function.isym;
1781         }
1782       else
1783         return SUCCESS;
1784     }
1785   else if (c && c->ext.actual != NULL)
1786     {
1787       arg0 = c->ext.actual;
1788       
1789       if (c->resolved_sym)
1790         esym = c->resolved_sym;
1791       else
1792         esym = c->symtree->n.sym;
1793       gcc_assert (esym);
1794
1795       if (!esym->attr.elemental)
1796         return SUCCESS;
1797     }
1798   else
1799     return SUCCESS;
1800
1801   /* The rank of an elemental is the rank of its array argument(s).  */
1802   for (arg = arg0; arg; arg = arg->next)
1803     {
1804       if (arg->expr != NULL && arg->expr->rank > 0)
1805         {
1806           rank = arg->expr->rank;
1807           if (arg->expr->expr_type == EXPR_VARIABLE
1808               && arg->expr->symtree->n.sym->attr.optional)
1809             set_by_optional = true;
1810
1811           /* Function specific; set the result rank and shape.  */
1812           if (expr)
1813             {
1814               expr->rank = rank;
1815               if (!expr->shape && arg->expr->shape)
1816                 {
1817                   expr->shape = gfc_get_shape (rank);
1818                   for (i = 0; i < rank; i++)
1819                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1820                 }
1821             }
1822           break;
1823         }
1824     }
1825
1826   /* If it is an array, it shall not be supplied as an actual argument
1827      to an elemental procedure unless an array of the same rank is supplied
1828      as an actual argument corresponding to a nonoptional dummy argument of
1829      that elemental procedure(12.4.1.5).  */
1830   formal_optional = false;
1831   if (isym)
1832     iformal = isym->formal;
1833   else
1834     eformal = esym->formal;
1835
1836   for (arg = arg0; arg; arg = arg->next)
1837     {
1838       if (eformal)
1839         {
1840           if (eformal->sym && eformal->sym->attr.optional)
1841             formal_optional = true;
1842           eformal = eformal->next;
1843         }
1844       else if (isym && iformal)
1845         {
1846           if (iformal->optional)
1847             formal_optional = true;
1848           iformal = iformal->next;
1849         }
1850       else if (isym)
1851         formal_optional = true;
1852
1853       if (pedantic && arg->expr != NULL
1854           && arg->expr->expr_type == EXPR_VARIABLE
1855           && arg->expr->symtree->n.sym->attr.optional
1856           && formal_optional
1857           && arg->expr->rank
1858           && (set_by_optional || arg->expr->rank != rank)
1859           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1860         {
1861           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1862                        "MISSING, it cannot be the actual argument of an "
1863                        "ELEMENTAL procedure unless there is a non-optional "
1864                        "argument with the same rank (12.4.1.5)",
1865                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1866           return FAILURE;
1867         }
1868     }
1869
1870   for (arg = arg0; arg; arg = arg->next)
1871     {
1872       if (arg->expr == NULL || arg->expr->rank == 0)
1873         continue;
1874
1875       /* Being elemental, the last upper bound of an assumed size array
1876          argument must be present.  */
1877       if (resolve_assumed_size_actual (arg->expr))
1878         return FAILURE;
1879
1880       /* Elemental procedure's array actual arguments must conform.  */
1881       if (e != NULL)
1882         {
1883           if (gfc_check_conformance (arg->expr, e,
1884                                      "elemental procedure") == FAILURE)
1885             return FAILURE;
1886         }
1887       else
1888         e = arg->expr;
1889     }
1890
1891   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1892      is an array, the intent inout/out variable needs to be also an array.  */
1893   if (rank > 0 && esym && expr == NULL)
1894     for (eformal = esym->formal, arg = arg0; arg && eformal;
1895          arg = arg->next, eformal = eformal->next)
1896       if ((eformal->sym->attr.intent == INTENT_OUT
1897            || eformal->sym->attr.intent == INTENT_INOUT)
1898           && arg->expr && arg->expr->rank == 0)
1899         {
1900           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1901                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1902                      "actual argument is an array", &arg->expr->where,
1903                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1904                      : "INOUT", eformal->sym->name, esym->name);
1905           return FAILURE;
1906         }
1907   return SUCCESS;
1908 }
1909
1910
1911 /* Go through each actual argument in ACTUAL and see if it can be
1912    implemented as an inlined, non-copying intrinsic.  FNSYM is the
1913    function being called, or NULL if not known.  */
1914
1915 static void
1916 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1917 {
1918   gfc_actual_arglist *ap;
1919   gfc_expr *expr;
1920
1921   for (ap = actual; ap; ap = ap->next)
1922     if (ap->expr
1923         && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1924         && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual,
1925                                          NOT_ELEMENTAL))
1926       ap->expr->inline_noncopying_intrinsic = 1;
1927 }
1928
1929
1930 /* This function does the checking of references to global procedures
1931    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1932    77 and 95 standards.  It checks for a gsymbol for the name, making
1933    one if it does not already exist.  If it already exists, then the
1934    reference being resolved must correspond to the type of gsymbol.
1935    Otherwise, the new symbol is equipped with the attributes of the
1936    reference.  The corresponding code that is called in creating
1937    global entities is parse.c.
1938
1939    In addition, for all but -std=legacy, the gsymbols are used to
1940    check the interfaces of external procedures from the same file.
1941    The namespace of the gsymbol is resolved and then, once this is
1942    done the interface is checked.  */
1943
1944
1945 static bool
1946 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1947 {
1948   if (!gsym_ns->proc_name->attr.recursive)
1949     return true;
1950
1951   if (sym->ns == gsym_ns)
1952     return false;
1953
1954   if (sym->ns->parent && sym->ns->parent == gsym_ns)
1955     return false;
1956
1957   return true;
1958 }
1959
1960 static bool
1961 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
1962 {
1963   if (gsym_ns->entries)
1964     {
1965       gfc_entry_list *entry = gsym_ns->entries;
1966
1967       for (; entry; entry = entry->next)
1968         {
1969           if (strcmp (sym->name, entry->sym->name) == 0)
1970             {
1971               if (strcmp (gsym_ns->proc_name->name,
1972                           sym->ns->proc_name->name) == 0)
1973                 return false;
1974
1975               if (sym->ns->parent
1976                   && strcmp (gsym_ns->proc_name->name,
1977                              sym->ns->parent->proc_name->name) == 0)
1978                 return false;
1979             }
1980         }
1981     }
1982   return true;
1983 }
1984
1985 static void
1986 resolve_global_procedure (gfc_symbol *sym, locus *where,
1987                           gfc_actual_arglist **actual, int sub)
1988 {
1989   gfc_gsymbol * gsym;
1990   gfc_namespace *ns;
1991   enum gfc_symbol_type type;
1992
1993   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1994
1995   gsym = gfc_get_gsymbol (sym->name);
1996
1997   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1998     gfc_global_used (gsym, where);
1999
2000   if (gfc_option.flag_whole_file
2001         && (sym->attr.if_source == IFSRC_UNKNOWN
2002             || sym->attr.if_source == IFSRC_IFBODY)
2003         && gsym->type != GSYM_UNKNOWN
2004         && gsym->ns
2005         && gsym->ns->resolved != -1
2006         && gsym->ns->proc_name
2007         && not_in_recursive (sym, gsym->ns)
2008         && not_entry_self_reference (sym, gsym->ns))
2009     {
2010       gfc_symbol *def_sym;
2011
2012       /* Resolve the gsymbol namespace if needed.  */
2013       if (!gsym->ns->resolved)
2014         {
2015           gfc_dt_list *old_dt_list;
2016
2017           /* Stash away derived types so that the backend_decls do not
2018              get mixed up.  */
2019           old_dt_list = gfc_derived_types;
2020           gfc_derived_types = NULL;
2021
2022           gfc_resolve (gsym->ns);
2023
2024           /* Store the new derived types with the global namespace.  */
2025           if (gfc_derived_types)
2026             gsym->ns->derived_types = gfc_derived_types;
2027
2028           /* Restore the derived types of this namespace.  */
2029           gfc_derived_types = old_dt_list;
2030         }
2031
2032       /* Make sure that translation for the gsymbol occurs before
2033          the procedure currently being resolved.  */
2034       ns = gfc_global_ns_list;
2035       for (; ns && ns != gsym->ns; ns = ns->sibling)
2036         {
2037           if (ns->sibling == gsym->ns)
2038             {
2039               ns->sibling = gsym->ns->sibling;
2040               gsym->ns->sibling = gfc_global_ns_list;
2041               gfc_global_ns_list = gsym->ns;
2042               break;
2043             }
2044         }
2045
2046       def_sym = gsym->ns->proc_name;
2047       if (def_sym->attr.entry_master)
2048         {
2049           gfc_entry_list *entry;
2050           for (entry = gsym->ns->entries; entry; entry = entry->next)
2051             if (strcmp (entry->sym->name, sym->name) == 0)
2052               {
2053                 def_sym = entry->sym;
2054                 break;
2055               }
2056         }
2057
2058       /* Differences in constant character lengths.  */
2059       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
2060         {
2061           long int l1 = 0, l2 = 0;
2062           gfc_charlen *cl1 = sym->ts.u.cl;
2063           gfc_charlen *cl2 = def_sym->ts.u.cl;
2064
2065           if (cl1 != NULL
2066               && cl1->length != NULL
2067               && cl1->length->expr_type == EXPR_CONSTANT)
2068             l1 = mpz_get_si (cl1->length->value.integer);
2069
2070           if (cl2 != NULL
2071               && cl2->length != NULL
2072               && cl2->length->expr_type == EXPR_CONSTANT)
2073             l2 = mpz_get_si (cl2->length->value.integer);
2074
2075           if (l1 && l2 && l1 != l2)
2076             gfc_error ("Character length mismatch in return type of "
2077                        "function '%s' at %L (%ld/%ld)", sym->name,
2078                        &sym->declared_at, l1, l2);
2079         }
2080
2081      /* Type mismatch of function return type and expected type.  */
2082      if (sym->attr.function
2083          && !gfc_compare_types (&sym->ts, &def_sym->ts))
2084         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
2085                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2086                    gfc_typename (&def_sym->ts));
2087
2088       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
2089         {
2090           gfc_formal_arglist *arg = def_sym->formal;
2091           for ( ; arg; arg = arg->next)
2092             if (!arg->sym)
2093               continue;
2094             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
2095             else if (arg->sym->attr.allocatable
2096                      || arg->sym->attr.asynchronous
2097                      || arg->sym->attr.optional
2098                      || arg->sym->attr.pointer
2099                      || arg->sym->attr.target
2100                      || arg->sym->attr.value
2101                      || arg->sym->attr.volatile_)
2102               {
2103                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
2104                            "has an attribute that requires an explicit "
2105                            "interface for this procedure", arg->sym->name,
2106                            sym->name, &sym->declared_at);
2107                 break;
2108               }
2109             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
2110             else if (arg->sym && arg->sym->as
2111                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
2112               {
2113                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
2114                            "argument '%s' must have an explicit interface",
2115                            sym->name, &sym->declared_at, arg->sym->name);
2116                 break;
2117               }
2118             /* F2008, 12.4.2.2 (2c)  */
2119             else if (arg->sym->attr.codimension)
2120               {
2121                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
2122                            "'%s' must have an explicit interface",
2123                            sym->name, &sym->declared_at, arg->sym->name);
2124                 break;
2125               }
2126             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
2127             else if (false) /* TODO: is a parametrized derived type  */
2128               {
2129                 gfc_error ("Procedure '%s' at %L with parametrized derived "
2130                            "type argument '%s' must have an explicit "
2131                            "interface", sym->name, &sym->declared_at,
2132                            arg->sym->name);
2133                 break;
2134               }
2135             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
2136             else if (arg->sym->ts.type == BT_CLASS)
2137               {
2138                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
2139                            "argument '%s' must have an explicit interface",
2140                            sym->name, &sym->declared_at, arg->sym->name);
2141                 break;
2142               }
2143         }
2144
2145       if (def_sym->attr.function)
2146         {
2147           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
2148           if (def_sym->as && def_sym->as->rank
2149               && (!sym->as || sym->as->rank != def_sym->as->rank))
2150             gfc_error ("The reference to function '%s' at %L either needs an "
2151                        "explicit INTERFACE or the rank is incorrect", sym->name,
2152                        where);
2153
2154           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
2155           if ((def_sym->result->attr.pointer
2156                || def_sym->result->attr.allocatable)
2157                && (sym->attr.if_source != IFSRC_IFBODY
2158                    || def_sym->result->attr.pointer
2159                         != sym->result->attr.pointer
2160                    || def_sym->result->attr.allocatable
2161                         != sym->result->attr.allocatable))
2162             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
2163                        "result must have an explicit interface", sym->name,
2164                        where);
2165
2166           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
2167           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
2168               && def_sym->ts.u.cl->length != NULL)
2169             {
2170               gfc_charlen *cl = sym->ts.u.cl;
2171
2172               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
2173                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
2174                 {
2175                   gfc_error ("Nonconstant character-length function '%s' at %L "
2176                              "must have an explicit interface", sym->name,
2177                              &sym->declared_at);
2178                 }
2179             }
2180         }
2181
2182       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2183       if (def_sym->attr.elemental && !sym->attr.elemental)
2184         {
2185           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2186                      "interface", sym->name, &sym->declared_at);
2187         }
2188
2189       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2190       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2191         {
2192           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2193                      "an explicit interface", sym->name, &sym->declared_at);
2194         }
2195
2196       if (gfc_option.flag_whole_file == 1
2197           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2198               && !(gfc_option.warn_std & GFC_STD_GNU)))
2199         gfc_errors_to_warnings (1);
2200
2201       if (sym->attr.if_source != IFSRC_IFBODY)  
2202         gfc_procedure_use (def_sym, actual, where);
2203
2204       gfc_errors_to_warnings (0);
2205     }
2206
2207   if (gsym->type == GSYM_UNKNOWN)
2208     {
2209       gsym->type = type;
2210       gsym->where = *where;
2211     }
2212
2213   gsym->used = 1;
2214 }
2215
2216
2217 /************* Function resolution *************/
2218
2219 /* Resolve a function call known to be generic.
2220    Section 14.1.2.4.1.  */
2221
2222 static match
2223 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2224 {
2225   gfc_symbol *s;
2226
2227   if (sym->attr.generic)
2228     {
2229       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2230       if (s != NULL)
2231         {
2232           expr->value.function.name = s->name;
2233           expr->value.function.esym = s;
2234
2235           if (s->ts.type != BT_UNKNOWN)
2236             expr->ts = s->ts;
2237           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2238             expr->ts = s->result->ts;
2239
2240           if (s->as != NULL)
2241             expr->rank = s->as->rank;
2242           else if (s->result != NULL && s->result->as != NULL)
2243             expr->rank = s->result->as->rank;
2244
2245           gfc_set_sym_referenced (expr->value.function.esym);
2246
2247           return MATCH_YES;
2248         }
2249
2250       /* TODO: Need to search for elemental references in generic
2251          interface.  */
2252     }
2253
2254   if (sym->attr.intrinsic)
2255     return gfc_intrinsic_func_interface (expr, 0);
2256
2257   return MATCH_NO;
2258 }
2259
2260
2261 static gfc_try
2262 resolve_generic_f (gfc_expr *expr)
2263 {
2264   gfc_symbol *sym;
2265   match m;
2266
2267   sym = expr->symtree->n.sym;
2268
2269   for (;;)
2270     {
2271       m = resolve_generic_f0 (expr, sym);
2272       if (m == MATCH_YES)
2273         return SUCCESS;
2274       else if (m == MATCH_ERROR)
2275         return FAILURE;
2276
2277 generic:
2278       if (sym->ns->parent == NULL)
2279         break;
2280       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2281
2282       if (sym == NULL)
2283         break;
2284       if (!generic_sym (sym))
2285         goto generic;
2286     }
2287
2288   /* Last ditch attempt.  See if the reference is to an intrinsic
2289      that possesses a matching interface.  14.1.2.4  */
2290   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
2291     {
2292       gfc_error ("There is no specific function for the generic '%s' at %L",
2293                  expr->symtree->n.sym->name, &expr->where);
2294       return FAILURE;
2295     }
2296
2297   m = gfc_intrinsic_func_interface (expr, 0);
2298   if (m == MATCH_YES)
2299     return SUCCESS;
2300   if (m == MATCH_NO)
2301     gfc_error ("Generic function '%s' at %L is not consistent with a "
2302                "specific intrinsic interface", expr->symtree->n.sym->name,
2303                &expr->where);
2304
2305   return FAILURE;
2306 }
2307
2308
2309 /* Resolve a function call known to be specific.  */
2310
2311 static match
2312 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2313 {
2314   match m;
2315
2316   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2317     {
2318       if (sym->attr.dummy)
2319         {
2320           sym->attr.proc = PROC_DUMMY;
2321           goto found;
2322         }
2323
2324       sym->attr.proc = PROC_EXTERNAL;
2325       goto found;
2326     }
2327
2328   if (sym->attr.proc == PROC_MODULE
2329       || sym->attr.proc == PROC_ST_FUNCTION
2330       || sym->attr.proc == PROC_INTERNAL)
2331     goto found;
2332
2333   if (sym->attr.intrinsic)
2334     {
2335       m = gfc_intrinsic_func_interface (expr, 1);
2336       if (m == MATCH_YES)
2337         return MATCH_YES;
2338       if (m == MATCH_NO)
2339         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2340                    "with an intrinsic", sym->name, &expr->where);
2341
2342       return MATCH_ERROR;
2343     }
2344
2345   return MATCH_NO;
2346
2347 found:
2348   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2349
2350   if (sym->result)
2351     expr->ts = sym->result->ts;
2352   else
2353     expr->ts = sym->ts;
2354   expr->value.function.name = sym->name;
2355   expr->value.function.esym = sym;
2356   if (sym->as != NULL)
2357     expr->rank = sym->as->rank;
2358
2359   return MATCH_YES;
2360 }
2361
2362
2363 static gfc_try
2364 resolve_specific_f (gfc_expr *expr)
2365 {
2366   gfc_symbol *sym;
2367   match m;
2368
2369   sym = expr->symtree->n.sym;
2370
2371   for (;;)
2372     {
2373       m = resolve_specific_f0 (sym, expr);
2374       if (m == MATCH_YES)
2375         return SUCCESS;
2376       if (m == MATCH_ERROR)
2377         return FAILURE;
2378
2379       if (sym->ns->parent == NULL)
2380         break;
2381
2382       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2383
2384       if (sym == NULL)
2385         break;
2386     }
2387
2388   gfc_error ("Unable to resolve the specific function '%s' at %L",
2389              expr->symtree->n.sym->name, &expr->where);
2390
2391   return SUCCESS;
2392 }
2393
2394
2395 /* Resolve a procedure call not known to be generic nor specific.  */
2396
2397 static gfc_try
2398 resolve_unknown_f (gfc_expr *expr)
2399 {
2400   gfc_symbol *sym;
2401   gfc_typespec *ts;
2402
2403   sym = expr->symtree->n.sym;
2404
2405   if (sym->attr.dummy)
2406     {
2407       sym->attr.proc = PROC_DUMMY;
2408       expr->value.function.name = sym->name;
2409       goto set_type;
2410     }
2411
2412   /* See if we have an intrinsic function reference.  */
2413
2414   if (gfc_is_intrinsic (sym, 0, expr->where))
2415     {
2416       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2417         return SUCCESS;
2418       return FAILURE;
2419     }
2420
2421   /* The reference is to an external name.  */
2422
2423   sym->attr.proc = PROC_EXTERNAL;
2424   expr->value.function.name = sym->name;
2425   expr->value.function.esym = expr->symtree->n.sym;
2426
2427   if (sym->as != NULL)
2428     expr->rank = sym->as->rank;
2429
2430   /* Type of the expression is either the type of the symbol or the
2431      default type of the symbol.  */
2432
2433 set_type:
2434   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2435
2436   if (sym->ts.type != BT_UNKNOWN)
2437     expr->ts = sym->ts;
2438   else
2439     {
2440       ts = gfc_get_default_type (sym->name, sym->ns);
2441
2442       if (ts->type == BT_UNKNOWN)
2443         {
2444           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2445                      sym->name, &expr->where);
2446           return FAILURE;
2447         }
2448       else
2449         expr->ts = *ts;
2450     }
2451
2452   return SUCCESS;
2453 }
2454
2455
2456 /* Return true, if the symbol is an external procedure.  */
2457 static bool
2458 is_external_proc (gfc_symbol *sym)
2459 {
2460   if (!sym->attr.dummy && !sym->attr.contained
2461         && !(sym->attr.intrinsic
2462               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2463         && sym->attr.proc != PROC_ST_FUNCTION
2464         && !sym->attr.proc_pointer
2465         && !sym->attr.use_assoc
2466         && sym->name)
2467     return true;
2468
2469   return false;
2470 }
2471
2472
2473 /* Figure out if a function reference is pure or not.  Also set the name
2474    of the function for a potential error message.  Return nonzero if the
2475    function is PURE, zero if not.  */
2476 static int
2477 pure_stmt_function (gfc_expr *, gfc_symbol *);
2478
2479 static int
2480 pure_function (gfc_expr *e, const char **name)
2481 {
2482   int pure;
2483
2484   *name = NULL;
2485
2486   if (e->symtree != NULL
2487         && e->symtree->n.sym != NULL
2488         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2489     return pure_stmt_function (e, e->symtree->n.sym);
2490
2491   if (e->value.function.esym)
2492     {
2493       pure = gfc_pure (e->value.function.esym);
2494       *name = e->value.function.esym->name;
2495     }
2496   else if (e->value.function.isym)
2497     {
2498       pure = e->value.function.isym->pure
2499              || e->value.function.isym->elemental;
2500       *name = e->value.function.isym->name;
2501     }
2502   else
2503     {
2504       /* Implicit functions are not pure.  */
2505       pure = 0;
2506       *name = e->value.function.name;
2507     }
2508
2509   return pure;
2510 }
2511
2512
2513 static bool
2514 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2515                  int *f ATTRIBUTE_UNUSED)
2516 {
2517   const char *name;
2518
2519   /* Don't bother recursing into other statement functions
2520      since they will be checked individually for purity.  */
2521   if (e->expr_type != EXPR_FUNCTION
2522         || !e->symtree
2523         || e->symtree->n.sym == sym
2524         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2525     return false;
2526
2527   return pure_function (e, &name) ? false : true;
2528 }
2529
2530
2531 static int
2532 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2533 {
2534   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2535 }
2536
2537
2538 static gfc_try
2539 is_scalar_expr_ptr (gfc_expr *expr)
2540 {
2541   gfc_try retval = SUCCESS;
2542   gfc_ref *ref;
2543   int start;
2544   int end;
2545
2546   /* See if we have a gfc_ref, which means we have a substring, array
2547      reference, or a component.  */
2548   if (expr->ref != NULL)
2549     {
2550       ref = expr->ref;
2551       while (ref->next != NULL)
2552         ref = ref->next;
2553
2554       switch (ref->type)
2555         {
2556         case REF_SUBSTRING:
2557           if (ref->u.ss.length != NULL 
2558               && ref->u.ss.length->length != NULL
2559               && ref->u.ss.start
2560               && ref->u.ss.start->expr_type == EXPR_CONSTANT 
2561               && ref->u.ss.end
2562               && ref->u.ss.end->expr_type == EXPR_CONSTANT)
2563             {
2564               start = (int) mpz_get_si (ref->u.ss.start->value.integer);
2565               end = (int) mpz_get_si (ref->u.ss.end->value.integer);
2566               if (end - start + 1 != 1)
2567                 retval = FAILURE;
2568             }
2569           else
2570             retval = FAILURE;
2571           break;
2572         case REF_ARRAY:
2573           if (ref->u.ar.type == AR_ELEMENT)
2574             retval = SUCCESS;
2575           else if (ref->u.ar.type == AR_FULL)
2576             {
2577               /* The user can give a full array if the array is of size 1.  */
2578               if (ref->u.ar.as != NULL
2579                   && ref->u.ar.as->rank == 1
2580                   && ref->u.ar.as->type == AS_EXPLICIT
2581                   && ref->u.ar.as->lower[0] != NULL
2582                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2583                   && ref->u.ar.as->upper[0] != NULL
2584                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2585                 {
2586                   /* If we have a character string, we need to check if
2587                      its length is one.  */
2588                   if (expr->ts.type == BT_CHARACTER)
2589                     {
2590                       if (expr->ts.u.cl == NULL
2591                           || expr->ts.u.cl->length == NULL
2592                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2593                           != 0)
2594                         retval = FAILURE;
2595                     }
2596                   else
2597                     {
2598                       /* We have constant lower and upper bounds.  If the
2599                          difference between is 1, it can be considered a
2600                          scalar.  */
2601                       start = (int) mpz_get_si
2602                                 (ref->u.ar.as->lower[0]->value.integer);
2603                       end = (int) mpz_get_si
2604                                 (ref->u.ar.as->upper[0]->value.integer);
2605                       if (end - start + 1 != 1)
2606                         retval = FAILURE;
2607                    }
2608                 }
2609               else
2610                 retval = FAILURE;
2611             }
2612           else
2613             retval = FAILURE;
2614           break;
2615         default:
2616           retval = SUCCESS;
2617           break;
2618         }
2619     }
2620   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2621     {
2622       /* Character string.  Make sure it's of length 1.  */
2623       if (expr->ts.u.cl == NULL
2624           || expr->ts.u.cl->length == NULL
2625           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2626         retval = FAILURE;
2627     }
2628   else if (expr->rank != 0)
2629     retval = FAILURE;
2630
2631   return retval;
2632 }
2633
2634
2635 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2636    and, in the case of c_associated, set the binding label based on
2637    the arguments.  */
2638
2639 static gfc_try
2640 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2641                           gfc_symbol **new_sym)
2642 {
2643   char name[GFC_MAX_SYMBOL_LEN + 1];
2644   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2645   int optional_arg = 0;
2646   gfc_try retval = SUCCESS;
2647   gfc_symbol *args_sym;
2648   gfc_typespec *arg_ts;
2649   symbol_attribute arg_attr;
2650
2651   if (args->expr->expr_type == EXPR_CONSTANT
2652       || args->expr->expr_type == EXPR_OP
2653       || args->expr->expr_type == EXPR_NULL)
2654     {
2655       gfc_error ("Argument to '%s' at %L is not a variable",
2656                  sym->name, &(args->expr->where));
2657       return FAILURE;
2658     }
2659
2660   args_sym = args->expr->symtree->n.sym;
2661
2662   /* The typespec for the actual arg should be that stored in the expr
2663      and not necessarily that of the expr symbol (args_sym), because
2664      the actual expression could be a part-ref of the expr symbol.  */
2665   arg_ts = &(args->expr->ts);
2666   arg_attr = gfc_expr_attr (args->expr);
2667     
2668   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2669     {
2670       /* If the user gave two args then they are providing something for
2671          the optional arg (the second cptr).  Therefore, set the name and
2672          binding label to the c_associated for two cptrs.  Otherwise,
2673          set c_associated to expect one cptr.  */
2674       if (args->next)
2675         {
2676           /* two args.  */
2677           sprintf (name, "%s_2", sym->name);
2678           sprintf (binding_label, "%s_2", sym->binding_label);
2679           optional_arg = 1;
2680         }
2681       else
2682         {
2683           /* one arg.  */
2684           sprintf (name, "%s_1", sym->name);
2685           sprintf (binding_label, "%s_1", sym->binding_label);
2686           optional_arg = 0;
2687         }
2688
2689       /* Get a new symbol for the version of c_associated that
2690          will get called.  */
2691       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2692     }
2693   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2694            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2695     {
2696       sprintf (name, "%s", sym->name);
2697       sprintf (binding_label, "%s", sym->binding_label);
2698
2699       /* Error check the call.  */
2700       if (args->next != NULL)
2701         {
2702           gfc_error_now ("More actual than formal arguments in '%s' "
2703                          "call at %L", name, &(args->expr->where));
2704           retval = FAILURE;
2705         }
2706       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2707         {
2708           /* Make sure we have either the target or pointer attribute.  */
2709           if (!arg_attr.target && !arg_attr.pointer)
2710             {
2711               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2712                              "a TARGET or an associated pointer",
2713                              args_sym->name,
2714                              sym->name, &(args->expr->where));
2715               retval = FAILURE;
2716             }
2717
2718           /* See if we have interoperable type and type param.  */
2719           if (verify_c_interop (arg_ts) == SUCCESS
2720               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2721             {
2722               if (args_sym->attr.target == 1)
2723                 {
2724                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2725                      has the target attribute and is interoperable.  */
2726                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2727                      allocatable variable that has the TARGET attribute and
2728                      is not an array of zero size.  */
2729                   if (args_sym->attr.allocatable == 1)
2730                     {
2731                       if (args_sym->attr.dimension != 0 
2732                           && (args_sym->as && args_sym->as->rank == 0))
2733                         {
2734                           gfc_error_now ("Allocatable variable '%s' used as a "
2735                                          "parameter to '%s' at %L must not be "
2736                                          "an array of zero size",
2737                                          args_sym->name, sym->name,
2738                                          &(args->expr->where));
2739                           retval = FAILURE;
2740                         }
2741                     }
2742                   else
2743                     {
2744                       /* A non-allocatable target variable with C
2745                          interoperable type and type parameters must be
2746                          interoperable.  */
2747                       if (args_sym && args_sym->attr.dimension)
2748                         {
2749                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2750                             {
2751                               gfc_error ("Assumed-shape array '%s' at %L "
2752                                          "cannot be an argument to the "
2753                                          "procedure '%s' because "
2754                                          "it is not C interoperable",
2755                                          args_sym->name,
2756                                          &(args->expr->where), sym->name);
2757                               retval = FAILURE;
2758                             }
2759                           else if (args_sym->as->type == AS_DEFERRED)
2760                             {
2761                               gfc_error ("Deferred-shape array '%s' at %L "
2762                                          "cannot be an argument to the "
2763                                          "procedure '%s' because "
2764                                          "it is not C interoperable",
2765                                          args_sym->name,
2766                                          &(args->expr->where), sym->name);
2767                               retval = FAILURE;
2768                             }
2769                         }
2770                               
2771                       /* Make sure it's not a character string.  Arrays of
2772                          any type should be ok if the variable is of a C
2773                          interoperable type.  */
2774                       if (arg_ts->type == BT_CHARACTER)
2775                         if (arg_ts->u.cl != NULL
2776                             && (arg_ts->u.cl->length == NULL
2777                                 || arg_ts->u.cl->length->expr_type
2778                                    != EXPR_CONSTANT
2779                                 || mpz_cmp_si
2780                                     (arg_ts->u.cl->length->value.integer, 1)
2781                                    != 0)
2782                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2783                           {
2784                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2785                                            "at %L must have a length of 1",
2786                                            args_sym->name, sym->name,
2787                                            &(args->expr->where));
2788                             retval = FAILURE;
2789                           }
2790                     }
2791                 }
2792               else if (arg_attr.pointer
2793                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2794                 {
2795                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2796                      scalar pointer.  */
2797                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2798                                  "associated scalar POINTER", args_sym->name,
2799                                  sym->name, &(args->expr->where));
2800                   retval = FAILURE;
2801                 }
2802             }
2803           else
2804             {
2805               /* The parameter is not required to be C interoperable.  If it
2806                  is not C interoperable, it must be a nonpolymorphic scalar
2807                  with no length type parameters.  It still must have either
2808                  the pointer or target attribute, and it can be
2809                  allocatable (but must be allocated when c_loc is called).  */
2810               if (args->expr->rank != 0 
2811                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2812                 {
2813                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2814                                  "scalar", args_sym->name, sym->name,
2815                                  &(args->expr->where));
2816                   retval = FAILURE;
2817                 }
2818               else if (arg_ts->type == BT_CHARACTER 
2819                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2820                 {
2821                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2822                                  "%L must have a length of 1",
2823                                  args_sym->name, sym->name,
2824                                  &(args->expr->where));
2825                   retval = FAILURE;
2826                 }
2827               else if (arg_ts->type == BT_CLASS)
2828                 {
2829                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
2830                                  "polymorphic", args_sym->name, sym->name,
2831                                  &(args->expr->where));
2832                   retval = FAILURE;
2833                 }
2834             }
2835         }
2836       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2837         {
2838           if (args_sym->attr.flavor != FL_PROCEDURE)
2839             {
2840               /* TODO: Update this error message to allow for procedure
2841                  pointers once they are implemented.  */
2842               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2843                              "procedure",
2844                              args_sym->name, sym->name,
2845                              &(args->expr->where));
2846               retval = FAILURE;
2847             }
2848           else if (args_sym->attr.is_bind_c != 1)
2849             {
2850               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2851                              "BIND(C)",
2852                              args_sym->name, sym->name,
2853                              &(args->expr->where));
2854               retval = FAILURE;
2855             }
2856         }
2857       
2858       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2859       *new_sym = sym;
2860     }
2861   else
2862     {
2863       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2864                           "iso_c_binding function: '%s'!\n", sym->name);
2865     }
2866
2867   return retval;
2868 }
2869
2870
2871 /* Resolve a function call, which means resolving the arguments, then figuring
2872    out which entity the name refers to.  */
2873 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2874    to INTENT(OUT) or INTENT(INOUT).  */
2875
2876 static gfc_try
2877 resolve_function (gfc_expr *expr)
2878 {
2879   gfc_actual_arglist *arg;
2880   gfc_symbol *sym;
2881   const char *name;
2882   gfc_try t;
2883   int temp;
2884   procedure_type p = PROC_INTRINSIC;
2885   bool no_formal_args;
2886
2887   sym = NULL;
2888   if (expr->symtree)
2889     sym = expr->symtree->n.sym;
2890
2891   /* If this is a procedure pointer component, it has already been resolved.  */
2892   if (gfc_is_proc_ptr_comp (expr, NULL))
2893     return SUCCESS;
2894   
2895   if (sym && sym->attr.intrinsic
2896       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2897     return FAILURE;
2898
2899   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2900     {
2901       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2902       return FAILURE;
2903     }
2904
2905   /* If this ia a deferred TBP with an abstract interface (which may
2906      of course be referenced), expr->value.function.esym will be set.  */
2907   if (sym && sym->attr.abstract && !expr->value.function.esym)
2908     {
2909       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2910                  sym->name, &expr->where);
2911       return FAILURE;
2912     }
2913
2914   /* Switch off assumed size checking and do this again for certain kinds
2915      of procedure, once the procedure itself is resolved.  */
2916   need_full_assumed_size++;
2917
2918   if (expr->symtree && expr->symtree->n.sym)
2919     p = expr->symtree->n.sym->attr.proc;
2920
2921   if (expr->value.function.isym && expr->value.function.isym->inquiry)
2922     inquiry_argument = true;
2923   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2924
2925   if (resolve_actual_arglist (expr->value.function.actual,
2926                               p, no_formal_args) == FAILURE)
2927     {
2928       inquiry_argument = false;
2929       return FAILURE;
2930     }
2931
2932   inquiry_argument = false;
2933  
2934   /* Need to setup the call to the correct c_associated, depending on
2935      the number of cptrs to user gives to compare.  */
2936   if (sym && sym->attr.is_iso_c == 1)
2937     {
2938       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2939           == FAILURE)
2940         return FAILURE;
2941       
2942       /* Get the symtree for the new symbol (resolved func).
2943          the old one will be freed later, when it's no longer used.  */
2944       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2945     }
2946   
2947   /* Resume assumed_size checking.  */
2948   need_full_assumed_size--;
2949
2950   /* If the procedure is external, check for usage.  */
2951   if (sym && is_external_proc (sym))
2952     resolve_global_procedure (sym, &expr->where,
2953                               &expr->value.function.actual, 0);
2954
2955   if (sym && sym->ts.type == BT_CHARACTER
2956       && sym->ts.u.cl
2957       && sym->ts.u.cl->length == NULL
2958       && !sym->attr.dummy
2959       && expr->value.function.esym == NULL
2960       && !sym->attr.contained)
2961     {
2962       /* Internal procedures are taken care of in resolve_contained_fntype.  */
2963       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2964                  "be used at %L since it is not a dummy argument",
2965                  sym->name, &expr->where);
2966       return FAILURE;
2967     }
2968
2969   /* See if function is already resolved.  */
2970
2971   if (expr->value.function.name != NULL)
2972     {
2973       if (expr->ts.type == BT_UNKNOWN)
2974         expr->ts = sym->ts;
2975       t = SUCCESS;
2976     }
2977   else
2978     {
2979       /* Apply the rules of section 14.1.2.  */
2980
2981       switch (procedure_kind (sym))
2982         {
2983         case PTYPE_GENERIC:
2984           t = resolve_generic_f (expr);
2985           break;
2986
2987         case PTYPE_SPECIFIC:
2988           t = resolve_specific_f (expr);
2989           break;
2990
2991         case PTYPE_UNKNOWN:
2992           t = resolve_unknown_f (expr);
2993           break;
2994
2995         default:
2996           gfc_internal_error ("resolve_function(): bad function type");
2997         }
2998     }
2999
3000   /* If the expression is still a function (it might have simplified),
3001      then we check to see if we are calling an elemental function.  */
3002
3003   if (expr->expr_type != EXPR_FUNCTION)
3004     return t;
3005
3006   temp = need_full_assumed_size;
3007   need_full_assumed_size = 0;
3008
3009   if (resolve_elemental_actual (expr, NULL) == FAILURE)
3010     return FAILURE;
3011
3012   if (omp_workshare_flag
3013       && expr->value.function.esym
3014       && ! gfc_elemental (expr->value.function.esym))
3015     {
3016       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
3017                  "in WORKSHARE construct", expr->value.function.esym->name,
3018                  &expr->where);
3019       t = FAILURE;
3020     }
3021
3022 #define GENERIC_ID expr->value.function.isym->id
3023   else if (expr->value.function.actual != NULL
3024            && expr->value.function.isym != NULL
3025            && GENERIC_ID != GFC_ISYM_LBOUND
3026            && GENERIC_ID != GFC_ISYM_LEN
3027            && GENERIC_ID != GFC_ISYM_LOC
3028            && GENERIC_ID != GFC_ISYM_PRESENT)
3029     {
3030       /* Array intrinsics must also have the last upper bound of an
3031          assumed size array argument.  UBOUND and SIZE have to be
3032          excluded from the check if the second argument is anything
3033          than a constant.  */
3034
3035       for (arg = expr->value.function.actual; arg; arg = arg->next)
3036         {
3037           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3038               && arg->next != NULL && arg->next->expr)
3039             {
3040               if (arg->next->expr->expr_type != EXPR_CONSTANT)
3041                 break;
3042
3043               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
3044                 break;
3045
3046               if ((int)mpz_get_si (arg->next->expr->value.integer)
3047                         < arg->expr->rank)
3048                 break;
3049             }
3050
3051           if (arg->expr != NULL
3052               && arg->expr->rank > 0
3053               && resolve_assumed_size_actual (arg->expr))
3054             return FAILURE;
3055         }
3056     }
3057 #undef GENERIC_ID
3058
3059   need_full_assumed_size = temp;
3060   name = NULL;
3061
3062   if (!pure_function (expr, &name) && name)
3063     {
3064       if (forall_flag)
3065         {
3066           gfc_error ("reference to non-PURE function '%s' at %L inside a "
3067                      "FORALL %s", name, &expr->where,
3068                      forall_flag == 2 ? "mask" : "block");
3069           t = FAILURE;
3070         }
3071       else if (gfc_pure (NULL))
3072         {
3073           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
3074                      "procedure within a PURE procedure", name, &expr->where);
3075           t = FAILURE;
3076         }
3077     }
3078
3079   /* Functions without the RECURSIVE attribution are not allowed to
3080    * call themselves.  */
3081   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3082     {
3083       gfc_symbol *esym;
3084       esym = expr->value.function.esym;
3085
3086       if (is_illegal_recursion (esym, gfc_current_ns))
3087       {
3088         if (esym->attr.entry && esym->ns->entries)
3089           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3090                      " function '%s' is not RECURSIVE",
3091                      esym->name, &expr->where, esym->ns->entries->sym->name);
3092         else
3093           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
3094                      " is not RECURSIVE", esym->name, &expr->where);
3095
3096         t = FAILURE;
3097       }
3098     }
3099
3100   /* Character lengths of use associated functions may contains references to
3101      symbols not referenced from the current program unit otherwise.  Make sure
3102      those symbols are marked as referenced.  */
3103
3104   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3105       && expr->value.function.esym->attr.use_assoc)
3106     {
3107       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3108     }
3109
3110   if (t == SUCCESS
3111         && !((expr->value.function.esym
3112                 && expr->value.function.esym->attr.elemental)
3113                         ||
3114              (expr->value.function.isym
3115                 && expr->value.function.isym->elemental)))
3116     find_noncopying_intrinsics (expr->value.function.esym,
3117                                 expr->value.function.actual);
3118
3119   /* Make sure that the expression has a typespec that works.  */
3120   if (expr->ts.type == BT_UNKNOWN)
3121     {
3122       if (expr->symtree->n.sym->result
3123             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3124             && !expr->symtree->n.sym->result->attr.proc_pointer)
3125         expr->ts = expr->symtree->n.sym->result->ts;
3126     }
3127
3128   return t;
3129 }
3130
3131
3132 /************* Subroutine resolution *************/
3133
3134 static void
3135 pure_subroutine (gfc_code *c, gfc_symbol *sym)
3136 {
3137   if (gfc_pure (sym))
3138     return;
3139
3140   if (forall_flag)
3141     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
3142                sym->name, &c->loc);
3143   else if (gfc_pure (NULL))
3144     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
3145                &c->loc);
3146 }
3147
3148
3149 static match
3150 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3151 {
3152   gfc_symbol *s;
3153
3154   if (sym->attr.generic)
3155     {
3156       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3157       if (s != NULL)
3158         {
3159           c->resolved_sym = s;
3160           pure_subroutine (c, s);
3161           return MATCH_YES;
3162         }
3163
3164       /* TODO: Need to search for elemental references in generic interface.  */
3165     }
3166
3167   if (sym->attr.intrinsic)
3168     return gfc_intrinsic_sub_interface (c, 0);
3169
3170   return MATCH_NO;
3171 }
3172
3173
3174 static gfc_try
3175 resolve_generic_s (gfc_code *c)
3176 {
3177   gfc_symbol *sym;
3178   match m;
3179
3180   sym = c->symtree->n.sym;
3181
3182   for (;;)
3183     {
3184       m = resolve_generic_s0 (c, sym);
3185       if (m == MATCH_YES)
3186         return SUCCESS;
3187       else if (m == MATCH_ERROR)
3188         return FAILURE;
3189
3190 generic:
3191       if (sym->ns->parent == NULL)
3192         break;
3193       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3194
3195       if (sym == NULL)
3196         break;
3197       if (!generic_sym (sym))
3198         goto generic;
3199     }
3200
3201   /* Last ditch attempt.  See if the reference is to an intrinsic
3202      that possesses a matching interface.  14.1.2.4  */
3203   sym = c->symtree->n.sym;
3204
3205   if (!gfc_is_intrinsic (sym, 1, c->loc))
3206     {
3207       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3208                  sym->name, &c->loc);
3209       return FAILURE;
3210     }
3211
3212   m = gfc_intrinsic_sub_interface (c, 0);
3213   if (m == MATCH_YES)
3214     return SUCCESS;
3215   if (m == MATCH_NO)
3216     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3217                "intrinsic subroutine interface", sym->name, &c->loc);
3218
3219   return FAILURE;
3220 }
3221
3222
3223 /* Set the name and binding label of the subroutine symbol in the call
3224    expression represented by 'c' to include the type and kind of the
3225    second parameter.  This function is for resolving the appropriate
3226    version of c_f_pointer() and c_f_procpointer().  For example, a
3227    call to c_f_pointer() for a default integer pointer could have a
3228    name of c_f_pointer_i4.  If no second arg exists, which is an error
3229    for these two functions, it defaults to the generic symbol's name
3230    and binding label.  */
3231
3232 static void
3233 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3234                     char *name, char *binding_label)
3235 {
3236   gfc_expr *arg = NULL;
3237   char type;
3238   int kind;
3239
3240   /* The second arg of c_f_pointer and c_f_procpointer determines
3241      the type and kind for the procedure name.  */
3242   arg = c->ext.actual->next->expr;
3243
3244   if (arg != NULL)
3245     {
3246       /* Set up the name to have the given symbol's name,
3247          plus the type and kind.  */
3248       /* a derived type is marked with the type letter 'u' */
3249       if (arg->ts.type == BT_DERIVED)
3250         {
3251           type = 'd';
3252           kind = 0; /* set the kind as 0 for now */
3253         }
3254       else
3255         {
3256           type = gfc_type_letter (arg->ts.type);
3257           kind = arg->ts.kind;
3258         }
3259
3260       if (arg->ts.type == BT_CHARACTER)
3261         /* Kind info for character strings not needed.  */
3262         kind = 0;
3263
3264       sprintf (name, "%s_%c%d", sym->name, type, kind);
3265       /* Set up the binding label as the given symbol's label plus
3266          the type and kind.  */
3267       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
3268     }
3269   else
3270     {
3271       /* If the second arg is missing, set the name and label as
3272          was, cause it should at least be found, and the missing
3273          arg error will be caught by compare_parameters().  */
3274       sprintf (name, "%s", sym->name);
3275       sprintf (binding_label, "%s", sym->binding_label);
3276     }
3277    
3278   return;
3279 }
3280
3281
3282 /* Resolve a generic version of the iso_c_binding procedure given
3283    (sym) to the specific one based on the type and kind of the
3284    argument(s).  Currently, this function resolves c_f_pointer() and
3285    c_f_procpointer based on the type and kind of the second argument
3286    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3287    Upon successfully exiting, c->resolved_sym will hold the resolved
3288    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3289    otherwise.  */
3290
3291 match
3292 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3293 {
3294   gfc_symbol *new_sym;
3295   /* this is fine, since we know the names won't use the max */
3296   char name[GFC_MAX_SYMBOL_LEN + 1];
3297   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3298   /* default to success; will override if find error */
3299   match m = MATCH_YES;
3300
3301   /* Make sure the actual arguments are in the necessary order (based on the 
3302      formal args) before resolving.  */
3303   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3304
3305   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3306       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3307     {
3308       set_name_and_label (c, sym, name, binding_label);
3309       
3310       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3311         {
3312           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3313             {
3314               /* Make sure we got a third arg if the second arg has non-zero
3315                  rank.  We must also check that the type and rank are
3316                  correct since we short-circuit this check in
3317                  gfc_procedure_use() (called above to sort actual args).  */
3318               if (c->ext.actual->next->expr->rank != 0)
3319                 {
3320                   if(c->ext.actual->next->next == NULL 
3321                      || c->ext.actual->next->next->expr == NULL)
3322                     {
3323                       m = MATCH_ERROR;
3324                       gfc_error ("Missing SHAPE parameter for call to %s "
3325                                  "at %L", sym->name, &(c->loc));
3326                     }
3327                   else if (c->ext.actual->next->next->expr->ts.type
3328                            != BT_INTEGER
3329                            || c->ext.actual->next->next->expr->rank != 1)
3330                     {
3331                       m = MATCH_ERROR;
3332                       gfc_error ("SHAPE parameter for call to %s at %L must "
3333                                  "be a rank 1 INTEGER array", sym->name,
3334                                  &(c->loc));
3335                     }
3336                 }
3337             }
3338         }
3339       
3340       if (m != MATCH_ERROR)
3341         {
3342           /* the 1 means to add the optional arg to formal list */
3343           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3344          
3345           /* for error reporting, say it's declared where the original was */
3346           new_sym->declared_at = sym->declared_at;
3347         }
3348     }
3349   else
3350     {
3351       /* no differences for c_loc or c_funloc */
3352       new_sym = sym;
3353     }
3354
3355   /* set the resolved symbol */
3356   if (m != MATCH_ERROR)
3357     c->resolved_sym = new_sym;
3358   else
3359     c->resolved_sym = sym;
3360   
3361   return m;
3362 }
3363
3364
3365 /* Resolve a subroutine call known to be specific.  */
3366
3367 static match
3368 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3369 {
3370   match m;
3371
3372   if(sym->attr.is_iso_c)
3373     {
3374       m = gfc_iso_c_sub_interface (c,sym);
3375       return m;
3376     }
3377   
3378   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3379     {
3380       if (sym->attr.dummy)
3381         {
3382           sym->attr.proc = PROC_DUMMY;
3383           goto found;
3384         }
3385
3386       sym->attr.proc = PROC_EXTERNAL;
3387       goto found;
3388     }
3389
3390   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3391     goto found;
3392
3393   if (sym->attr.intrinsic)
3394     {
3395       m = gfc_intrinsic_sub_interface (c, 1);
3396       if (m == MATCH_YES)
3397         return MATCH_YES;
3398       if (m == MATCH_NO)
3399         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3400                    "with an intrinsic", sym->name, &c->loc);
3401
3402       return MATCH_ERROR;
3403     }
3404
3405   return MATCH_NO;
3406
3407 found:
3408   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3409
3410   c->resolved_sym = sym;
3411   pure_subroutine (c, sym);
3412
3413   return MATCH_YES;
3414 }
3415
3416
3417 static gfc_try
3418 resolve_specific_s (gfc_code *c)
3419 {
3420   gfc_symbol *sym;
3421   match m;
3422
3423   sym = c->symtree->n.sym;
3424
3425   for (;;)
3426     {
3427       m = resolve_specific_s0 (c, sym);
3428       if (m == MATCH_YES)
3429         return SUCCESS;
3430       if (m == MATCH_ERROR)
3431         return FAILURE;
3432
3433       if (sym->ns->parent == NULL)
3434         break;
3435
3436       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3437
3438       if (sym == NULL)
3439         break;
3440     }
3441
3442   sym = c->symtree->n.sym;
3443   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3444              sym->name, &c->loc);
3445
3446   return FAILURE;
3447 }
3448
3449
3450 /* Resolve a subroutine call not known to be generic nor specific.  */
3451
3452 static gfc_try
3453 resolve_unknown_s (gfc_code *c)
3454 {
3455   gfc_symbol *sym;
3456
3457   sym = c->symtree->n.sym;
3458
3459   if (sym->attr.dummy)
3460     {
3461       sym->attr.proc = PROC_DUMMY;
3462       goto found;
3463     }
3464
3465   /* See if we have an intrinsic function reference.  */
3466
3467   if (gfc_is_intrinsic (sym, 1, c->loc))
3468     {
3469       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3470         return SUCCESS;
3471       return FAILURE;
3472     }
3473
3474   /* The reference is to an external name.  */
3475
3476 found:
3477   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3478
3479   c->resolved_sym = sym;
3480
3481   pure_subroutine (c, sym);
3482
3483   return SUCCESS;
3484 }
3485
3486
3487 /* Resolve a subroutine call.  Although it was tempting to use the same code
3488    for functions, subroutines and functions are stored differently and this
3489    makes things awkward.  */
3490
3491 static gfc_try
3492 resolve_call (gfc_code *c)
3493 {
3494   gfc_try t;
3495   procedure_type ptype = PROC_INTRINSIC;
3496   gfc_symbol *csym, *sym;
3497   bool no_formal_args;
3498
3499   csym = c->symtree ? c->symtree->n.sym : NULL;
3500
3501   if (csym && csym->ts.type != BT_UNKNOWN)
3502     {
3503       gfc_error ("'%s' at %L has a type, which is not consistent with "
3504                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3505       return FAILURE;
3506     }
3507
3508   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3509     {
3510       gfc_symtree *st;
3511       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3512       sym = st ? st->n.sym : NULL;
3513       if (sym && csym != sym
3514               && sym->ns == gfc_current_ns
3515               && sym->attr.flavor == FL_PROCEDURE
3516               && sym->attr.contained)
3517         {
3518           sym->refs++;
3519           if (csym->attr.generic)
3520             c->symtree->n.sym = sym;
3521           else
3522             c->symtree = st;
3523           csym = c->symtree->n.sym;
3524         }
3525     }
3526
3527   /* If this ia a deferred TBP with an abstract interface
3528      (which may of course be referenced), c->expr1 will be set.  */
3529   if (csym && csym->attr.abstract && !c->expr1)
3530     {
3531       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3532                  csym->name, &c->loc);
3533       return FAILURE;
3534     }
3535
3536   /* Subroutines without the RECURSIVE attribution are not allowed to
3537    * call themselves.  */
3538   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3539     {
3540       if (csym->attr.entry && csym->ns->entries)
3541         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3542                    " subroutine '%s' is not RECURSIVE",
3543                    csym->name, &c->loc, csym->ns->entries->sym->name);
3544       else
3545         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3546                    " is not RECURSIVE", csym->name, &c->loc);
3547
3548       t = FAILURE;
3549     }
3550
3551   /* Switch off assumed size checking and do this again for certain kinds
3552      of procedure, once the procedure itself is resolved.  */
3553   need_full_assumed_size++;
3554
3555   if (csym)
3556     ptype = csym->attr.proc;
3557
3558   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3559   if (resolve_actual_arglist (c->ext.actual, ptype,
3560                               no_formal_args) == FAILURE)
3561     return FAILURE;
3562
3563   /* Resume assumed_size checking.  */
3564   need_full_assumed_size--;
3565
3566   /* If external, check for usage.  */
3567   if (csym && is_external_proc (csym))
3568     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3569
3570   t = SUCCESS;
3571   if (c->resolved_sym == NULL)
3572     {
3573       c->resolved_isym = NULL;
3574       switch (procedure_kind (csym))
3575         {
3576         case PTYPE_GENERIC:
3577           t = resolve_generic_s (c);
3578           break;
3579
3580         case PTYPE_SPECIFIC:
3581           t = resolve_specific_s (c);
3582           break;
3583
3584         case PTYPE_UNKNOWN:
3585           t = resolve_unknown_s (c);
3586           break;
3587
3588         default:
3589           gfc_internal_error ("resolve_subroutine(): bad function type");
3590         }
3591     }
3592
3593   /* Some checks of elemental subroutine actual arguments.  */
3594   if (resolve_elemental_actual (NULL, c) == FAILURE)
3595     return FAILURE;
3596
3597   if (t == SUCCESS && !(c->resolved_sym && c->resolved_sym->attr.elemental))
3598     find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
3599   return t;
3600 }
3601
3602
3603 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3604    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3605    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3606    if their shapes do not match.  If either op1->shape or op2->shape is
3607    NULL, return SUCCESS.  */
3608
3609 static gfc_try
3610 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3611 {
3612   gfc_try t;
3613   int i;
3614
3615   t = SUCCESS;
3616
3617   if (op1->shape != NULL && op2->shape != NULL)
3618     {
3619       for (i = 0; i < op1->rank; i++)
3620         {
3621           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3622            {
3623              gfc_error ("Shapes for operands at %L and %L are not conformable",
3624                          &op1->where, &op2->where);
3625              t = FAILURE;
3626              break;
3627            }
3628         }
3629     }
3630
3631   return t;
3632 }
3633
3634
3635 /* Resolve an operator expression node.  This can involve replacing the
3636    operation with a user defined function call.  */
3637
3638 static gfc_try
3639 resolve_operator (gfc_expr *e)
3640 {
3641   gfc_expr *op1, *op2;
3642   char msg[200];
3643   bool dual_locus_error;
3644   gfc_try t;
3645
3646   /* Resolve all subnodes-- give them types.  */
3647
3648   switch (e->value.op.op)
3649     {
3650     default:
3651       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3652         return FAILURE;
3653
3654     /* Fall through...  */
3655
3656     case INTRINSIC_NOT:
3657     case INTRINSIC_UPLUS:
3658     case INTRINSIC_UMINUS:
3659     case INTRINSIC_PARENTHESES:
3660       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3661         return FAILURE;
3662       break;
3663     }
3664
3665   /* Typecheck the new node.  */
3666
3667   op1 = e->value.op.op1;
3668   op2 = e->value.op.op2;
3669   dual_locus_error = false;
3670
3671   if ((op1 && op1->expr_type == EXPR_NULL)
3672       || (op2 && op2->expr_type == EXPR_NULL))
3673     {
3674       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3675       goto bad_op;
3676     }
3677
3678   switch (e->value.op.op)
3679     {
3680     case INTRINSIC_UPLUS:
3681     case INTRINSIC_UMINUS:
3682       if (op1->ts.type == BT_INTEGER
3683           || op1->ts.type == BT_REAL
3684           || op1->ts.type == BT_COMPLEX)
3685         {
3686           e->ts = op1->ts;
3687           break;
3688         }
3689
3690       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3691                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3692       goto bad_op;
3693
3694     case INTRINSIC_PLUS:
3695     case INTRINSIC_MINUS:
3696     case INTRINSIC_TIMES:
3697     case INTRINSIC_DIVIDE:
3698     case INTRINSIC_POWER:
3699       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3700         {
3701           gfc_type_convert_binary (e, 1);
3702           break;
3703         }
3704
3705       sprintf (msg,
3706                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3707                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3708                gfc_typename (&op2->ts));
3709       goto bad_op;
3710
3711     case INTRINSIC_CONCAT:
3712       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3713           && op1->ts.kind == op2->ts.kind)
3714         {
3715           e->ts.type = BT_CHARACTER;
3716           e->ts.kind = op1->ts.kind;
3717           break;
3718         }
3719
3720       sprintf (msg,
3721                _("Operands of string concatenation operator at %%L are %s/%s"),
3722                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3723       goto bad_op;
3724
3725     case INTRINSIC_AND:
3726     case INTRINSIC_OR:
3727     case INTRINSIC_EQV:
3728     case INTRINSIC_NEQV:
3729       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3730         {
3731           e->ts.type = BT_LOGICAL;
3732           e->ts.kind = gfc_kind_max (op1, op2);
3733           if (op1->ts.kind < e->ts.kind)
3734             gfc_convert_type (op1, &e->ts, 2);
3735           else if (op2->ts.kind < e->ts.kind)
3736             gfc_convert_type (op2, &e->ts, 2);
3737           break;
3738         }
3739
3740       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3741                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3742                gfc_typename (&op2->ts));
3743
3744       goto bad_op;
3745
3746     case INTRINSIC_NOT:
3747       if (op1->ts.type == BT_LOGICAL)
3748         {
3749           e->ts.type = BT_LOGICAL;
3750           e->ts.kind = op1->ts.kind;
3751           break;
3752         }
3753
3754       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3755                gfc_typename (&op1->ts));
3756       goto bad_op;
3757
3758     case INTRINSIC_GT:
3759     case INTRINSIC_GT_OS:
3760     case INTRINSIC_GE:
3761     case INTRINSIC_GE_OS:
3762     case INTRINSIC_LT:
3763     case INTRINSIC_LT_OS:
3764     case INTRINSIC_LE:
3765     case INTRINSIC_LE_OS:
3766       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3767         {
3768           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3769           goto bad_op;
3770         }
3771
3772       /* Fall through...  */
3773
3774     case INTRINSIC_EQ:
3775     case INTRINSIC_EQ_OS:
3776     case INTRINSIC_NE:
3777     case INTRINSIC_NE_OS:
3778       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3779           && op1->ts.kind == op2->ts.kind)
3780         {
3781           e->ts.type = BT_LOGICAL;
3782           e->ts.kind = gfc_default_logical_kind;
3783           break;
3784         }
3785
3786       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3787         {
3788           gfc_type_convert_binary (e, 1);
3789
3790           e->ts.type = BT_LOGICAL;
3791           e->ts.kind = gfc_default_logical_kind;
3792           break;
3793         }
3794
3795       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3796         sprintf (msg,
3797                  _("Logicals at %%L must be compared with %s instead of %s"),
3798                  (e->value.op.op == INTRINSIC_EQ 
3799                   || e->value.op.op == INTRINSIC_EQ_OS)
3800                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3801       else
3802         sprintf (msg,
3803                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3804                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3805                  gfc_typename (&op2->ts));
3806
3807       goto bad_op;
3808
3809     case INTRINSIC_USER:
3810       if (e->value.op.uop->op == NULL)
3811         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3812       else if (op2 == NULL)
3813         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3814                  e->value.op.uop->name, gfc_typename (&op1->ts));
3815       else
3816         sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3817                  e->value.op.uop->name, gfc_typename (&op1->ts),
3818                  gfc_typename (&op2->ts));
3819
3820       goto bad_op;
3821
3822     case INTRINSIC_PARENTHESES:
3823       e->ts = op1->ts;
3824       if (e->ts.type == BT_CHARACTER)
3825         e->ts.u.cl = op1->ts.u.cl;
3826       break;
3827
3828     default:
3829       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3830     }
3831
3832   /* Deal with arrayness of an operand through an operator.  */
3833
3834   t = SUCCESS;
3835
3836   switch (e->value.op.op)
3837     {
3838     case INTRINSIC_PLUS:
3839     case INTRINSIC_MINUS:
3840     case INTRINSIC_TIMES:
3841     case INTRINSIC_DIVIDE:
3842     case INTRINSIC_POWER:
3843     case INTRINSIC_CONCAT:
3844     case INTRINSIC_AND:
3845     case INTRINSIC_OR:
3846     case INTRINSIC_EQV:
3847     case INTRINSIC_NEQV:
3848     case INTRINSIC_EQ:
3849     case INTRINSIC_EQ_OS:
3850     case INTRINSIC_NE:
3851     case INTRINSIC_NE_OS:
3852     case INTRINSIC_GT:
3853     case INTRINSIC_GT_OS:
3854     case INTRINSIC_GE:
3855     case INTRINSIC_GE_OS:
3856     case INTRINSIC_LT:
3857     case INTRINSIC_LT_OS:
3858     case INTRINSIC_LE:
3859     case INTRINSIC_LE_OS:
3860
3861       if (op1->rank == 0 && op2->rank == 0)
3862         e->rank = 0;
3863
3864       if (op1->rank == 0 && op2->rank != 0)
3865         {
3866           e->rank = op2->rank;
3867
3868           if (e->shape == NULL)
3869             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3870         }
3871
3872       if (op1->rank != 0 && op2->rank == 0)
3873         {
3874           e->rank = op1->rank;
3875
3876           if (e->shape == NULL)
3877             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3878         }
3879
3880       if (op1->rank != 0 && op2->rank != 0)
3881         {
3882           if (op1->rank == op2->rank)
3883             {
3884               e->rank = op1->rank;
3885               if (e->shape == NULL)
3886                 {
3887                   t = compare_shapes (op1, op2);
3888                   if (t == FAILURE)
3889                     e->shape = NULL;
3890                   else
3891                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
3892                 }
3893             }
3894           else
3895             {
3896               /* Allow higher level expressions to work.  */
3897               e->rank = 0;
3898
3899               /* Try user-defined operators, and otherwise throw an error.  */
3900               dual_locus_error = true;
3901               sprintf (msg,
3902                        _("Inconsistent ranks for operator at %%L and %%L"));
3903               goto bad_op;
3904             }
3905         }
3906
3907       break;
3908
3909     case INTRINSIC_PARENTHESES:
3910     case INTRINSIC_NOT:
3911     case INTRINSIC_UPLUS:
3912     case INTRINSIC_UMINUS:
3913       /* Simply copy arrayness attribute */
3914       e->rank = op1->rank;
3915
3916       if (e->shape == NULL)
3917         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3918
3919       break;
3920
3921     default:
3922       break;
3923     }
3924
3925   /* Attempt to simplify the expression.  */
3926   if (t == SUCCESS)
3927     {
3928       t = gfc_simplify_expr (e, 0);
3929       /* Some calls do not succeed in simplification and return FAILURE
3930          even though there is no error; e.g. variable references to
3931          PARAMETER arrays.  */
3932       if (!gfc_is_constant_expr (e))
3933         t = SUCCESS;
3934     }
3935   return t;
3936
3937 bad_op:
3938
3939   {
3940     bool real_error;
3941     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3942       return SUCCESS;
3943
3944     if (real_error)
3945       return FAILURE;
3946   }
3947
3948   if (dual_locus_error)
3949     gfc_error (msg, &op1->where, &op2->where);
3950   else
3951     gfc_error (msg, &e->where);
3952
3953   return FAILURE;
3954 }
3955
3956
3957 /************** Array resolution subroutines **************/
3958
3959 typedef enum
3960 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3961 comparison;
3962
3963 /* Compare two integer expressions.  */
3964
3965 static comparison
3966 compare_bound (gfc_expr *a, gfc_expr *b)
3967 {
3968   int i;
3969
3970   if (a == NULL || a->expr_type != EXPR_CONSTANT
3971       || b == NULL || b->expr_type != EXPR_CONSTANT)
3972     return CMP_UNKNOWN;
3973
3974   /* If either of the types isn't INTEGER, we must have
3975      raised an error earlier.  */
3976
3977   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3978     return CMP_UNKNOWN;
3979
3980   i = mpz_cmp (a->value.integer, b->value.integer);
3981
3982   if (i < 0)
3983     return CMP_LT;
3984   if (i > 0)
3985     return CMP_GT;
3986   return CMP_EQ;
3987 }
3988
3989
3990 /* Compare an integer expression with an integer.  */
3991
3992 static comparison
3993 compare_bound_int (gfc_expr *a, int b)
3994 {
3995   int i;
3996
3997   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3998     return CMP_UNKNOWN;
3999
4000   if (a->ts.type != BT_INTEGER)
4001     gfc_internal_error ("compare_bound_int(): Bad expression");
4002
4003   i = mpz_cmp_si (a->value.integer, b);
4004
4005   if (i < 0)
4006     return CMP_LT;
4007   if (i > 0)
4008     return CMP_GT;
4009   return CMP_EQ;
4010 }
4011
4012
4013 /* Compare an integer expression with a mpz_t.  */
4014
4015 static comparison
4016 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
4017 {
4018   int i;
4019
4020   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4021     return CMP_UNKNOWN;
4022
4023   if (a->ts.type != BT_INTEGER)
4024     gfc_internal_error ("compare_bound_int(): Bad expression");
4025
4026   i = mpz_cmp (a->value.integer, b);
4027
4028   if (i < 0)
4029     return CMP_LT;
4030   if (i > 0)
4031     return CMP_GT;
4032   return CMP_EQ;
4033 }
4034
4035
4036 /* Compute the last value of a sequence given by a triplet.  
4037    Return 0 if it wasn't able to compute the last value, or if the
4038    sequence if empty, and 1 otherwise.  */
4039
4040 static int
4041 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
4042                                 gfc_expr *stride, mpz_t last)
4043 {
4044   mpz_t rem;
4045
4046   if (start == NULL || start->expr_type != EXPR_CONSTANT
4047       || end == NULL || end->expr_type != EXPR_CONSTANT
4048       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
4049     return 0;
4050
4051   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
4052       || (stride != NULL && stride->ts.type != BT_INTEGER))
4053     return 0;
4054
4055   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
4056     {
4057       if (compare_bound (start, end) == CMP_GT)
4058         return 0;
4059       mpz_set (last, end->value.integer);
4060       return 1;
4061     }
4062
4063   if (compare_bound_int (stride, 0) == CMP_GT)
4064     {
4065       /* Stride is positive */
4066       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
4067         return 0;
4068     }
4069   else
4070     {
4071       /* Stride is negative */
4072       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
4073         return 0;
4074     }
4075
4076   mpz_init (rem);
4077   mpz_sub (rem, end->value.integer, start->value.integer);
4078   mpz_tdiv_r (rem, rem, stride->value.integer);
4079   mpz_sub (last, end->value.integer, rem);
4080   mpz_clear (rem);
4081
4082   return 1;
4083 }
4084
4085
4086 /* Compare a single dimension of an array reference to the array
4087    specification.  */
4088
4089 static gfc_try
4090 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
4091 {
4092   mpz_t last_value;
4093
4094   if (ar->dimen_type[i] == DIMEN_STAR)
4095     {
4096       gcc_assert (ar->stride[i] == NULL);
4097       /* This implies [*] as [*:] and [*:3] are not possible.  */
4098       if (ar->start[i] == NULL)
4099         {
4100           gcc_assert (ar->end[i] == NULL);
4101           return SUCCESS;
4102         }
4103     }
4104
4105 /* Given start, end and stride values, calculate the minimum and
4106    maximum referenced indexes.  */
4107
4108   switch (ar->dimen_type[i])
4109     {
4110     case DIMEN_VECTOR:
4111       break;
4112
4113     case DIMEN_STAR:
4114     case DIMEN_ELEMENT:
4115       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4116         {
4117           if (i < as->rank)
4118             gfc_warning ("Array reference at %L is out of bounds "
4119                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
4120                          mpz_get_si (ar->start[i]->value.integer),
4121                          mpz_get_si (as->lower[i]->value.integer), i+1);
4122           else
4123             gfc_warning ("Array reference at %L is out of bounds "
4124                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
4125                          mpz_get_si (ar->start[i]->value.integer),
4126                          mpz_get_si (as->lower[i]->value.integer),
4127                          i + 1 - as->rank);
4128           return SUCCESS;
4129         }
4130       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4131         {
4132           if (i < as->rank)
4133             gfc_warning ("Array reference at %L is out of bounds "
4134                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
4135                          mpz_get_si (ar->start[i]->value.integer),
4136                          mpz_get_si (as->upper[i]->value.integer), i+1);
4137           else
4138             gfc_warning ("Array reference at %L is out of bounds "
4139                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
4140                          mpz_get_si (ar->start[i]->value.integer),
4141                          mpz_get_si (as->upper[i]->value.integer),
4142                          i + 1 - as->rank);
4143           return SUCCESS;
4144         }
4145
4146       break;
4147
4148     case DIMEN_RANGE:
4149       {
4150 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4151 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4152
4153         comparison comp_start_end = compare_bound (AR_START, AR_END);
4154
4155         /* Check for zero stride, which is not allowed.  */
4156         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4157           {
4158             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4159             return FAILURE;
4160           }
4161
4162         /* if start == len || (stride > 0 && start < len)
4163                            || (stride < 0 && start > len),
4164            then the array section contains at least one element.  In this
4165            case, there is an out-of-bounds access if
4166            (start < lower || start > upper).  */
4167         if (compare_bound (AR_START, AR_END) == CMP_EQ
4168             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4169                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4170             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4171                 && comp_start_end == CMP_GT))
4172           {
4173             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4174               {
4175                 gfc_warning ("Lower array reference at %L is out of bounds "
4176                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4177                        mpz_get_si (AR_START->value.integer),
4178                        mpz_get_si (as->lower[i]->value.integer), i+1);
4179                 return SUCCESS;
4180               }
4181             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4182               {
4183                 gfc_warning ("Lower array reference at %L is out of bounds "
4184                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4185                        mpz_get_si (AR_START->value.integer),
4186                        mpz_get_si (as->upper[i]->value.integer), i+1);
4187                 return SUCCESS;
4188               }
4189           }
4190
4191         /* If we can compute the highest index of the array section,
4192            then it also has to be between lower and upper.  */
4193         mpz_init (last_value);
4194         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4195                                             last_value))
4196           {
4197             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4198               {
4199                 gfc_warning ("Upper array reference at %L is out of bounds "
4200                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4201                        mpz_get_si (last_value),
4202                        mpz_get_si (as->lower[i]->value.integer), i+1);
4203                 mpz_clear (last_value);
4204                 return SUCCESS;
4205               }
4206             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4207               {
4208                 gfc_warning ("Upper array reference at %L is out of bounds "
4209                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4210                        mpz_get_si (last_value),
4211                        mpz_get_si (as->upper[i]->value.integer), i+1);
4212                 mpz_clear (last_value);
4213                 return SUCCESS;
4214               }
4215           }
4216         mpz_clear (last_value);
4217
4218 #undef AR_START
4219 #undef AR_END
4220       }
4221       break;
4222
4223     default:
4224       gfc_internal_error ("check_dimension(): Bad array reference");
4225     }
4226
4227   return SUCCESS;
4228 }
4229
4230
4231 /* Compare an array reference with an array specification.  */
4232
4233 static gfc_try
4234 compare_spec_to_ref (gfc_array_ref *ar)
4235 {
4236   gfc_array_spec *as;
4237   int i;
4238
4239   as = ar->as;
4240   i = as->rank - 1;
4241   /* TODO: Full array sections are only allowed as actual parameters.  */
4242   if (as->type == AS_ASSUMED_SIZE
4243       && (/*ar->type == AR_FULL
4244           ||*/ (ar->type == AR_SECTION
4245               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4246     {
4247       gfc_error ("Rightmost upper bound of assumed size array section "
4248                  "not specified at %L", &ar->where);
4249       return FAILURE;
4250     }
4251
4252   if (ar->type == AR_FULL)
4253     return SUCCESS;
4254
4255   if (as->rank != ar->dimen)
4256     {
4257       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4258                  &ar->where, ar->dimen, as->rank);
4259       return FAILURE;
4260     }
4261
4262   /* ar->codimen == 0 is a local array.  */
4263   if (as->corank != ar->codimen && ar->codimen != 0)
4264     {
4265       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4266                  &ar->where, ar->codimen, as->corank);
4267       return FAILURE;
4268     }
4269
4270   for (i = 0; i < as->rank; i++)
4271     if (check_dimension (i, ar, as) == FAILURE)
4272       return FAILURE;
4273
4274   /* Local access has no coarray spec.  */
4275   if (ar->codimen != 0)
4276     for (i = as->rank; i < as->rank + as->corank; i++)
4277       {
4278         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate)
4279           {
4280             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4281                        i + 1 - as->rank, &ar->where);
4282             return FAILURE;
4283           }
4284         if (check_dimension (i, ar, as) == FAILURE)
4285           return FAILURE;
4286       }
4287
4288   return SUCCESS;
4289 }
4290
4291
4292 /* Resolve one part of an array index.  */
4293
4294 static gfc_try
4295 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4296                      int force_index_integer_kind)
4297 {
4298   gfc_typespec ts;
4299
4300   if (index == NULL)
4301     return SUCCESS;
4302
4303   if (gfc_resolve_expr (index) == FAILURE)
4304     return FAILURE;
4305
4306   if (check_scalar && index->rank != 0)
4307     {
4308       gfc_error ("Array index at %L must be scalar", &index->where);
4309       return FAILURE;
4310     }
4311
4312   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4313     {
4314       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4315                  &index->where, gfc_basic_typename (index->ts.type));
4316       return FAILURE;
4317     }
4318
4319   if (index->ts.type == BT_REAL)
4320     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4321                         &index->where) == FAILURE)
4322       return FAILURE;
4323
4324   if ((index->ts.kind != gfc_index_integer_kind
4325        && force_index_integer_kind)
4326       || index->ts.type != BT_INTEGER)
4327     {
4328       gfc_clear_ts (&ts);
4329       ts.type = BT_INTEGER;
4330       ts.kind = gfc_index_integer_kind;
4331
4332       gfc_convert_type_warn (index, &ts, 2, 0);
4333     }
4334
4335   return SUCCESS;
4336 }
4337
4338 /* Resolve one part of an array index.  */
4339
4340 gfc_try
4341 gfc_resolve_index (gfc_expr *index, int check_scalar)
4342 {
4343   return gfc_resolve_index_1 (index, check_scalar, 1);
4344 }
4345
4346 /* Resolve a dim argument to an intrinsic function.  */
4347
4348 gfc_try
4349 gfc_resolve_dim_arg (gfc_expr *dim)
4350 {
4351   if (dim == NULL)
4352     return SUCCESS;
4353
4354   if (gfc_resolve_expr (dim) == FAILURE)
4355     return FAILURE;
4356
4357   if (dim->rank != 0)
4358     {
4359       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4360       return FAILURE;
4361
4362     }
4363
4364   if (dim->ts.type != BT_INTEGER)
4365     {
4366       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4367       return FAILURE;
4368     }
4369
4370   if (dim->ts.kind != gfc_index_integer_kind)
4371     {
4372       gfc_typespec ts;
4373
4374       gfc_clear_ts (&ts);
4375       ts.type = BT_INTEGER;
4376       ts.kind = gfc_index_integer_kind;
4377
4378       gfc_convert_type_warn (dim, &ts, 2, 0);
4379     }
4380
4381   return SUCCESS;
4382 }
4383
4384 /* Given an expression that contains array references, update those array
4385    references to point to the right array specifications.  While this is
4386    filled in during matching, this information is difficult to save and load
4387    in a module, so we take care of it here.
4388
4389    The idea here is that the original array reference comes from the
4390    base symbol.  We traverse the list of reference structures, setting
4391    the stored reference to references.  Component references can
4392    provide an additional array specification.  */
4393
4394 static void
4395 find_array_spec (gfc_expr *e)
4396 {
4397   gfc_array_spec *as;
4398   gfc_component *c;
4399   gfc_symbol *derived;
4400   gfc_ref *ref;
4401
4402   if (e->symtree->n.sym->ts.type == BT_CLASS)
4403     as = CLASS_DATA (e->symtree->n.sym)->as;
4404   else
4405     as = e->symtree->n.sym->as;
4406   derived = NULL;
4407
4408   for (ref = e->ref; ref; ref = ref->next)
4409     switch (ref->type)
4410       {
4411       case REF_ARRAY:
4412         if (as == NULL)
4413           gfc_internal_error ("find_array_spec(): Missing spec");
4414
4415         ref->u.ar.as = as;
4416         as = NULL;
4417         break;
4418
4419       case REF_COMPONENT:
4420         if (derived == NULL)
4421           derived = e->symtree->n.sym->ts.u.derived;
4422
4423         if (derived->attr.is_class)
4424           derived = derived->components->ts.u.derived;
4425
4426         c = derived->components;
4427
4428         for (; c; c = c->next)
4429           if (c == ref->u.c.component)
4430             {
4431               /* Track the sequence of component references.  */
4432               if (c->ts.type == BT_DERIVED)
4433                 derived = c->ts.u.derived;
4434               break;
4435             }
4436
4437         if (c == NULL)
4438           gfc_internal_error ("find_array_spec(): Component not found");
4439
4440         if (c->attr.dimension)
4441           {
4442             if (as != NULL)
4443               gfc_internal_error ("find_array_spec(): unused as(1)");
4444             as = c->as;
4445           }
4446
4447         break;
4448
4449       case REF_SUBSTRING:
4450         break;
4451       }
4452
4453   if (as != NULL)
4454     gfc_internal_error ("find_array_spec(): unused as(2)");
4455 }
4456
4457
4458 /* Resolve an array reference.  */
4459
4460 static gfc_try
4461 resolve_array_ref (gfc_array_ref *ar)
4462 {
4463   int i, check_scalar;
4464   gfc_expr *e;
4465
4466   for (i = 0; i < ar->dimen + ar->codimen; i++)
4467     {
4468       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4469
4470       /* Do not force gfc_index_integer_kind for the start.  We can
4471          do fine with any integer kind.  This avoids temporary arrays
4472          created for indexing with a vector.  */
4473       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4474         return FAILURE;
4475       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4476         return FAILURE;
4477       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4478         return FAILURE;
4479
4480       e = ar->start[i];
4481
4482       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4483         switch (e->rank)
4484           {
4485           case 0:
4486             ar->dimen_type[i] = DIMEN_ELEMENT;
4487             break;
4488
4489           case 1:
4490             ar->dimen_type[i] = DIMEN_VECTOR;
4491             if (e->expr_type == EXPR_VARIABLE
4492                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4493               ar->start[i] = gfc_get_parentheses (e);
4494             break;
4495
4496           default:
4497             gfc_error ("Array index at %L is an array of rank %d",
4498                        &ar->c_where[i], e->rank);
4499             return FAILURE;
4500           }
4501
4502       /* Fill in the upper bound, which may be lower than the
4503          specified one for something like a(2:10:5), which is
4504          identical to a(2:7:5).  Only relevant for strides not equal
4505          to one.  */
4506       if (ar->dimen_type[i] == DIMEN_RANGE
4507           && ar->stride[i] != NULL && ar->stride[i]->expr_type == EXPR_CONSTANT
4508           && mpz_cmp_si (ar->stride[i]->value.integer, 1L) != 0)
4509         {
4510           mpz_t size, end;
4511
4512           if (gfc_ref_dimen_size (ar, i, &size, &end) == SUCCESS)
4513             {
4514               if (ar->end[i] == NULL)
4515                 {
4516                   ar->end[i] =
4517                     gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
4518                                            &ar->where);
4519                   mpz_set (ar->end[i]->value.integer, end);
4520                 }
4521               else if (ar->end[i]->ts.type == BT_INTEGER
4522                        && ar->end[i]->expr_type == EXPR_CONSTANT)
4523                 {
4524                   mpz_set (ar->end[i]->value.integer, end);
4525                 }
4526               else
4527                 gcc_unreachable ();
4528
4529               mpz_clear (size);
4530               mpz_clear (end);
4531             }
4532         }
4533     }
4534
4535   if (ar->type == AR_FULL && ar->as->rank == 0)
4536     ar->type = AR_ELEMENT;
4537
4538   /* If the reference type is unknown, figure out what kind it is.  */
4539
4540   if (ar->type == AR_UNKNOWN)
4541     {
4542       ar->type = AR_ELEMENT;
4543       for (i = 0; i < ar->dimen; i++)
4544         if (ar->dimen_type[i] == DIMEN_RANGE
4545             || ar->dimen_type[i] == DIMEN_VECTOR)
4546           {
4547             ar->type = AR_SECTION;
4548             break;
4549           }
4550     }
4551
4552   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4553     return FAILURE;
4554
4555   return SUCCESS;
4556 }
4557
4558
4559 static gfc_try
4560 resolve_substring (gfc_ref *ref)
4561 {
4562   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4563
4564   if (ref->u.ss.start != NULL)
4565     {
4566       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4567         return FAILURE;
4568
4569       if (ref->u.ss.start->ts.type != BT_INTEGER)
4570         {
4571           gfc_error ("Substring start index at %L must be of type INTEGER",
4572                      &ref->u.ss.start->where);
4573           return FAILURE;
4574         }
4575
4576       if (ref->u.ss.start->rank != 0)
4577         {
4578           gfc_error ("Substring start index at %L must be scalar",
4579                      &ref->u.ss.start->where);
4580           return FAILURE;
4581         }
4582
4583       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4584           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4585               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4586         {
4587           gfc_error ("Substring start index at %L is less than one",
4588                      &ref->u.ss.start->where);
4589           return FAILURE;
4590         }
4591     }
4592
4593   if (ref->u.ss.end != NULL)
4594     {
4595       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4596         return FAILURE;
4597
4598       if (ref->u.ss.end->ts.type != BT_INTEGER)
4599         {
4600           gfc_error ("Substring end index at %L must be of type INTEGER",
4601                      &ref->u.ss.end->where);
4602           return FAILURE;
4603         }
4604
4605       if (ref->u.ss.end->rank != 0)
4606         {
4607           gfc_error ("Substring end index at %L must be scalar",
4608                      &ref->u.ss.end->where);
4609           return FAILURE;
4610         }
4611
4612       if (ref->u.ss.length != NULL
4613           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4614           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4615               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4616         {
4617           gfc_error ("Substring end index at %L exceeds the string length",
4618                      &ref->u.ss.start->where);
4619           return FAILURE;
4620         }
4621
4622       if (compare_bound_mpz_t (ref->u.ss.end,
4623                                gfc_integer_kinds[k].huge) == CMP_GT
4624           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4625               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4626         {
4627           gfc_error ("Substring end index at %L is too large",
4628                      &ref->u.ss.end->where);
4629           return FAILURE;
4630         }
4631     }
4632
4633   return SUCCESS;
4634 }
4635
4636
4637 /* This function supplies missing substring charlens.  */
4638
4639 void
4640 gfc_resolve_substring_charlen (gfc_expr *e)
4641 {
4642   gfc_ref *char_ref;
4643   gfc_expr *start, *end;
4644
4645   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4646     if (char_ref->type == REF_SUBSTRING)
4647       break;
4648
4649   if (!char_ref)
4650     return;
4651
4652   gcc_assert (char_ref->next == NULL);
4653
4654   if (e->ts.u.cl)
4655     {
4656       if (e->ts.u.cl->length)
4657         gfc_free_expr (e->ts.u.cl->length);
4658       else if (e->expr_type == EXPR_VARIABLE
4659                  && e->symtree->n.sym->attr.dummy)
4660         return;
4661     }
4662
4663   e->ts.type = BT_CHARACTER;
4664   e->ts.kind = gfc_default_character_kind;
4665
4666   if (!e->ts.u.cl)
4667     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4668
4669   if (char_ref->u.ss.start)
4670     start = gfc_copy_expr (char_ref->u.ss.start);
4671   else
4672     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4673
4674   if (char_ref->u.ss.end)
4675     end = gfc_copy_expr (char_ref->u.ss.end);
4676   else if (e->expr_type == EXPR_VARIABLE)
4677     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4678   else
4679     end = NULL;
4680
4681   if (!start || !end)
4682     return;
4683
4684   /* Length = (end - start +1).  */
4685   e->ts.u.cl->length = gfc_subtract (end, start);
4686   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4687                                 gfc_get_int_expr (gfc_default_integer_kind,
4688                                                   NULL, 1));
4689
4690   e->ts.u.cl->length->ts.type = BT_INTEGER;
4691   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4692
4693   /* Make sure that the length is simplified.  */
4694   gfc_simplify_expr (e->ts.u.cl->length, 1);
4695   gfc_resolve_expr (e->ts.u.cl->length);
4696 }
4697
4698
4699 /* Resolve subtype references.  */
4700
4701 static gfc_try
4702 resolve_ref (gfc_expr *expr)
4703 {
4704   int current_part_dimension, n_components, seen_part_dimension;
4705   gfc_ref *ref;
4706
4707   for (ref = expr->ref; ref; ref = ref->next)
4708     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4709       {
4710         find_array_spec (expr);
4711         break;
4712       }
4713
4714   for (ref = expr->ref; ref; ref = ref->next)
4715     switch (ref->type)
4716       {
4717       case REF_ARRAY:
4718         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4719           return FAILURE;
4720         break;
4721
4722       case REF_COMPONENT:
4723         break;
4724
4725       case REF_SUBSTRING:
4726         resolve_substring (ref);
4727         break;
4728       }
4729
4730   /* Check constraints on part references.  */
4731
4732   current_part_dimension = 0;
4733   seen_part_dimension = 0;
4734   n_components = 0;
4735
4736   for (ref = expr->ref; ref; ref = ref->next)
4737     {
4738       switch (ref->type)
4739         {
4740         case REF_ARRAY:
4741           switch (ref->u.ar.type)
4742             {
4743             case AR_FULL:
4744               /* Coarray scalar.  */
4745               if (ref->u.ar.as->rank == 0)
4746                 {
4747                   current_part_dimension = 0;
4748                   break;
4749                 }
4750               /* Fall through.  */
4751             case AR_SECTION:
4752               current_part_dimension = 1;
4753               break;
4754
4755             case AR_ELEMENT:
4756               current_part_dimension = 0;
4757               break;
4758
4759             case AR_UNKNOWN:
4760               gfc_internal_error ("resolve_ref(): Bad array reference");
4761             }
4762
4763           break;
4764
4765         case REF_COMPONENT:
4766           if (current_part_dimension || seen_part_dimension)
4767             {
4768               /* F03:C614.  */
4769               if (ref->u.c.component->attr.pointer
4770                   || ref->u.c.component->attr.proc_pointer)
4771                 {
4772                   gfc_error ("Component to the right of a part reference "
4773                              "with nonzero rank must not have the POINTER "
4774                              "attribute at %L", &expr->where);
4775                   return FAILURE;
4776                 }
4777               else if (ref->u.c.component->attr.allocatable)
4778                 {
4779                   gfc_error ("Component to the right of a part reference "
4780                              "with nonzero rank must not have the ALLOCATABLE "
4781                              "attribute at %L", &expr->where);
4782                   return FAILURE;
4783                 }
4784             }
4785
4786           n_components++;
4787           break;
4788
4789         case REF_SUBSTRING:
4790           break;
4791         }
4792
4793       if (((ref->type == REF_COMPONENT && n_components > 1)
4794            || ref->next == NULL)
4795           && current_part_dimension
4796           && seen_part_dimension)
4797         {
4798           gfc_error ("Two or more part references with nonzero rank must "
4799                      "not be specified at %L", &expr->where);
4800           return FAILURE;
4801         }
4802
4803       if (ref->type == REF_COMPONENT)
4804         {
4805           if (current_part_dimension)
4806             seen_part_dimension = 1;
4807
4808           /* reset to make sure */
4809           current_part_dimension = 0;
4810         }
4811     }
4812
4813   return SUCCESS;
4814 }
4815
4816
4817 /* Given an expression, determine its shape.  This is easier than it sounds.
4818    Leaves the shape array NULL if it is not possible to determine the shape.  */
4819
4820 static void
4821 expression_shape (gfc_expr *e)
4822 {
4823   mpz_t array[GFC_MAX_DIMENSIONS];
4824   int i;
4825
4826   if (e->rank == 0 || e->shape != NULL)
4827     return;
4828
4829   for (i = 0; i < e->rank; i++)
4830     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4831       goto fail;
4832
4833   e->shape = gfc_get_shape (e->rank);
4834
4835   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4836
4837   return;
4838
4839 fail:
4840   for (i--; i >= 0; i--)
4841     mpz_clear (array[i]);
4842 }
4843
4844
4845 /* Given a variable expression node, compute the rank of the expression by
4846    examining the base symbol and any reference structures it may have.  */
4847
4848 static void
4849 expression_rank (gfc_expr *e)
4850 {
4851   gfc_ref *ref;
4852   int i, rank;
4853
4854   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4855      could lead to serious confusion...  */
4856   gcc_assert (e->expr_type != EXPR_COMPCALL);
4857
4858   if (e->ref == NULL)
4859     {
4860       if (e->expr_type == EXPR_ARRAY)
4861         goto done;
4862       /* Constructors can have a rank different from one via RESHAPE().  */
4863
4864       if (e->symtree == NULL)
4865         {
4866           e->rank = 0;
4867           goto done;
4868         }
4869
4870       e->rank = (e->symtree->n.sym->as == NULL)
4871                 ? 0 : e->symtree->n.sym->as->rank;
4872       goto done;
4873     }
4874
4875   rank = 0;
4876
4877   for (ref = e->ref; ref; ref = ref->next)
4878     {
4879       if (ref->type != REF_ARRAY)
4880         continue;
4881
4882       if (ref->u.ar.type == AR_FULL)
4883         {
4884           rank = ref->u.ar.as->rank;
4885           break;
4886         }
4887
4888       if (ref->u.ar.type == AR_SECTION)
4889         {
4890           /* Figure out the rank of the section.  */
4891           if (rank != 0)
4892             gfc_internal_error ("expression_rank(): Two array specs");
4893
4894           for (i = 0; i < ref->u.ar.dimen; i++)
4895             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4896                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4897               rank++;
4898
4899           break;
4900         }
4901     }
4902
4903   e->rank = rank;
4904
4905 done:
4906   expression_shape (e);
4907 }
4908
4909
4910 /* Resolve a variable expression.  */
4911
4912 static gfc_try
4913 resolve_variable (gfc_expr *e)
4914 {
4915   gfc_symbol *sym;
4916   gfc_try t;
4917
4918   t = SUCCESS;
4919
4920   if (e->symtree == NULL)
4921     return FAILURE;
4922   sym = e->symtree->n.sym;
4923
4924   /* If this is an associate-name, it may be parsed with references in error
4925      even though the target is scalar.  Fail directly in this case.  */
4926   if (sym->assoc && !sym->attr.dimension && e->ref)
4927     return FAILURE;
4928
4929   /* On the other hand, the parser may not have known this is an array;
4930      in this case, we have to add a FULL reference.  */
4931   if (sym->assoc && sym->attr.dimension && !e->ref)
4932     {
4933       e->ref = gfc_get_ref ();
4934       e->ref->type = REF_ARRAY;
4935       e->ref->u.ar.type = AR_FULL;
4936       e->ref->u.ar.dimen = 0;
4937     }
4938
4939   if (e->ref && resolve_ref (e) == FAILURE)
4940     return FAILURE;
4941
4942   if (sym->attr.flavor == FL_PROCEDURE
4943       && (!sym->attr.function
4944           || (sym->attr.function && sym->result
4945               && sym->result->attr.proc_pointer
4946               && !sym->result->attr.function)))
4947     {
4948       e->ts.type = BT_PROCEDURE;
4949       goto resolve_procedure;
4950     }
4951
4952   if (sym->ts.type != BT_UNKNOWN)
4953     gfc_variable_attr (e, &e->ts);
4954   else
4955     {
4956       /* Must be a simple variable reference.  */
4957       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
4958         return FAILURE;
4959       e->ts = sym->ts;
4960     }
4961
4962   if (check_assumed_size_reference (sym, e))
4963     return FAILURE;
4964
4965   /* Deal with forward references to entries during resolve_code, to
4966      satisfy, at least partially, 12.5.2.5.  */
4967   if (gfc_current_ns->entries
4968       && current_entry_id == sym->entry_id
4969       && cs_base
4970       && cs_base->current
4971       && cs_base->current->op != EXEC_ENTRY)
4972     {
4973       gfc_entry_list *entry;
4974       gfc_formal_arglist *formal;
4975       int n;
4976       bool seen;
4977
4978       /* If the symbol is a dummy...  */
4979       if (sym->attr.dummy && sym->ns == gfc_current_ns)
4980         {
4981           entry = gfc_current_ns->entries;
4982           seen = false;
4983
4984           /* ...test if the symbol is a parameter of previous entries.  */
4985           for (; entry && entry->id <= current_entry_id; entry = entry->next)
4986             for (formal = entry->sym->formal; formal; formal = formal->next)
4987               {
4988                 if (formal->sym && sym->name == formal->sym->name)
4989                   seen = true;
4990               }
4991
4992           /*  If it has not been seen as a dummy, this is an error.  */
4993           if (!seen)
4994             {
4995               if (specification_expr)
4996                 gfc_error ("Variable '%s', used in a specification expression"
4997                            ", is referenced at %L before the ENTRY statement "
4998                            "in which it is a parameter",
4999                            sym->name, &cs_base->current->loc);
5000               else
5001                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
5002                            "statement in which it is a parameter",
5003                            sym->name, &cs_base->current->loc);
5004               t = FAILURE;
5005             }
5006         }
5007
5008       /* Now do the same check on the specification expressions.  */
5009       specification_expr = 1;
5010       if (sym->ts.type == BT_CHARACTER
5011           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
5012         t = FAILURE;
5013
5014       if (sym->as)
5015         for (n = 0; n < sym->as->rank; n++)
5016           {
5017              specification_expr = 1;
5018              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
5019                t = FAILURE;
5020              specification_expr = 1;
5021              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
5022                t = FAILURE;
5023           }
5024       specification_expr = 0;
5025
5026       if (t == SUCCESS)
5027         /* Update the symbol's entry level.  */
5028         sym->entry_id = current_entry_id + 1;
5029     }
5030
5031   /* If a symbol has been host_associated mark it.  This is used latter,
5032      to identify if aliasing is possible via host association.  */
5033   if (sym->attr.flavor == FL_VARIABLE
5034         && gfc_current_ns->parent
5035         && (gfc_current_ns->parent == sym->ns
5036               || (gfc_current_ns->parent->parent
5037                     && gfc_current_ns->parent->parent == sym->ns)))
5038     sym->attr.host_assoc = 1;
5039
5040 resolve_procedure:
5041   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
5042     t = FAILURE;
5043
5044   /* F2008, C617 and C1229.  */
5045   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5046       && gfc_is_coindexed (e))
5047     {
5048       gfc_ref *ref, *ref2 = NULL;
5049
5050       if (e->ts.type == BT_CLASS)
5051         {
5052           gfc_error ("Polymorphic subobject of coindexed object at %L",
5053                      &e->where);
5054           t = FAILURE;
5055         }
5056
5057       for (ref = e->ref; ref; ref = ref->next)
5058         {
5059           if (ref->type == REF_COMPONENT)
5060             ref2 = ref;
5061           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5062             break;
5063         }
5064
5065       for ( ; ref; ref = ref->next)
5066         if (ref->type == REF_COMPONENT)
5067           break;
5068
5069       /* Expression itself is coindexed object.  */
5070       if (ref == NULL)
5071         {
5072           gfc_component *c;
5073           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5074           for ( ; c; c = c->next)
5075             if (c->attr.allocatable && c->ts.type == BT_CLASS)
5076               {
5077                 gfc_error ("Coindexed object with polymorphic allocatable "
5078                          "subcomponent at %L", &e->where);
5079                 t = FAILURE;
5080                 break;
5081               }
5082         }
5083     }
5084
5085   return t;
5086 }
5087
5088
5089 /* Checks to see that the correct symbol has been host associated.
5090    The only situation where this arises is that in which a twice
5091    contained function is parsed after the host association is made.
5092    Therefore, on detecting this, change the symbol in the expression
5093    and convert the array reference into an actual arglist if the old
5094    symbol is a variable.  */
5095 static bool
5096 check_host_association (gfc_expr *e)
5097 {
5098   gfc_symbol *sym, *old_sym;
5099   gfc_symtree *st;
5100   int n;
5101   gfc_ref *ref;
5102   gfc_actual_arglist *arg, *tail = NULL;
5103   bool retval = e->expr_type == EXPR_FUNCTION;
5104
5105   /*  If the expression is the result of substitution in
5106       interface.c(gfc_extend_expr) because there is no way in
5107       which the host association can be wrong.  */
5108   if (e->symtree == NULL
5109         || e->symtree->n.sym == NULL
5110         || e->user_operator)
5111     return retval;
5112
5113   old_sym = e->symtree->n.sym;
5114
5115   if (gfc_current_ns->parent
5116         && old_sym->ns != gfc_current_ns)
5117     {
5118       /* Use the 'USE' name so that renamed module symbols are
5119          correctly handled.  */
5120       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5121
5122       if (sym && old_sym != sym
5123               && sym->ts.type == old_sym->ts.type
5124               && sym->attr.flavor == FL_PROCEDURE
5125               && sym->attr.contained)
5126         {
5127           /* Clear the shape, since it might not be valid.  */
5128           if (e->shape != NULL)
5129             {
5130               for (n = 0; n < e->rank; n++)
5131                 mpz_clear (e->shape[n]);
5132
5133               gfc_free (e->shape);
5134             }
5135
5136           /* Give the expression the right symtree!  */
5137           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5138           gcc_assert (st != NULL);
5139
5140           if (old_sym->attr.flavor == FL_PROCEDURE
5141                 || e->expr_type == EXPR_FUNCTION)
5142             {
5143               /* Original was function so point to the new symbol, since
5144                  the actual argument list is already attached to the
5145                  expression. */
5146               e->value.function.esym = NULL;
5147               e->symtree = st;
5148             }
5149           else
5150             {
5151               /* Original was variable so convert array references into
5152                  an actual arglist. This does not need any checking now
5153                  since gfc_resolve_function will take care of it.  */
5154               e->value.function.actual = NULL;
5155               e->expr_type = EXPR_FUNCTION;
5156               e->symtree = st;
5157
5158               /* Ambiguity will not arise if the array reference is not
5159                  the last reference.  */
5160               for (ref = e->ref; ref; ref = ref->next)
5161                 if (ref->type == REF_ARRAY && ref->next == NULL)
5162                   break;
5163
5164               gcc_assert (ref->type == REF_ARRAY);
5165
5166               /* Grab the start expressions from the array ref and
5167                  copy them into actual arguments.  */
5168               for (n = 0; n < ref->u.ar.dimen; n++)
5169                 {
5170                   arg = gfc_get_actual_arglist ();
5171                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5172                   if (e->value.function.actual == NULL)
5173                     tail = e->value.function.actual = arg;
5174                   else
5175                     {
5176                       tail->next = arg;
5177                       tail = arg;
5178                     }
5179                 }
5180
5181               /* Dump the reference list and set the rank.  */
5182               gfc_free_ref_list (e->ref);
5183               e->ref = NULL;
5184               e->rank = sym->as ? sym->as->rank : 0;
5185             }
5186
5187           gfc_resolve_expr (e);
5188           sym->refs++;
5189         }
5190     }
5191   /* This might have changed!  */
5192   return e->expr_type == EXPR_FUNCTION;
5193 }
5194
5195
5196 static void
5197 gfc_resolve_character_operator (gfc_expr *e)
5198 {
5199   gfc_expr *op1 = e->value.op.op1;
5200   gfc_expr *op2 = e->value.op.op2;
5201   gfc_expr *e1 = NULL;
5202   gfc_expr *e2 = NULL;
5203
5204   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5205
5206   if (op1->ts.u.cl && op1->ts.u.cl->length)
5207     e1 = gfc_copy_expr (op1->ts.u.cl->length);
5208   else if (op1->expr_type == EXPR_CONSTANT)
5209     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5210                            op1->value.character.length);
5211
5212   if (op2->ts.u.cl && op2->ts.u.cl->length)
5213     e2 = gfc_copy_expr (op2->ts.u.cl->length);
5214   else if (op2->expr_type == EXPR_CONSTANT)
5215     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5216                            op2->value.character.length);
5217
5218   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5219
5220   if (!e1 || !e2)
5221     return;
5222
5223   e->ts.u.cl->length = gfc_add (e1, e2);
5224   e->ts.u.cl->length->ts.type = BT_INTEGER;
5225   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5226   gfc_simplify_expr (e->ts.u.cl->length, 0);
5227   gfc_resolve_expr (e->ts.u.cl->length);
5228
5229   return;
5230 }
5231
5232
5233 /*  Ensure that an character expression has a charlen and, if possible, a
5234     length expression.  */
5235
5236 static void
5237 fixup_charlen (gfc_expr *e)
5238 {
5239   /* The cases fall through so that changes in expression type and the need
5240      for multiple fixes are picked up.  In all circumstances, a charlen should
5241      be available for the middle end to hang a backend_decl on.  */
5242   switch (e->expr_type)
5243     {
5244     case EXPR_OP:
5245       gfc_resolve_character_operator (e);
5246
5247     case EXPR_ARRAY:
5248       if (e->expr_type == EXPR_ARRAY)
5249         gfc_resolve_character_array_constructor (e);
5250
5251     case EXPR_SUBSTRING:
5252       if (!e->ts.u.cl && e->ref)
5253         gfc_resolve_substring_charlen (e);
5254
5255     default:
5256       if (!e->ts.u.cl)
5257         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5258
5259       break;
5260     }
5261 }
5262
5263
5264 /* Update an actual argument to include the passed-object for type-bound
5265    procedures at the right position.  */
5266
5267 static gfc_actual_arglist*
5268 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5269                      const char *name)
5270 {
5271   gcc_assert (argpos > 0);
5272
5273   if (argpos == 1)
5274     {
5275       gfc_actual_arglist* result;
5276
5277       result = gfc_get_actual_arglist ();
5278       result->expr = po;
5279       result->next = lst;
5280       if (name)
5281         result->name = name;
5282
5283       return result;
5284     }
5285
5286   if (lst)
5287     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5288   else
5289     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5290   return lst;
5291 }
5292
5293
5294 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5295
5296 static gfc_expr*
5297 extract_compcall_passed_object (gfc_expr* e)
5298 {
5299   gfc_expr* po;
5300
5301   gcc_assert (e->expr_type == EXPR_COMPCALL);
5302
5303   if (e->value.compcall.base_object)
5304     po = gfc_copy_expr (e->value.compcall.base_object);
5305   else
5306     {
5307       po = gfc_get_expr ();
5308       po->expr_type = EXPR_VARIABLE;
5309       po->symtree = e->symtree;
5310       po->ref = gfc_copy_ref (e->ref);
5311       po->where = e->where;
5312     }
5313
5314   if (gfc_resolve_expr (po) == FAILURE)
5315     return NULL;
5316
5317   return po;
5318 }
5319
5320
5321 /* Update the arglist of an EXPR_COMPCALL expression to include the
5322    passed-object.  */
5323
5324 static gfc_try
5325 update_compcall_arglist (gfc_expr* e)
5326 {
5327   gfc_expr* po;
5328   gfc_typebound_proc* tbp;
5329
5330   tbp = e->value.compcall.tbp;
5331
5332   if (tbp->error)
5333     return FAILURE;
5334
5335   po = extract_compcall_passed_object (e);
5336   if (!po)
5337     return FAILURE;
5338
5339   if (tbp->nopass || e->value.compcall.ignore_pass)
5340     {
5341       gfc_free_expr (po);
5342       return SUCCESS;
5343     }
5344
5345   gcc_assert (tbp->pass_arg_num > 0);
5346   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5347                                                   tbp->pass_arg_num,
5348                                                   tbp->pass_arg);
5349
5350   return SUCCESS;
5351 }
5352
5353
5354 /* Extract the passed object from a PPC call (a copy of it).  */
5355
5356 static gfc_expr*
5357 extract_ppc_passed_object (gfc_expr *e)
5358 {
5359   gfc_expr *po;
5360   gfc_ref **ref;
5361
5362   po = gfc_get_expr ();
5363   po->expr_type = EXPR_VARIABLE;
5364   po->symtree = e->symtree;
5365   po->ref = gfc_copy_ref (e->ref);
5366   po->where = e->where;
5367
5368   /* Remove PPC reference.  */
5369   ref = &po->ref;
5370   while ((*ref)->next)
5371     ref = &(*ref)->next;
5372   gfc_free_ref_list (*ref);
5373   *ref = NULL;
5374
5375   if (gfc_resolve_expr (po) == FAILURE)
5376     return NULL;
5377
5378   return po;
5379 }
5380
5381
5382 /* Update the actual arglist of a procedure pointer component to include the
5383    passed-object.  */
5384
5385 static gfc_try
5386 update_ppc_arglist (gfc_expr* e)
5387 {
5388   gfc_expr* po;
5389   gfc_component *ppc;
5390   gfc_typebound_proc* tb;
5391
5392   if (!gfc_is_proc_ptr_comp (e, &ppc))
5393     return FAILURE;
5394
5395   tb = ppc->tb;
5396
5397   if (tb->error)
5398     return FAILURE;
5399   else if (tb->nopass)
5400     return SUCCESS;
5401
5402   po = extract_ppc_passed_object (e);
5403   if (!po)
5404     return FAILURE;
5405
5406   if (po->rank > 0)
5407     {
5408       gfc_error ("Passed-object at %L must be scalar", &e->where);
5409       return FAILURE;
5410     }
5411
5412   gcc_assert (tb->pass_arg_num > 0);
5413   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5414                                                   tb->pass_arg_num,
5415                                                   tb->pass_arg);
5416
5417   return SUCCESS;
5418 }
5419
5420
5421 /* Check that the object a TBP is called on is valid, i.e. it must not be
5422    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5423
5424 static gfc_try
5425 check_typebound_baseobject (gfc_expr* e)
5426 {
5427   gfc_expr* base;
5428
5429   base = extract_compcall_passed_object (e);
5430   if (!base)
5431     return FAILURE;
5432
5433   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5434
5435   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5436     {
5437       gfc_error ("Base object for type-bound procedure call at %L is of"
5438                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5439       return FAILURE;
5440     }
5441
5442   /* If the procedure called is NOPASS, the base object must be scalar.  */
5443   if (e->value.compcall.tbp->nopass && base->rank > 0)
5444     {
5445       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5446                  " be scalar", &e->where);
5447       return FAILURE;
5448     }
5449
5450   /* FIXME: Remove once PR 41177 (this problem) is fixed completely.  */
5451   if (base->rank > 0)
5452     {
5453       gfc_error ("Non-scalar base object at %L currently not implemented",
5454                  &e->where);
5455       return FAILURE;
5456     }
5457
5458   return SUCCESS;
5459 }
5460
5461
5462 /* Resolve a call to a type-bound procedure, either function or subroutine,
5463    statically from the data in an EXPR_COMPCALL expression.  The adapted
5464    arglist and the target-procedure symtree are returned.  */
5465
5466 static gfc_try
5467 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5468                           gfc_actual_arglist** actual)
5469 {
5470   gcc_assert (e->expr_type == EXPR_COMPCALL);
5471   gcc_assert (!e->value.compcall.tbp->is_generic);
5472
5473   /* Update the actual arglist for PASS.  */
5474   if (update_compcall_arglist (e) == FAILURE)
5475     return FAILURE;
5476
5477   *actual = e->value.compcall.actual;
5478   *target = e->value.compcall.tbp->u.specific;
5479
5480   gfc_free_ref_list (e->ref);
5481   e->ref = NULL;
5482   e->value.compcall.actual = NULL;
5483
5484   return SUCCESS;
5485 }
5486
5487
5488 /* Get the ultimate declared type from an expression.  In addition,
5489    return the last class/derived type reference and the copy of the
5490    reference list.  */
5491 static gfc_symbol*
5492 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5493                         gfc_expr *e)
5494 {
5495   gfc_symbol *declared;
5496   gfc_ref *ref;
5497
5498   declared = NULL;
5499   if (class_ref)
5500     *class_ref = NULL;
5501   if (new_ref)
5502     *new_ref = gfc_copy_ref (e->ref);
5503
5504   for (ref = e->ref; ref; ref = ref->next)
5505     {
5506       if (ref->type != REF_COMPONENT)
5507         continue;
5508
5509       if (ref->u.c.component->ts.type == BT_CLASS
5510             || ref->u.c.component->ts.type == BT_DERIVED)
5511         {
5512           declared = ref->u.c.component->ts.u.derived;
5513           if (class_ref)
5514             *class_ref = ref;
5515         }
5516     }
5517
5518   if (declared == NULL)
5519     declared = e->symtree->n.sym->ts.u.derived;
5520
5521   return declared;
5522 }
5523
5524
5525 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5526    which of the specific bindings (if any) matches the arglist and transform
5527    the expression into a call of that binding.  */
5528
5529 static gfc_try
5530 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5531 {
5532   gfc_typebound_proc* genproc;
5533   const char* genname;
5534   gfc_symtree *st;
5535   gfc_symbol *derived;
5536
5537   gcc_assert (e->expr_type == EXPR_COMPCALL);
5538   genname = e->value.compcall.name;
5539   genproc = e->value.compcall.tbp;
5540
5541   if (!genproc->is_generic)
5542     return SUCCESS;
5543
5544   /* Try the bindings on this type and in the inheritance hierarchy.  */
5545   for (; genproc; genproc = genproc->overridden)
5546     {
5547       gfc_tbp_generic* g;
5548
5549       gcc_assert (genproc->is_generic);
5550       for (g = genproc->u.generic; g; g = g->next)
5551         {
5552           gfc_symbol* target;
5553           gfc_actual_arglist* args;
5554           bool matches;
5555
5556           gcc_assert (g->specific);
5557
5558           if (g->specific->error)
5559             continue;
5560
5561           target = g->specific->u.specific->n.sym;
5562
5563           /* Get the right arglist by handling PASS/NOPASS.  */
5564           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5565           if (!g->specific->nopass)
5566             {
5567               gfc_expr* po;
5568               po = extract_compcall_passed_object (e);
5569               if (!po)
5570                 return FAILURE;
5571
5572               gcc_assert (g->specific->pass_arg_num > 0);
5573               gcc_assert (!g->specific->error);
5574               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5575                                           g->specific->pass_arg);
5576             }
5577           resolve_actual_arglist (args, target->attr.proc,
5578                                   is_external_proc (target) && !target->formal);
5579
5580           /* Check if this arglist matches the formal.  */
5581           matches = gfc_arglist_matches_symbol (&args, target);
5582
5583           /* Clean up and break out of the loop if we've found it.  */
5584           gfc_free_actual_arglist (args);
5585           if (matches)
5586             {
5587               e->value.compcall.tbp = g->specific;
5588               genname = g->specific_st->name;
5589               /* Pass along the name for CLASS methods, where the vtab
5590                  procedure pointer component has to be referenced.  */
5591               if (name)
5592                 *name = genname;
5593               goto success;
5594             }
5595         }
5596     }
5597
5598   /* Nothing matching found!  */
5599   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5600              " '%s' at %L", genname, &e->where);
5601   return FAILURE;
5602
5603 success:
5604   /* Make sure that we have the right specific instance for the name.  */
5605   derived = get_declared_from_expr (NULL, NULL, e);
5606
5607   st = gfc_find_typebound_proc (derived, NULL, genname, false, &e->where);
5608   if (st)
5609     e->value.compcall.tbp = st->n.tb;
5610
5611   return SUCCESS;
5612 }
5613
5614
5615 /* Resolve a call to a type-bound subroutine.  */
5616
5617 static gfc_try
5618 resolve_typebound_call (gfc_code* c, const char **name)
5619 {
5620   gfc_actual_arglist* newactual;
5621   gfc_symtree* target;
5622
5623   /* Check that's really a SUBROUTINE.  */
5624   if (!c->expr1->value.compcall.tbp->subroutine)
5625     {
5626       gfc_error ("'%s' at %L should be a SUBROUTINE",
5627                  c->expr1->value.compcall.name, &c->loc);
5628       return FAILURE;
5629     }
5630
5631   if (check_typebound_baseobject (c->expr1) == FAILURE)
5632     return FAILURE;
5633
5634   /* Pass along the name for CLASS methods, where the vtab
5635      procedure pointer component has to be referenced.  */
5636   if (name)
5637     *name = c->expr1->value.compcall.name;
5638
5639   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5640     return FAILURE;
5641
5642   /* Transform into an ordinary EXEC_CALL for now.  */
5643
5644   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5645     return FAILURE;
5646
5647   c->ext.actual = newactual;
5648   c->symtree = target;
5649   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5650
5651   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5652
5653   gfc_free_expr (c->expr1);
5654   c->expr1 = gfc_get_expr ();
5655   c->expr1->expr_type = EXPR_FUNCTION;
5656   c->expr1->symtree = target;
5657   c->expr1->where = c->loc;
5658
5659   return resolve_call (c);
5660 }
5661
5662
5663 /* Resolve a component-call expression.  */
5664 static gfc_try
5665 resolve_compcall (gfc_expr* e, const char **name)
5666 {
5667   gfc_actual_arglist* newactual;
5668   gfc_symtree* target;
5669
5670   /* Check that's really a FUNCTION.  */
5671   if (!e->value.compcall.tbp->function)
5672     {
5673       gfc_error ("'%s' at %L should be a FUNCTION",
5674                  e->value.compcall.name, &e->where);
5675       return FAILURE;
5676     }
5677
5678   /* These must not be assign-calls!  */
5679   gcc_assert (!e->value.compcall.assign);
5680
5681   if (check_typebound_baseobject (e) == FAILURE)
5682     return FAILURE;
5683
5684   /* Pass along the name for CLASS methods, where the vtab
5685      procedure pointer component has to be referenced.  */
5686   if (name)
5687     *name = e->value.compcall.name;
5688
5689   if (resolve_typebound_generic_call (e, name) == FAILURE)
5690     return FAILURE;
5691   gcc_assert (!e->value.compcall.tbp->is_generic);
5692
5693   /* Take the rank from the function's symbol.  */
5694   if (e->value.compcall.tbp->u.specific->n.sym->as)
5695     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5696
5697   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5698      arglist to the TBP's binding target.  */
5699
5700   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5701     return FAILURE;
5702
5703   e->value.function.actual = newactual;
5704   e->value.function.name = NULL;
5705   e->value.function.esym = target->n.sym;
5706   e->value.function.isym = NULL;
5707   e->symtree = target;
5708   e->ts = target->n.sym->ts;
5709   e->expr_type = EXPR_FUNCTION;
5710
5711   /* Resolution is not necessary if this is a class subroutine; this
5712      function only has to identify the specific proc. Resolution of
5713      the call will be done next in resolve_typebound_call.  */
5714   return gfc_resolve_expr (e);
5715 }
5716
5717
5718
5719 /* Resolve a typebound function, or 'method'. First separate all
5720    the non-CLASS references by calling resolve_compcall directly.  */
5721
5722 static gfc_try
5723 resolve_typebound_function (gfc_expr* e)
5724 {
5725   gfc_symbol *declared;
5726   gfc_component *c;
5727   gfc_ref *new_ref;
5728   gfc_ref *class_ref;
5729   gfc_symtree *st;
5730   const char *name;
5731   gfc_typespec ts;
5732   gfc_expr *expr;
5733
5734   st = e->symtree;
5735
5736   /* Deal with typebound operators for CLASS objects.  */
5737   expr = e->value.compcall.base_object;
5738   if (expr && expr->symtree->n.sym->ts.type == BT_CLASS
5739         && e->value.compcall.name)
5740     {
5741       /* Since the typebound operators are generic, we have to ensure
5742          that any delays in resolution are corrected and that the vtab
5743          is present.  */
5744       ts = expr->symtree->n.sym->ts;
5745       declared = ts.u.derived;
5746       c = gfc_find_component (declared, "$vptr", true, true);
5747       if (c->ts.u.derived == NULL)
5748         c->ts.u.derived = gfc_find_derived_vtab (declared);
5749
5750       if (resolve_compcall (e, &name) == FAILURE)
5751         return FAILURE;
5752
5753       /* Use the generic name if it is there.  */
5754       name = name ? name : e->value.function.esym->name;
5755       e->symtree = expr->symtree;
5756       expr->symtree->n.sym->ts.u.derived = declared;
5757       gfc_add_component_ref (e, "$vptr");
5758       gfc_add_component_ref (e, name);
5759       e->value.function.esym = NULL;
5760       return SUCCESS;
5761     }
5762
5763   if (st == NULL)
5764     return resolve_compcall (e, NULL);
5765
5766   if (resolve_ref (e) == FAILURE)
5767     return FAILURE;
5768
5769   /* Get the CLASS declared type.  */
5770   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5771
5772   /* Weed out cases of the ultimate component being a derived type.  */
5773   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5774          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5775     {
5776       gfc_free_ref_list (new_ref);
5777       return resolve_compcall (e, NULL);
5778     }
5779
5780   c = gfc_find_component (declared, "$data", true, true);
5781   declared = c->ts.u.derived;
5782
5783   /* Treat the call as if it is a typebound procedure, in order to roll
5784      out the correct name for the specific function.  */
5785   if (resolve_compcall (e, &name) == FAILURE)
5786     return FAILURE;
5787   ts = e->ts;
5788
5789   /* Then convert the expression to a procedure pointer component call.  */
5790   e->value.function.esym = NULL;
5791   e->symtree = st;
5792
5793   if (new_ref)  
5794     e->ref = new_ref;
5795
5796   /* '$vptr' points to the vtab, which contains the procedure pointers.  */
5797   gfc_add_component_ref (e, "$vptr");
5798   gfc_add_component_ref (e, name);
5799
5800   /* Recover the typespec for the expression.  This is really only
5801      necessary for generic procedures, where the additional call
5802      to gfc_add_component_ref seems to throw the collection of the
5803      correct typespec.  */
5804   e->ts = ts;
5805   return SUCCESS;
5806 }
5807
5808 /* Resolve a typebound subroutine, or 'method'. First separate all
5809    the non-CLASS references by calling resolve_typebound_call
5810    directly.  */
5811
5812 static gfc_try
5813 resolve_typebound_subroutine (gfc_code *code)
5814 {
5815   gfc_symbol *declared;
5816   gfc_component *c;
5817   gfc_ref *new_ref;
5818   gfc_ref *class_ref;
5819   gfc_symtree *st;
5820   const char *name;
5821   gfc_typespec ts;
5822   gfc_expr *expr;
5823
5824   st = code->expr1->symtree;
5825
5826   /* Deal with typebound operators for CLASS objects.  */
5827   expr = code->expr1->value.compcall.base_object;
5828   if (expr && expr->symtree->n.sym->ts.type == BT_CLASS
5829         && code->expr1->value.compcall.name)
5830     {
5831       /* Since the typebound operators are generic, we have to ensure
5832          that any delays in resolution are corrected and that the vtab
5833          is present.  */
5834       ts = expr->symtree->n.sym->ts;
5835       declared = ts.u.derived;
5836       c = gfc_find_component (declared, "$vptr", true, true);
5837       if (c->ts.u.derived == NULL)
5838         c->ts.u.derived = gfc_find_derived_vtab (declared);
5839
5840       if (resolve_typebound_call (code, &name) == FAILURE)
5841         return FAILURE;
5842
5843       /* Use the generic name if it is there.  */
5844       name = name ? name : code->expr1->value.function.esym->name;
5845       code->expr1->symtree = expr->symtree;
5846       expr->symtree->n.sym->ts.u.derived = declared;
5847       gfc_add_component_ref (code->expr1, "$vptr");
5848       gfc_add_component_ref (code->expr1, name);
5849       code->expr1->value.function.esym = NULL;
5850       return SUCCESS;
5851     }
5852
5853   if (st == NULL)
5854     return resolve_typebound_call (code, NULL);
5855
5856   if (resolve_ref (code->expr1) == FAILURE)
5857     return FAILURE;
5858
5859   /* Get the CLASS declared type.  */
5860   get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5861
5862   /* Weed out cases of the ultimate component being a derived type.  */
5863   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5864          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5865     {
5866       gfc_free_ref_list (new_ref);
5867       return resolve_typebound_call (code, NULL);
5868     }
5869
5870   if (resolve_typebound_call (code, &name) == FAILURE)
5871     return FAILURE;
5872   ts = code->expr1->ts;
5873
5874   /* Then convert the expression to a procedure pointer component call.  */
5875   code->expr1->value.function.esym = NULL;
5876   code->expr1->symtree = st;
5877
5878   if (new_ref)
5879     code->expr1->ref = new_ref;
5880
5881   /* '$vptr' points to the vtab, which contains the procedure pointers.  */
5882   gfc_add_component_ref (code->expr1, "$vptr");
5883   gfc_add_component_ref (code->expr1, name);
5884
5885   /* Recover the typespec for the expression.  This is really only
5886      necessary for generic procedures, where the additional call
5887      to gfc_add_component_ref seems to throw the collection of the
5888      correct typespec.  */
5889   code->expr1->ts = ts;
5890   return SUCCESS;
5891 }
5892
5893
5894 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5895
5896 static gfc_try
5897 resolve_ppc_call (gfc_code* c)
5898 {
5899   gfc_component *comp;
5900   bool b;
5901
5902   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5903   gcc_assert (b);
5904
5905   c->resolved_sym = c->expr1->symtree->n.sym;
5906   c->expr1->expr_type = EXPR_VARIABLE;
5907
5908   if (!comp->attr.subroutine)
5909     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5910
5911   if (resolve_ref (c->expr1) == FAILURE)
5912     return FAILURE;
5913
5914   if (update_ppc_arglist (c->expr1) == FAILURE)
5915     return FAILURE;
5916
5917   c->ext.actual = c->expr1->value.compcall.actual;
5918
5919   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5920                               comp->formal == NULL) == FAILURE)
5921     return FAILURE;
5922
5923   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
5924
5925   return SUCCESS;
5926 }
5927
5928
5929 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
5930
5931 static gfc_try
5932 resolve_expr_ppc (gfc_expr* e)
5933 {
5934   gfc_component *comp;
5935   bool b;
5936
5937   b = gfc_is_proc_ptr_comp (e, &comp);
5938   gcc_assert (b);
5939
5940   /* Convert to EXPR_FUNCTION.  */
5941   e->expr_type = EXPR_FUNCTION;
5942   e->value.function.isym = NULL;
5943   e->value.function.actual = e->value.compcall.actual;
5944   e->ts = comp->ts;
5945   if (comp->as != NULL)
5946     e->rank = comp->as->rank;
5947
5948   if (!comp->attr.function)
5949     gfc_add_function (&comp->attr, comp->name, &e->where);
5950
5951   if (resolve_ref (e) == FAILURE)
5952     return FAILURE;
5953
5954   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
5955                               comp->formal == NULL) == FAILURE)
5956     return FAILURE;
5957
5958   if (update_ppc_arglist (e) == FAILURE)
5959     return FAILURE;
5960
5961   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
5962
5963   return SUCCESS;
5964 }
5965
5966
5967 static bool
5968 gfc_is_expandable_expr (gfc_expr *e)
5969 {
5970   gfc_constructor *con;
5971
5972   if (e->expr_type == EXPR_ARRAY)
5973     {
5974       /* Traverse the constructor looking for variables that are flavor
5975          parameter.  Parameters must be expanded since they are fully used at
5976          compile time.  */
5977       con = gfc_constructor_first (e->value.constructor);
5978       for (; con; con = gfc_constructor_next (con))
5979         {
5980           if (con->expr->expr_type == EXPR_VARIABLE
5981               && con->expr->symtree
5982               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
5983               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
5984             return true;
5985           if (con->expr->expr_type == EXPR_ARRAY
5986               && gfc_is_expandable_expr (con->expr))
5987             return true;
5988         }
5989     }
5990
5991   return false;
5992 }
5993
5994 /* Resolve an expression.  That is, make sure that types of operands agree
5995    with their operators, intrinsic operators are converted to function calls
5996    for overloaded types and unresolved function references are resolved.  */
5997
5998 gfc_try
5999 gfc_resolve_expr (gfc_expr *e)
6000 {
6001   gfc_try t;
6002   bool inquiry_save;
6003
6004   if (e == NULL)
6005     return SUCCESS;
6006
6007   /* inquiry_argument only applies to variables.  */
6008   inquiry_save = inquiry_argument;
6009   if (e->expr_type != EXPR_VARIABLE)
6010     inquiry_argument = false;
6011
6012   switch (e->expr_type)
6013     {
6014     case EXPR_OP:
6015       t = resolve_operator (e);
6016       break;
6017
6018     case EXPR_FUNCTION:
6019     case EXPR_VARIABLE:
6020
6021       if (check_host_association (e))
6022         t = resolve_function (e);
6023       else
6024         {
6025           t = resolve_variable (e);
6026           if (t == SUCCESS)
6027             expression_rank (e);
6028         }
6029
6030       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6031           && e->ref->type != REF_SUBSTRING)
6032         gfc_resolve_substring_charlen (e);
6033
6034       break;
6035
6036     case EXPR_COMPCALL:
6037       t = resolve_typebound_function (e);
6038       break;
6039
6040     case EXPR_SUBSTRING:
6041       t = resolve_ref (e);
6042       break;
6043
6044     case EXPR_CONSTANT:
6045     case EXPR_NULL:
6046       t = SUCCESS;
6047       break;
6048
6049     case EXPR_PPC:
6050       t = resolve_expr_ppc (e);
6051       break;
6052
6053     case EXPR_ARRAY:
6054       t = FAILURE;
6055       if (resolve_ref (e) == FAILURE)
6056         break;
6057
6058       t = gfc_resolve_array_constructor (e);
6059       /* Also try to expand a constructor.  */
6060       if (t == SUCCESS)
6061         {
6062           expression_rank (e);
6063           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6064             gfc_expand_constructor (e, false);
6065         }
6066
6067       /* This provides the opportunity for the length of constructors with
6068          character valued function elements to propagate the string length
6069          to the expression.  */
6070       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
6071         {
6072           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6073              here rather then add a duplicate test for it above.  */ 
6074           gfc_expand_constructor (e, false);
6075           t = gfc_resolve_character_array_constructor (e);
6076         }
6077
6078       break;
6079
6080     case EXPR_STRUCTURE:
6081       t = resolve_ref (e);
6082       if (t == FAILURE)
6083         break;
6084
6085       t = resolve_structure_cons (e, 0);
6086       if (t == FAILURE)
6087         break;
6088
6089       t = gfc_simplify_expr (e, 0);
6090       break;
6091
6092     default:
6093       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6094     }
6095
6096   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
6097     fixup_charlen (e);
6098
6099   inquiry_argument = inquiry_save;
6100
6101   return t;
6102 }
6103
6104
6105 /* Resolve an expression from an iterator.  They must be scalar and have
6106    INTEGER or (optionally) REAL type.  */
6107
6108 static gfc_try
6109 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6110                            const char *name_msgid)
6111 {
6112   if (gfc_resolve_expr (expr) == FAILURE)
6113     return FAILURE;
6114
6115   if (expr->rank != 0)
6116     {
6117       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6118       return FAILURE;
6119     }
6120
6121   if (expr->ts.type != BT_INTEGER)
6122     {
6123       if (expr->ts.type == BT_REAL)
6124         {
6125           if (real_ok)
6126             return gfc_notify_std (GFC_STD_F95_DEL,
6127                                    "Deleted feature: %s at %L must be integer",
6128                                    _(name_msgid), &expr->where);
6129           else
6130             {
6131               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6132                          &expr->where);
6133               return FAILURE;
6134             }
6135         }
6136       else
6137         {
6138           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6139           return FAILURE;
6140         }
6141     }
6142   return SUCCESS;
6143 }
6144
6145
6146 /* Resolve the expressions in an iterator structure.  If REAL_OK is
6147    false allow only INTEGER type iterators, otherwise allow REAL types.  */
6148
6149 gfc_try
6150 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
6151 {
6152   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
6153       == FAILURE)
6154     return FAILURE;
6155
6156   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
6157     {
6158       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
6159                  &iter->var->where);
6160       return FAILURE;
6161     }
6162
6163   if (gfc_resolve_iterator_expr (iter->start, real_ok,
6164                                  "Start expression in DO loop") == FAILURE)
6165     return FAILURE;
6166
6167   if (gfc_resolve_iterator_expr (iter->end, real_ok,
6168                                  "End expression in DO loop") == FAILURE)
6169     return FAILURE;
6170
6171   if (gfc_resolve_iterator_expr (iter->step, real_ok,
6172                                  "Step expression in DO loop") == FAILURE)
6173     return FAILURE;
6174
6175   if (iter->step->expr_type == EXPR_CONSTANT)
6176     {
6177       if ((iter->step->ts.type == BT_INTEGER
6178            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6179           || (iter->step->ts.type == BT_REAL
6180               && mpfr_sgn (iter->step->value.real) == 0))
6181         {
6182           gfc_error ("Step expression in DO loop at %L cannot be zero",
6183                      &iter->step->where);
6184           return FAILURE;
6185         }
6186     }
6187
6188   /* Convert start, end, and step to the same type as var.  */
6189   if (iter->start->ts.kind != iter->var->ts.kind
6190       || iter->start->ts.type != iter->var->ts.type)
6191     gfc_convert_type (iter->start, &iter->var->ts, 2);
6192
6193   if (iter->end->ts.kind != iter->var->ts.kind
6194       || iter->end->ts.type != iter->var->ts.type)
6195     gfc_convert_type (iter->end, &iter->var->ts, 2);
6196
6197   if (iter->step->ts.kind != iter->var->ts.kind
6198       || iter->step->ts.type != iter->var->ts.type)
6199     gfc_convert_type (iter->step, &iter->var->ts, 2);
6200
6201   if (iter->start->expr_type == EXPR_CONSTANT
6202       && iter->end->expr_type == EXPR_CONSTANT
6203       && iter->step->expr_type == EXPR_CONSTANT)
6204     {
6205       int sgn, cmp;
6206       if (iter->start->ts.type == BT_INTEGER)
6207         {
6208           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6209           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6210         }
6211       else
6212         {
6213           sgn = mpfr_sgn (iter->step->value.real);
6214           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6215         }
6216       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
6217         gfc_warning ("DO loop at %L will be executed zero times",
6218                      &iter->step->where);
6219     }
6220
6221   return SUCCESS;
6222 }
6223
6224
6225 /* Traversal function for find_forall_index.  f == 2 signals that
6226    that variable itself is not to be checked - only the references.  */
6227
6228 static bool
6229 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6230 {
6231   if (expr->expr_type != EXPR_VARIABLE)
6232     return false;
6233   
6234   /* A scalar assignment  */
6235   if (!expr->ref || *f == 1)
6236     {
6237       if (expr->symtree->n.sym == sym)
6238         return true;
6239       else
6240         return false;
6241     }
6242
6243   if (*f == 2)
6244     *f = 1;
6245   return false;
6246 }
6247
6248
6249 /* Check whether the FORALL index appears in the expression or not.
6250    Returns SUCCESS if SYM is found in EXPR.  */
6251
6252 gfc_try
6253 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6254 {
6255   if (gfc_traverse_expr (expr, sym, forall_index, f))
6256     return SUCCESS;
6257   else
6258     return FAILURE;
6259 }
6260
6261
6262 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6263    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6264    INTEGERs, and if stride is a constant it must be nonzero.
6265    Furthermore "A subscript or stride in a forall-triplet-spec shall
6266    not contain a reference to any index-name in the
6267    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6268
6269 static void
6270 resolve_forall_iterators (gfc_forall_iterator *it)
6271 {
6272   gfc_forall_iterator *iter, *iter2;
6273
6274   for (iter = it; iter; iter = iter->next)
6275     {
6276       if (gfc_resolve_expr (iter->var) == SUCCESS
6277           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6278         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6279                    &iter->var->where);
6280
6281       if (gfc_resolve_expr (iter->start) == SUCCESS
6282           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6283         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6284                    &iter->start->where);
6285       if (iter->var->ts.kind != iter->start->ts.kind)
6286         gfc_convert_type (iter->start, &iter->var->ts, 2);
6287
6288       if (gfc_resolve_expr (iter->end) == SUCCESS
6289           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6290         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6291                    &iter->end->where);
6292       if (iter->var->ts.kind != iter->end->ts.kind)
6293         gfc_convert_type (iter->end, &iter->var->ts, 2);
6294
6295       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6296         {
6297           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6298             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6299                        &iter->stride->where, "INTEGER");
6300
6301           if (iter->stride->expr_type == EXPR_CONSTANT
6302               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6303             gfc_error ("FORALL stride expression at %L cannot be zero",
6304                        &iter->stride->where);
6305         }
6306       if (iter->var->ts.kind != iter->stride->ts.kind)
6307         gfc_convert_type (iter->stride, &iter->var->ts, 2);
6308     }
6309
6310   for (iter = it; iter; iter = iter->next)
6311     for (iter2 = iter; iter2; iter2 = iter2->next)
6312       {
6313         if (find_forall_index (iter2->start,
6314                                iter->var->symtree->n.sym, 0) == SUCCESS
6315             || find_forall_index (iter2->end,
6316                                   iter->var->symtree->n.sym, 0) == SUCCESS
6317             || find_forall_index (iter2->stride,
6318                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6319           gfc_error ("FORALL index '%s' may not appear in triplet "
6320                      "specification at %L", iter->var->symtree->name,
6321                      &iter2->start->where);
6322       }
6323 }
6324
6325
6326 /* Given a pointer to a symbol that is a derived type, see if it's
6327    inaccessible, i.e. if it's defined in another module and the components are
6328    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6329    inaccessible components are found, nonzero otherwise.  */
6330
6331 static int
6332 derived_inaccessible (gfc_symbol *sym)
6333 {
6334   gfc_component *c;
6335
6336   if (sym->attr.use_assoc && sym->attr.private_comp)
6337     return 1;
6338
6339   for (c = sym->components; c; c = c->next)
6340     {
6341         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6342           return 1;
6343     }
6344
6345   return 0;
6346 }
6347
6348
6349 /* Resolve the argument of a deallocate expression.  The expression must be
6350    a pointer or a full array.  */
6351
6352 static gfc_try
6353 resolve_deallocate_expr (gfc_expr *e)
6354 {
6355   symbol_attribute attr;
6356   int allocatable, pointer, check_intent_in;
6357   gfc_ref *ref;
6358   gfc_symbol *sym;
6359   gfc_component *c;
6360
6361   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
6362   check_intent_in = 1;
6363
6364   if (gfc_resolve_expr (e) == FAILURE)
6365     return FAILURE;
6366
6367   if (e->expr_type != EXPR_VARIABLE)
6368     goto bad;
6369
6370   sym = e->symtree->n.sym;
6371
6372   if (sym->ts.type == BT_CLASS)
6373     {
6374       allocatable = CLASS_DATA (sym)->attr.allocatable;
6375       pointer = CLASS_DATA (sym)->attr.class_pointer;
6376     }
6377   else
6378     {
6379       allocatable = sym->attr.allocatable;
6380       pointer = sym->attr.pointer;
6381     }
6382   for (ref = e->ref; ref; ref = ref->next)
6383     {
6384       if (pointer)
6385         check_intent_in = 0;
6386
6387       switch (ref->type)
6388         {
6389         case REF_ARRAY:
6390           if (ref->u.ar.type != AR_FULL)
6391             allocatable = 0;
6392           break;
6393
6394         case REF_COMPONENT:
6395           c = ref->u.c.component;
6396           if (c->ts.type == BT_CLASS)
6397             {
6398               allocatable = CLASS_DATA (c)->attr.allocatable;
6399               pointer = CLASS_DATA (c)->attr.class_pointer;
6400             }
6401           else
6402             {
6403               allocatable = c->attr.allocatable;
6404               pointer = c->attr.pointer;
6405             }
6406           break;
6407
6408         case REF_SUBSTRING:
6409           allocatable = 0;
6410           break;
6411         }
6412     }
6413
6414   attr = gfc_expr_attr (e);
6415
6416   if (allocatable == 0 && attr.pointer == 0)
6417     {
6418     bad:
6419       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6420                  &e->where);
6421       return FAILURE;
6422     }
6423
6424   if (check_intent_in && sym->attr.intent == INTENT_IN)
6425     {
6426       gfc_error ("Cannot deallocate INTENT(IN) variable '%s' at %L",
6427                  sym->name, &e->where);
6428       return FAILURE;
6429     }
6430
6431   if (e->ts.type == BT_CLASS)
6432     {
6433       /* Only deallocate the DATA component.  */
6434       gfc_add_component_ref (e, "$data");
6435     }
6436
6437   return SUCCESS;
6438 }
6439
6440
6441 /* Returns true if the expression e contains a reference to the symbol sym.  */
6442 static bool
6443 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6444 {
6445   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6446     return true;
6447
6448   return false;
6449 }
6450
6451 bool
6452 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6453 {
6454   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6455 }
6456
6457
6458 /* Given the expression node e for an allocatable/pointer of derived type to be
6459    allocated, get the expression node to be initialized afterwards (needed for
6460    derived types with default initializers, and derived types with allocatable
6461    components that need nullification.)  */
6462
6463 gfc_expr *
6464 gfc_expr_to_initialize (gfc_expr *e)
6465 {
6466   gfc_expr *result;
6467   gfc_ref *ref;
6468   int i;
6469
6470   result = gfc_copy_expr (e);
6471
6472   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6473   for (ref = result->ref; ref; ref = ref->next)
6474     if (ref->type == REF_ARRAY && ref->next == NULL)
6475       {
6476         ref->u.ar.type = AR_FULL;
6477
6478         for (i = 0; i < ref->u.ar.dimen; i++)
6479           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6480
6481         result->rank = ref->u.ar.dimen;
6482         break;
6483       }
6484
6485   return result;
6486 }
6487
6488
6489 /* Used in resolve_allocate_expr to check that a allocation-object and
6490    a source-expr are conformable.  This does not catch all possible 
6491    cases; in particular a runtime checking is needed.  */
6492
6493 static gfc_try
6494 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6495 {
6496   gfc_ref *tail;
6497   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6498   
6499   /* First compare rank.  */
6500   if (tail && e1->rank != tail->u.ar.as->rank)
6501     {
6502       gfc_error ("Source-expr at %L must be scalar or have the "
6503                  "same rank as the allocate-object at %L",
6504                  &e1->where, &e2->where);
6505       return FAILURE;
6506     }
6507
6508   if (e1->shape)
6509     {
6510       int i;
6511       mpz_t s;
6512
6513       mpz_init (s);
6514
6515       for (i = 0; i < e1->rank; i++)
6516         {
6517           if (tail->u.ar.end[i])
6518             {
6519               mpz_set (s, tail->u.ar.end[i]->value.integer);
6520               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6521               mpz_add_ui (s, s, 1);
6522             }
6523           else
6524             {
6525               mpz_set (s, tail->u.ar.start[i]->value.integer);
6526             }
6527
6528           if (mpz_cmp (e1->shape[i], s) != 0)
6529             {
6530               gfc_error ("Source-expr at %L and allocate-object at %L must "
6531                          "have the same shape", &e1->where, &e2->where);
6532               mpz_clear (s);
6533               return FAILURE;
6534             }
6535         }
6536
6537       mpz_clear (s);
6538     }
6539
6540   return SUCCESS;
6541 }
6542
6543
6544 /* Resolve the expression in an ALLOCATE statement, doing the additional
6545    checks to see whether the expression is OK or not.  The expression must
6546    have a trailing array reference that gives the size of the array.  */
6547
6548 static gfc_try
6549 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6550 {
6551   int i, pointer, allocatable, dimension, check_intent_in, is_abstract;
6552   int codimension;
6553   symbol_attribute attr;
6554   gfc_ref *ref, *ref2;
6555   gfc_array_ref *ar;
6556   gfc_symbol *sym = NULL;
6557   gfc_alloc *a;
6558   gfc_component *c;
6559
6560   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
6561   check_intent_in = 1;
6562
6563   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6564      checking of coarrays.  */
6565   for (ref = e->ref; ref; ref = ref->next)
6566     if (ref->next == NULL)
6567       break;
6568
6569   if (ref && ref->type == REF_ARRAY)
6570     ref->u.ar.in_allocate = true;
6571
6572   if (gfc_resolve_expr (e) == FAILURE)
6573     goto failure;
6574
6575   /* Make sure the expression is allocatable or a pointer.  If it is
6576      pointer, the next-to-last reference must be a pointer.  */
6577
6578   ref2 = NULL;
6579   if (e->symtree)
6580     sym = e->symtree->n.sym;
6581
6582   /* Check whether ultimate component is abstract and CLASS.  */
6583   is_abstract = 0;
6584
6585   if (e->expr_type != EXPR_VARIABLE)
6586     {
6587       allocatable = 0;
6588       attr = gfc_expr_attr (e);
6589       pointer = attr.pointer;
6590       dimension = attr.dimension;
6591       codimension = attr.codimension;
6592     }
6593   else
6594     {
6595       if (sym->ts.type == BT_CLASS)
6596         {
6597           allocatable = CLASS_DATA (sym)->attr.allocatable;
6598           pointer = CLASS_DATA (sym)->attr.class_pointer;
6599           dimension = CLASS_DATA (sym)->attr.dimension;
6600           codimension = CLASS_DATA (sym)->attr.codimension;
6601           is_abstract = CLASS_DATA (sym)->attr.abstract;
6602         }
6603       else
6604         {
6605           allocatable = sym->attr.allocatable;
6606           pointer = sym->attr.pointer;
6607           dimension = sym->attr.dimension;
6608           codimension = sym->attr.codimension;
6609         }
6610
6611       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6612         {
6613           if (pointer)
6614             check_intent_in = 0;
6615
6616           switch (ref->type)
6617             {
6618               case REF_ARRAY:
6619                 if (ref->next != NULL)
6620                   pointer = 0;
6621                 break;
6622
6623               case REF_COMPONENT:
6624                 /* F2008, C644.  */
6625                 if (gfc_is_coindexed (e))
6626                   {
6627                     gfc_error ("Coindexed allocatable object at %L",
6628                                &e->where);
6629                     goto failure;
6630                   }
6631
6632                 c = ref->u.c.component;
6633                 if (c->ts.type == BT_CLASS)
6634                   {
6635                     allocatable = CLASS_DATA (c)->attr.allocatable;
6636                     pointer = CLASS_DATA (c)->attr.class_pointer;
6637                     dimension = CLASS_DATA (c)->attr.dimension;
6638                     codimension = CLASS_DATA (c)->attr.codimension;
6639                     is_abstract = CLASS_DATA (c)->attr.abstract;
6640                   }
6641                 else
6642                   {
6643                     allocatable = c->attr.allocatable;
6644                     pointer = c->attr.pointer;
6645                     dimension = c->attr.dimension;
6646                     codimension = c->attr.codimension;
6647                     is_abstract = c->attr.abstract;
6648                   }
6649                 break;
6650
6651               case REF_SUBSTRING:
6652                 allocatable = 0;
6653                 pointer = 0;
6654                 break;
6655             }
6656         }
6657     }
6658
6659   if (allocatable == 0 && pointer == 0)
6660     {
6661       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6662                  &e->where);
6663       goto failure;
6664     }
6665
6666   /* Some checks for the SOURCE tag.  */
6667   if (code->expr3)
6668     {
6669       /* Check F03:C631.  */
6670       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6671         {
6672           gfc_error ("Type of entity at %L is type incompatible with "
6673                       "source-expr at %L", &e->where, &code->expr3->where);
6674           goto failure;
6675         }
6676
6677       /* Check F03:C632 and restriction following Note 6.18.  */
6678       if (code->expr3->rank > 0
6679           && conformable_arrays (code->expr3, e) == FAILURE)
6680         goto failure;
6681
6682       /* Check F03:C633.  */
6683       if (code->expr3->ts.kind != e->ts.kind)
6684         {
6685           gfc_error ("The allocate-object at %L and the source-expr at %L "
6686                       "shall have the same kind type parameter",
6687                       &e->where, &code->expr3->where);
6688           goto failure;
6689         }
6690     }
6691
6692   /* Check F08:C629.  */
6693   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
6694       && !code->expr3)
6695     {
6696       gcc_assert (e->ts.type == BT_CLASS);
6697       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6698                  "type-spec or source-expr", sym->name, &e->where);
6699       goto failure;
6700     }
6701
6702   if (check_intent_in && sym->attr.intent == INTENT_IN)
6703     {
6704       gfc_error ("Cannot allocate INTENT(IN) variable '%s' at %L",
6705                  sym->name, &e->where);
6706       goto failure;
6707     }
6708     
6709   if (!code->expr3 || code->expr3->mold)
6710     {
6711       /* Add default initializer for those derived types that need them.  */
6712       gfc_expr *init_e = NULL;
6713       gfc_typespec ts;
6714
6715       if (code->ext.alloc.ts.type == BT_DERIVED)
6716         ts = code->ext.alloc.ts;
6717       else if (code->expr3)
6718         ts = code->expr3->ts;
6719       else
6720         ts = e->ts;
6721
6722       if (ts.type == BT_DERIVED)
6723         init_e = gfc_default_initializer (&ts);
6724       /* FIXME: Use default init of dynamic type (cf. PR 44541).  */
6725       else if (e->ts.type == BT_CLASS)
6726         init_e = gfc_default_initializer (&ts.u.derived->components->ts);
6727
6728       if (init_e)
6729         {
6730           gfc_code *init_st = gfc_get_code ();
6731           init_st->loc = code->loc;
6732           init_st->op = EXEC_INIT_ASSIGN;
6733           init_st->expr1 = gfc_expr_to_initialize (e);
6734           init_st->expr2 = init_e;
6735           init_st->next = code->next;
6736           code->next = init_st;
6737         }
6738     }
6739
6740   if (e->ts.type == BT_CLASS)
6741     {
6742       /* Make sure the vtab symbol is present when
6743          the module variables are generated.  */
6744       gfc_typespec ts = e->ts;
6745       if (code->expr3)
6746         ts = code->expr3->ts;
6747       else if (code->ext.alloc.ts.type == BT_DERIVED)
6748         ts = code->ext.alloc.ts;
6749       gfc_find_derived_vtab (ts.u.derived);
6750     }
6751
6752   if (pointer || (dimension == 0 && codimension == 0))
6753     goto success;
6754
6755   /* Make sure the next-to-last reference node is an array specification.  */
6756
6757   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
6758       || (dimension && ref2->u.ar.dimen == 0))
6759     {
6760       gfc_error ("Array specification required in ALLOCATE statement "
6761                  "at %L", &e->where);
6762       goto failure;
6763     }
6764
6765   /* Make sure that the array section reference makes sense in the
6766     context of an ALLOCATE specification.  */
6767
6768   ar = &ref2->u.ar;
6769
6770   if (codimension && ar->codimen == 0)
6771     {
6772       gfc_error ("Coarray specification required in ALLOCATE statement "
6773                  "at %L", &e->where);
6774       goto failure;
6775     }
6776
6777   for (i = 0; i < ar->dimen; i++)
6778     {
6779       if (ref2->u.ar.type == AR_ELEMENT)
6780         goto check_symbols;
6781
6782       switch (ar->dimen_type[i])
6783         {
6784         case DIMEN_ELEMENT:
6785           break;
6786
6787         case DIMEN_RANGE:
6788           if (ar->start[i] != NULL
6789               && ar->end[i] != NULL
6790               && ar->stride[i] == NULL)
6791             break;
6792
6793           /* Fall Through...  */
6794
6795         case DIMEN_UNKNOWN:
6796         case DIMEN_VECTOR:
6797         case DIMEN_STAR:
6798           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6799                      &e->where);
6800           goto failure;
6801         }
6802
6803 check_symbols:
6804       for (a = code->ext.alloc.list; a; a = a->next)
6805         {
6806           sym = a->expr->symtree->n.sym;
6807
6808           /* TODO - check derived type components.  */
6809           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6810             continue;
6811
6812           if ((ar->start[i] != NULL
6813                && gfc_find_sym_in_expr (sym, ar->start[i]))
6814               || (ar->end[i] != NULL
6815                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6816             {
6817               gfc_error ("'%s' must not appear in the array specification at "
6818                          "%L in the same ALLOCATE statement where it is "
6819                          "itself allocated", sym->name, &ar->where);
6820               goto failure;
6821             }
6822         }
6823     }
6824
6825   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
6826     {
6827       if (ar->dimen_type[i] == DIMEN_ELEMENT
6828           || ar->dimen_type[i] == DIMEN_RANGE)
6829         {
6830           if (i == (ar->dimen + ar->codimen - 1))
6831             {
6832               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
6833                          "statement at %L", &e->where);
6834               goto failure;
6835             }
6836           break;
6837         }
6838
6839       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
6840           && ar->stride[i] == NULL)
6841         break;
6842
6843       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
6844                  &e->where);
6845       goto failure;
6846     }
6847
6848   if (codimension && ar->as->rank == 0)
6849     {
6850       gfc_error ("Sorry, allocatable scalar coarrays are not yet supported "
6851                  "at %L", &e->where);
6852       goto failure;
6853     }
6854
6855 success:
6856   return SUCCESS;
6857
6858 failure:
6859   return FAILURE;
6860 }
6861
6862 static void
6863 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6864 {
6865   gfc_expr *stat, *errmsg, *pe, *qe;
6866   gfc_alloc *a, *p, *q;
6867
6868   stat = code->expr1 ? code->expr1 : NULL;
6869
6870   errmsg = code->expr2 ? code->expr2 : NULL;
6871
6872   /* Check the stat variable.  */
6873   if (stat)
6874     {
6875       if (stat->symtree->n.sym->attr.intent == INTENT_IN)
6876         gfc_error ("Stat-variable '%s' at %L cannot be INTENT(IN)",
6877                    stat->symtree->n.sym->name, &stat->where);
6878
6879       if (gfc_pure (NULL) && gfc_impure_variable (stat->symtree->n.sym))
6880         gfc_error ("Illegal stat-variable at %L for a PURE procedure",
6881                    &stat->where);
6882
6883       if ((stat->ts.type != BT_INTEGER
6884            && !(stat->ref && (stat->ref->type == REF_ARRAY
6885                               || stat->ref->type == REF_COMPONENT)))
6886           || stat->rank > 0)
6887         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6888                    "variable", &stat->where);
6889
6890       for (p = code->ext.alloc.list; p; p = p->next)
6891         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6892           {
6893             gfc_ref *ref1, *ref2;
6894             bool found = true;
6895
6896             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
6897                  ref1 = ref1->next, ref2 = ref2->next)
6898               {
6899                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
6900                   continue;
6901                 if (ref1->u.c.component->name != ref2->u.c.component->name)
6902                   {
6903                     found = false;
6904                     break;
6905                   }
6906               }
6907
6908             if (found)
6909               {
6910                 gfc_error ("Stat-variable at %L shall not be %sd within "
6911                            "the same %s statement", &stat->where, fcn, fcn);
6912                 break;
6913               }
6914           }
6915     }
6916
6917   /* Check the errmsg variable.  */
6918   if (errmsg)
6919     {
6920       if (!stat)
6921         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
6922                      &errmsg->where);
6923
6924       if (errmsg->symtree->n.sym->attr.intent == INTENT_IN)
6925         gfc_error ("Errmsg-variable '%s' at %L cannot be INTENT(IN)",
6926                    errmsg->symtree->n.sym->name, &errmsg->where);
6927
6928       if (gfc_pure (NULL) && gfc_impure_variable (errmsg->symtree->n.sym))
6929         gfc_error ("Illegal errmsg-variable at %L for a PURE procedure",
6930                    &errmsg->where);
6931
6932       if ((errmsg->ts.type != BT_CHARACTER
6933            && !(errmsg->ref
6934                 && (errmsg->ref->type == REF_ARRAY
6935                     || errmsg->ref->type == REF_COMPONENT)))
6936           || errmsg->rank > 0 )
6937         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
6938                    "variable", &errmsg->where);
6939
6940       for (p = code->ext.alloc.list; p; p = p->next)
6941         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
6942           {
6943             gfc_ref *ref1, *ref2;
6944             bool found = true;
6945
6946             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
6947                  ref1 = ref1->next, ref2 = ref2->next)
6948               {
6949                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
6950                   continue;
6951                 if (ref1->u.c.component->name != ref2->u.c.component->name)
6952                   {
6953                     found = false;
6954                     break;
6955                   }
6956               }
6957
6958             if (found)
6959               {
6960                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
6961                            "the same %s statement", &errmsg->where, fcn, fcn);
6962                 break;
6963               }
6964           }
6965     }
6966
6967   /* Check that an allocate-object appears only once in the statement.  
6968      FIXME: Checking derived types is disabled.  */
6969   for (p = code->ext.alloc.list; p; p = p->next)
6970     {
6971       pe = p->expr;
6972       if ((pe->ref && pe->ref->type != REF_COMPONENT)
6973            && (pe->symtree->n.sym->ts.type != BT_DERIVED))
6974         {
6975           for (q = p->next; q; q = q->next)
6976             {
6977               qe = q->expr;
6978               if ((qe->ref && qe->ref->type != REF_COMPONENT)
6979                   && (qe->symtree->n.sym->ts.type != BT_DERIVED)
6980                   && (pe->symtree->n.sym->name == qe->symtree->n.sym->name))
6981                 gfc_error ("Allocate-object at %L also appears at %L",
6982                            &pe->where, &qe->where);
6983             }
6984         }
6985     }
6986
6987   if (strcmp (fcn, "ALLOCATE") == 0)
6988     {
6989       for (a = code->ext.alloc.list; a; a = a->next)
6990         resolve_allocate_expr (a->expr, code);
6991     }
6992   else
6993     {
6994       for (a = code->ext.alloc.list; a; a = a->next)
6995         resolve_deallocate_expr (a->expr);
6996     }
6997 }
6998
6999
7000 /************ SELECT CASE resolution subroutines ************/
7001
7002 /* Callback function for our mergesort variant.  Determines interval
7003    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7004    op1 > op2.  Assumes we're not dealing with the default case.  
7005    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7006    There are nine situations to check.  */
7007
7008 static int
7009 compare_cases (const gfc_case *op1, const gfc_case *op2)
7010 {
7011   int retval;
7012
7013   if (op1->low == NULL) /* op1 = (:L)  */
7014     {
7015       /* op2 = (:N), so overlap.  */
7016       retval = 0;
7017       /* op2 = (M:) or (M:N),  L < M  */
7018       if (op2->low != NULL
7019           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7020         retval = -1;
7021     }
7022   else if (op1->high == NULL) /* op1 = (K:)  */
7023     {
7024       /* op2 = (M:), so overlap.  */
7025       retval = 0;
7026       /* op2 = (:N) or (M:N), K > N  */
7027       if (op2->high != NULL
7028           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7029         retval = 1;
7030     }
7031   else /* op1 = (K:L)  */
7032     {
7033       if (op2->low == NULL)       /* op2 = (:N), K > N  */
7034         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7035                  ? 1 : 0;
7036       else if (op2->high == NULL) /* op2 = (M:), L < M  */
7037         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7038                  ? -1 : 0;
7039       else                      /* op2 = (M:N)  */
7040         {
7041           retval =  0;
7042           /* L < M  */
7043           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7044             retval =  -1;
7045           /* K > N  */
7046           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7047             retval =  1;
7048         }
7049     }
7050
7051   return retval;
7052 }
7053
7054
7055 /* Merge-sort a double linked case list, detecting overlap in the
7056    process.  LIST is the head of the double linked case list before it
7057    is sorted.  Returns the head of the sorted list if we don't see any
7058    overlap, or NULL otherwise.  */
7059
7060 static gfc_case *
7061 check_case_overlap (gfc_case *list)
7062 {
7063   gfc_case *p, *q, *e, *tail;
7064   int insize, nmerges, psize, qsize, cmp, overlap_seen;
7065
7066   /* If the passed list was empty, return immediately.  */
7067   if (!list)
7068     return NULL;
7069
7070   overlap_seen = 0;
7071   insize = 1;
7072
7073   /* Loop unconditionally.  The only exit from this loop is a return
7074      statement, when we've finished sorting the case list.  */
7075   for (;;)
7076     {
7077       p = list;
7078       list = NULL;
7079       tail = NULL;
7080
7081       /* Count the number of merges we do in this pass.  */
7082       nmerges = 0;
7083
7084       /* Loop while there exists a merge to be done.  */
7085       while (p)
7086         {
7087           int i;
7088
7089           /* Count this merge.  */
7090           nmerges++;
7091
7092           /* Cut the list in two pieces by stepping INSIZE places
7093              forward in the list, starting from P.  */
7094           psize = 0;
7095           q = p;
7096           for (i = 0; i < insize; i++)
7097             {
7098               psize++;
7099               q = q->right;
7100               if (!q)
7101                 break;
7102             }
7103           qsize = insize;
7104
7105           /* Now we have two lists.  Merge them!  */
7106           while (psize > 0 || (qsize > 0 && q != NULL))
7107             {
7108               /* See from which the next case to merge comes from.  */
7109               if (psize == 0)
7110                 {
7111                   /* P is empty so the next case must come from Q.  */
7112                   e = q;
7113                   q = q->right;
7114                   qsize--;
7115                 }
7116               else if (qsize == 0 || q == NULL)
7117                 {
7118                   /* Q is empty.  */
7119                   e = p;
7120                   p = p->right;
7121                   psize--;
7122                 }
7123               else
7124                 {
7125                   cmp = compare_cases (p, q);
7126                   if (cmp < 0)
7127                     {
7128                       /* The whole case range for P is less than the
7129                          one for Q.  */
7130                       e = p;
7131                       p = p->right;
7132                       psize--;
7133                     }
7134                   else if (cmp > 0)
7135                     {
7136                       /* The whole case range for Q is greater than
7137                          the case range for P.  */
7138                       e = q;
7139                       q = q->right;
7140                       qsize--;
7141                     }
7142                   else
7143                     {
7144                       /* The cases overlap, or they are the same
7145                          element in the list.  Either way, we must
7146                          issue an error and get the next case from P.  */
7147                       /* FIXME: Sort P and Q by line number.  */
7148                       gfc_error ("CASE label at %L overlaps with CASE "
7149                                  "label at %L", &p->where, &q->where);
7150                       overlap_seen = 1;
7151                       e = p;
7152                       p = p->right;
7153                       psize--;
7154                     }
7155                 }
7156
7157                 /* Add the next element to the merged list.  */
7158               if (tail)
7159                 tail->right = e;
7160               else
7161                 list = e;
7162               e->left = tail;
7163               tail = e;
7164             }
7165
7166           /* P has now stepped INSIZE places along, and so has Q.  So
7167              they're the same.  */
7168           p = q;
7169         }
7170       tail->right = NULL;
7171
7172       /* If we have done only one merge or none at all, we've
7173          finished sorting the cases.  */
7174       if (nmerges <= 1)
7175         {
7176           if (!overlap_seen)
7177             return list;
7178           else
7179             return NULL;
7180         }
7181
7182       /* Otherwise repeat, merging lists twice the size.  */
7183       insize *= 2;
7184     }
7185 }
7186
7187
7188 /* Check to see if an expression is suitable for use in a CASE statement.
7189    Makes sure that all case expressions are scalar constants of the same
7190    type.  Return FAILURE if anything is wrong.  */
7191
7192 static gfc_try
7193 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7194 {
7195   if (e == NULL) return SUCCESS;
7196
7197   if (e->ts.type != case_expr->ts.type)
7198     {
7199       gfc_error ("Expression in CASE statement at %L must be of type %s",
7200                  &e->where, gfc_basic_typename (case_expr->ts.type));
7201       return FAILURE;
7202     }
7203
7204   /* C805 (R808) For a given case-construct, each case-value shall be of
7205      the same type as case-expr.  For character type, length differences
7206      are allowed, but the kind type parameters shall be the same.  */
7207
7208   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7209     {
7210       gfc_error ("Expression in CASE statement at %L must be of kind %d",
7211                  &e->where, case_expr->ts.kind);
7212       return FAILURE;
7213     }
7214
7215   /* Convert the case value kind to that of case expression kind,
7216      if needed */
7217
7218   if (e->ts.kind != case_expr->ts.kind)
7219     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7220
7221   if (e->rank != 0)
7222     {
7223       gfc_error ("Expression in CASE statement at %L must be scalar",
7224                  &e->where);
7225       return FAILURE;
7226     }
7227
7228   return SUCCESS;
7229 }
7230
7231
7232 /* Given a completely parsed select statement, we:
7233
7234      - Validate all expressions and code within the SELECT.
7235      - Make sure that the selection expression is not of the wrong type.
7236      - Make sure that no case ranges overlap.
7237      - Eliminate unreachable cases and unreachable code resulting from
7238        removing case labels.
7239
7240    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7241    they are a hassle for code generation, and to prevent that, we just
7242    cut them out here.  This is not necessary for overlapping cases
7243    because they are illegal and we never even try to generate code.
7244
7245    We have the additional caveat that a SELECT construct could have
7246    been a computed GOTO in the source code. Fortunately we can fairly
7247    easily work around that here: The case_expr for a "real" SELECT CASE
7248    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7249    we have to do is make sure that the case_expr is a scalar integer
7250    expression.  */
7251
7252 static void
7253 resolve_select (gfc_code *code)
7254 {
7255   gfc_code *body;
7256   gfc_expr *case_expr;
7257   gfc_case *cp, *default_case, *tail, *head;
7258   int seen_unreachable;
7259   int seen_logical;
7260   int ncases;
7261   bt type;
7262   gfc_try t;
7263
7264   if (code->expr1 == NULL)
7265     {
7266       /* This was actually a computed GOTO statement.  */
7267       case_expr = code->expr2;
7268       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7269         gfc_error ("Selection expression in computed GOTO statement "
7270                    "at %L must be a scalar integer expression",
7271                    &case_expr->where);
7272
7273       /* Further checking is not necessary because this SELECT was built
7274          by the compiler, so it should always be OK.  Just move the
7275          case_expr from expr2 to expr so that we can handle computed
7276          GOTOs as normal SELECTs from here on.  */
7277       code->expr1 = code->expr2;
7278       code->expr2 = NULL;
7279       return;
7280     }
7281
7282   case_expr = code->expr1;
7283
7284   type = case_expr->ts.type;
7285   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7286     {
7287       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7288                  &case_expr->where, gfc_typename (&case_expr->ts));
7289
7290       /* Punt. Going on here just produce more garbage error messages.  */
7291       return;
7292     }
7293
7294   if (case_expr->rank != 0)
7295     {
7296       gfc_error ("Argument of SELECT statement at %L must be a scalar "
7297                  "expression", &case_expr->where);
7298
7299       /* Punt.  */
7300       return;
7301     }
7302
7303
7304   /* Raise a warning if an INTEGER case value exceeds the range of
7305      the case-expr. Later, all expressions will be promoted to the
7306      largest kind of all case-labels.  */
7307
7308   if (type == BT_INTEGER)
7309     for (body = code->block; body; body = body->block)
7310       for (cp = body->ext.case_list; cp; cp = cp->next)
7311         {
7312           if (cp->low
7313               && gfc_check_integer_range (cp->low->value.integer,
7314                                           case_expr->ts.kind) != ARITH_OK)
7315             gfc_warning ("Expression in CASE statement at %L is "
7316                          "not in the range of %s", &cp->low->where,
7317                          gfc_typename (&case_expr->ts));
7318
7319           if (cp->high
7320               && cp->low != cp->high
7321               && gfc_check_integer_range (cp->high->value.integer,
7322                                           case_expr->ts.kind) != ARITH_OK)
7323             gfc_warning ("Expression in CASE statement at %L is "
7324                          "not in the range of %s", &cp->high->where,
7325                          gfc_typename (&case_expr->ts));
7326         }
7327
7328   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7329      of the SELECT CASE expression and its CASE values.  Walk the lists
7330      of case values, and if we find a mismatch, promote case_expr to
7331      the appropriate kind.  */
7332
7333   if (type == BT_LOGICAL || type == BT_INTEGER)
7334     {
7335       for (body = code->block; body; body = body->block)
7336         {
7337           /* Walk the case label list.  */
7338           for (cp = body->ext.case_list; cp; cp = cp->next)
7339             {
7340               /* Intercept the DEFAULT case.  It does not have a kind.  */
7341               if (cp->low == NULL && cp->high == NULL)
7342                 continue;
7343
7344               /* Unreachable case ranges are discarded, so ignore.  */
7345               if (cp->low != NULL && cp->high != NULL
7346                   && cp->low != cp->high
7347                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7348                 continue;
7349
7350               if (cp->low != NULL
7351                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7352                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7353
7354               if (cp->high != NULL
7355                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7356                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7357             }
7358          }
7359     }
7360
7361   /* Assume there is no DEFAULT case.  */
7362   default_case = NULL;
7363   head = tail = NULL;
7364   ncases = 0;
7365   seen_logical = 0;
7366
7367   for (body = code->block; body; body = body->block)
7368     {
7369       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7370       t = SUCCESS;
7371       seen_unreachable = 0;
7372
7373       /* Walk the case label list, making sure that all case labels
7374          are legal.  */
7375       for (cp = body->ext.case_list; cp; cp = cp->next)
7376         {
7377           /* Count the number of cases in the whole construct.  */
7378           ncases++;
7379
7380           /* Intercept the DEFAULT case.  */
7381           if (cp->low == NULL && cp->high == NULL)
7382             {
7383               if (default_case != NULL)
7384                 {
7385                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7386                              "by a second DEFAULT CASE at %L",
7387                              &default_case->where, &cp->where);
7388                   t = FAILURE;
7389                   break;
7390                 }
7391               else
7392                 {
7393                   default_case = cp;
7394                   continue;
7395                 }
7396             }
7397
7398           /* Deal with single value cases and case ranges.  Errors are
7399              issued from the validation function.  */
7400           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7401               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7402             {
7403               t = FAILURE;
7404               break;
7405             }
7406
7407           if (type == BT_LOGICAL
7408               && ((cp->low == NULL || cp->high == NULL)
7409                   || cp->low != cp->high))
7410             {
7411               gfc_error ("Logical range in CASE statement at %L is not "
7412                          "allowed", &cp->low->where);
7413               t = FAILURE;
7414               break;
7415             }
7416
7417           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7418             {
7419               int value;
7420               value = cp->low->value.logical == 0 ? 2 : 1;
7421               if (value & seen_logical)
7422                 {
7423                   gfc_error ("Constant logical value in CASE statement "
7424                              "is repeated at %L",
7425                              &cp->low->where);
7426                   t = FAILURE;
7427                   break;
7428                 }
7429               seen_logical |= value;
7430             }
7431
7432           if (cp->low != NULL && cp->high != NULL
7433               && cp->low != cp->high
7434               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7435             {
7436               if (gfc_option.warn_surprising)
7437                 gfc_warning ("Range specification at %L can never "
7438                              "be matched", &cp->where);
7439
7440               cp->unreachable = 1;
7441               seen_unreachable = 1;
7442             }
7443           else
7444             {
7445               /* If the case range can be matched, it can also overlap with
7446                  other cases.  To make sure it does not, we put it in a
7447                  double linked list here.  We sort that with a merge sort
7448                  later on to detect any overlapping cases.  */
7449               if (!head)
7450                 {
7451                   head = tail = cp;
7452                   head->right = head->left = NULL;
7453                 }
7454               else
7455                 {
7456                   tail->right = cp;
7457                   tail->right->left = tail;
7458                   tail = tail->right;
7459                   tail->right = NULL;
7460                 }
7461             }
7462         }
7463
7464       /* It there was a failure in the previous case label, give up
7465          for this case label list.  Continue with the next block.  */
7466       if (t == FAILURE)
7467         continue;
7468
7469       /* See if any case labels that are unreachable have been seen.
7470          If so, we eliminate them.  This is a bit of a kludge because
7471          the case lists for a single case statement (label) is a
7472          single forward linked lists.  */
7473       if (seen_unreachable)
7474       {
7475         /* Advance until the first case in the list is reachable.  */
7476         while (body->ext.case_list != NULL
7477                && body->ext.case_list->unreachable)
7478           {
7479             gfc_case *n = body->ext.case_list;
7480             body->ext.case_list = body->ext.case_list->next;
7481             n->next = NULL;
7482             gfc_free_case_list (n);
7483           }
7484
7485         /* Strip all other unreachable cases.  */
7486         if (body->ext.case_list)
7487           {
7488             for (cp = body->ext.case_list; cp->next; cp = cp->next)
7489               {
7490                 if (cp->next->unreachable)
7491                   {
7492                     gfc_case *n = cp->next;
7493                     cp->next = cp->next->next;
7494                     n->next = NULL;
7495                     gfc_free_case_list (n);
7496                   }
7497               }
7498           }
7499       }
7500     }
7501
7502   /* See if there were overlapping cases.  If the check returns NULL,
7503      there was overlap.  In that case we don't do anything.  If head
7504      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7505      then used during code generation for SELECT CASE constructs with
7506      a case expression of a CHARACTER type.  */
7507   if (head)
7508     {
7509       head = check_case_overlap (head);
7510
7511       /* Prepend the default_case if it is there.  */
7512       if (head != NULL && default_case)
7513         {
7514           default_case->left = NULL;
7515           default_case->right = head;
7516           head->left = default_case;
7517         }
7518     }
7519
7520   /* Eliminate dead blocks that may be the result if we've seen
7521      unreachable case labels for a block.  */
7522   for (body = code; body && body->block; body = body->block)
7523     {
7524       if (body->block->ext.case_list == NULL)
7525         {
7526           /* Cut the unreachable block from the code chain.  */
7527           gfc_code *c = body->block;
7528           body->block = c->block;
7529
7530           /* Kill the dead block, but not the blocks below it.  */
7531           c->block = NULL;
7532           gfc_free_statements (c);
7533         }
7534     }
7535
7536   /* More than two cases is legal but insane for logical selects.
7537      Issue a warning for it.  */
7538   if (gfc_option.warn_surprising && type == BT_LOGICAL
7539       && ncases > 2)
7540     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7541                  &code->loc);
7542 }
7543
7544
7545 /* Check if a derived type is extensible.  */
7546
7547 bool
7548 gfc_type_is_extensible (gfc_symbol *sym)
7549 {
7550   return !(sym->attr.is_bind_c || sym->attr.sequence);
7551 }
7552
7553
7554 /* Resolve a SELECT TYPE statement.  */
7555
7556 static void
7557 resolve_select_type (gfc_code *code)
7558 {
7559   gfc_symbol *selector_type;
7560   gfc_code *body, *new_st, *if_st, *tail;
7561   gfc_code *class_is = NULL, *default_case = NULL;
7562   gfc_case *c;
7563   gfc_symtree *st;
7564   char name[GFC_MAX_SYMBOL_LEN];
7565   gfc_namespace *ns;
7566   int error = 0;
7567
7568   ns = code->ext.block.ns;
7569   gfc_resolve (ns);
7570
7571   /* Check for F03:C813.  */
7572   if (code->expr1->ts.type != BT_CLASS
7573       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
7574     {
7575       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
7576                  "at %L", &code->loc);
7577       return;
7578     }
7579
7580   if (code->expr2)
7581     {
7582       if (code->expr1->symtree->n.sym->attr.untyped)
7583         code->expr1->symtree->n.sym->ts = code->expr2->ts;
7584       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
7585     }
7586   else
7587     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
7588
7589   /* Loop over TYPE IS / CLASS IS cases.  */
7590   for (body = code->block; body; body = body->block)
7591     {
7592       c = body->ext.case_list;
7593
7594       /* Check F03:C815.  */
7595       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7596           && !gfc_type_is_extensible (c->ts.u.derived))
7597         {
7598           gfc_error ("Derived type '%s' at %L must be extensible",
7599                      c->ts.u.derived->name, &c->where);
7600           error++;
7601           continue;
7602         }
7603
7604       /* Check F03:C816.  */
7605       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7606           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
7607         {
7608           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
7609                      c->ts.u.derived->name, &c->where, selector_type->name);
7610           error++;
7611           continue;
7612         }
7613
7614       /* Intercept the DEFAULT case.  */
7615       if (c->ts.type == BT_UNKNOWN)
7616         {
7617           /* Check F03:C818.  */
7618           if (default_case)
7619             {
7620               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7621                          "by a second DEFAULT CASE at %L",
7622                          &default_case->ext.case_list->where, &c->where);
7623               error++;
7624               continue;
7625             }
7626           else
7627             default_case = body;
7628         }
7629     }
7630     
7631   if (error>0)
7632     return;
7633
7634   if (code->expr2)
7635     {
7636       /* Insert assignment for selector variable.  */
7637       new_st = gfc_get_code ();
7638       new_st->op = EXEC_ASSIGN;
7639       new_st->expr1 = gfc_copy_expr (code->expr1);
7640       new_st->expr2 = gfc_copy_expr (code->expr2);
7641       ns->code = new_st;
7642     }
7643
7644   /* Put SELECT TYPE statement inside a BLOCK.  */
7645   new_st = gfc_get_code ();
7646   new_st->op = code->op;
7647   new_st->expr1 = code->expr1;
7648   new_st->expr2 = code->expr2;
7649   new_st->block = code->block;
7650   if (!ns->code)
7651     ns->code = new_st;
7652   else
7653     ns->code->next = new_st;
7654   code->op = EXEC_BLOCK;
7655   code->ext.block.assoc = NULL;
7656   code->expr1 = code->expr2 =  NULL;
7657   code->block = NULL;
7658
7659   code = new_st;
7660
7661   /* Transform to EXEC_SELECT.  */
7662   code->op = EXEC_SELECT;
7663   gfc_add_component_ref (code->expr1, "$vptr");
7664   gfc_add_component_ref (code->expr1, "$hash");
7665
7666   /* Loop over TYPE IS / CLASS IS cases.  */
7667   for (body = code->block; body; body = body->block)
7668     {
7669       c = body->ext.case_list;
7670
7671       if (c->ts.type == BT_DERIVED)
7672         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
7673                                              c->ts.u.derived->hash_value);
7674
7675       else if (c->ts.type == BT_UNKNOWN)
7676         continue;
7677
7678       /* Assign temporary to selector.  */
7679       if (c->ts.type == BT_CLASS)
7680         sprintf (name, "tmp$class$%s", c->ts.u.derived->name);
7681       else
7682         sprintf (name, "tmp$type$%s", c->ts.u.derived->name);
7683       st = gfc_find_symtree (ns->sym_root, name);
7684       new_st = gfc_get_code ();
7685       new_st->expr1 = gfc_get_variable_expr (st);
7686       new_st->expr2 = gfc_get_variable_expr (code->expr1->symtree);
7687       if (c->ts.type == BT_DERIVED)
7688         {
7689           new_st->op = EXEC_POINTER_ASSIGN;
7690           gfc_add_component_ref (new_st->expr2, "$data");
7691         }
7692       else
7693         new_st->op = EXEC_POINTER_ASSIGN;
7694       new_st->next = body->next;
7695       body->next = new_st;
7696     }
7697     
7698   /* Take out CLASS IS cases for separate treatment.  */
7699   body = code;
7700   while (body && body->block)
7701     {
7702       if (body->block->ext.case_list->ts.type == BT_CLASS)
7703         {
7704           /* Add to class_is list.  */
7705           if (class_is == NULL)
7706             { 
7707               class_is = body->block;
7708               tail = class_is;
7709             }
7710           else
7711             {
7712               for (tail = class_is; tail->block; tail = tail->block) ;
7713               tail->block = body->block;
7714               tail = tail->block;
7715             }
7716           /* Remove from EXEC_SELECT list.  */
7717           body->block = body->block->block;
7718           tail->block = NULL;
7719         }
7720       else
7721         body = body->block;
7722     }
7723
7724   if (class_is)
7725     {
7726       gfc_symbol *vtab;
7727       
7728       if (!default_case)
7729         {
7730           /* Add a default case to hold the CLASS IS cases.  */
7731           for (tail = code; tail->block; tail = tail->block) ;
7732           tail->block = gfc_get_code ();
7733           tail = tail->block;
7734           tail->op = EXEC_SELECT_TYPE;
7735           tail->ext.case_list = gfc_get_case ();
7736           tail->ext.case_list->ts.type = BT_UNKNOWN;
7737           tail->next = NULL;
7738           default_case = tail;
7739         }
7740
7741       /* More than one CLASS IS block?  */
7742       if (class_is->block)
7743         {
7744           gfc_code **c1,*c2;
7745           bool swapped;
7746           /* Sort CLASS IS blocks by extension level.  */
7747           do
7748             {
7749               swapped = false;
7750               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
7751                 {
7752                   c2 = (*c1)->block;
7753                   /* F03:C817 (check for doubles).  */
7754                   if ((*c1)->ext.case_list->ts.u.derived->hash_value
7755                       == c2->ext.case_list->ts.u.derived->hash_value)
7756                     {
7757                       gfc_error ("Double CLASS IS block in SELECT TYPE "
7758                                  "statement at %L", &c2->ext.case_list->where);
7759                       return;
7760                     }
7761                   if ((*c1)->ext.case_list->ts.u.derived->attr.extension
7762                       < c2->ext.case_list->ts.u.derived->attr.extension)
7763                     {
7764                       /* Swap.  */
7765                       (*c1)->block = c2->block;
7766                       c2->block = *c1;
7767                       *c1 = c2;
7768                       swapped = true;
7769                     }
7770                 }
7771             }
7772           while (swapped);
7773         }
7774         
7775       /* Generate IF chain.  */
7776       if_st = gfc_get_code ();
7777       if_st->op = EXEC_IF;
7778       new_st = if_st;
7779       for (body = class_is; body; body = body->block)
7780         {
7781           new_st->block = gfc_get_code ();
7782           new_st = new_st->block;
7783           new_st->op = EXEC_IF;
7784           /* Set up IF condition: Call _gfortran_is_extension_of.  */
7785           new_st->expr1 = gfc_get_expr ();
7786           new_st->expr1->expr_type = EXPR_FUNCTION;
7787           new_st->expr1->ts.type = BT_LOGICAL;
7788           new_st->expr1->ts.kind = 4;
7789           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
7790           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
7791           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
7792           /* Set up arguments.  */
7793           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
7794           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
7795           gfc_add_component_ref (new_st->expr1->value.function.actual->expr, "$vptr");
7796           vtab = gfc_find_derived_vtab (body->ext.case_list->ts.u.derived);
7797           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
7798           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
7799           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
7800           new_st->next = body->next;
7801         }
7802         if (default_case->next)
7803           {
7804             new_st->block = gfc_get_code ();
7805             new_st = new_st->block;
7806             new_st->op = EXEC_IF;
7807             new_st->next = default_case->next;
7808           }
7809           
7810         /* Replace CLASS DEFAULT code by the IF chain.  */
7811         default_case->next = if_st;
7812     }
7813
7814   resolve_select (code);
7815
7816 }
7817
7818
7819 /* Resolve a transfer statement. This is making sure that:
7820    -- a derived type being transferred has only non-pointer components
7821    -- a derived type being transferred doesn't have private components, unless 
7822       it's being transferred from the module where the type was defined
7823    -- we're not trying to transfer a whole assumed size array.  */
7824
7825 static void
7826 resolve_transfer (gfc_code *code)
7827 {
7828   gfc_typespec *ts;
7829   gfc_symbol *sym;
7830   gfc_ref *ref;
7831   gfc_expr *exp;
7832
7833   exp = code->expr1;
7834
7835   while (exp != NULL && exp->expr_type == EXPR_OP
7836          && exp->value.op.op == INTRINSIC_PARENTHESES)
7837     exp = exp->value.op.op1;
7838
7839   if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
7840                       && exp->expr_type != EXPR_FUNCTION))
7841     return;
7842
7843   sym = exp->symtree->n.sym;
7844   ts = &sym->ts;
7845
7846   /* Go to actual component transferred.  */
7847   for (ref = code->expr1->ref; ref; ref = ref->next)
7848     if (ref->type == REF_COMPONENT)
7849       ts = &ref->u.c.component->ts;
7850
7851   if (ts->type == BT_DERIVED)
7852     {
7853       /* Check that transferred derived type doesn't contain POINTER
7854          components.  */
7855       if (ts->u.derived->attr.pointer_comp)
7856         {
7857           gfc_error ("Data transfer element at %L cannot have "
7858                      "POINTER components", &code->loc);
7859           return;
7860         }
7861
7862       if (ts->u.derived->attr.alloc_comp)
7863         {
7864           gfc_error ("Data transfer element at %L cannot have "
7865                      "ALLOCATABLE components", &code->loc);
7866           return;
7867         }
7868
7869       if (derived_inaccessible (ts->u.derived))
7870         {
7871           gfc_error ("Data transfer element at %L cannot have "
7872                      "PRIVATE components",&code->loc);
7873           return;
7874         }
7875     }
7876
7877   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
7878       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
7879     {
7880       gfc_error ("Data transfer element at %L cannot be a full reference to "
7881                  "an assumed-size array", &code->loc);
7882       return;
7883     }
7884 }
7885
7886
7887 /*********** Toplevel code resolution subroutines ***********/
7888
7889 /* Find the set of labels that are reachable from this block.  We also
7890    record the last statement in each block.  */
7891      
7892 static void
7893 find_reachable_labels (gfc_code *block)
7894 {
7895   gfc_code *c;
7896
7897   if (!block)
7898     return;
7899
7900   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
7901
7902   /* Collect labels in this block.  We don't keep those corresponding
7903      to END {IF|SELECT}, these are checked in resolve_branch by going
7904      up through the code_stack.  */
7905   for (c = block; c; c = c->next)
7906     {
7907       if (c->here && c->op != EXEC_END_BLOCK)
7908         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
7909     }
7910
7911   /* Merge with labels from parent block.  */
7912   if (cs_base->prev)
7913     {
7914       gcc_assert (cs_base->prev->reachable_labels);
7915       bitmap_ior_into (cs_base->reachable_labels,
7916                        cs_base->prev->reachable_labels);
7917     }
7918 }
7919
7920
7921 static void
7922 resolve_sync (gfc_code *code)
7923 {
7924   /* Check imageset. The * case matches expr1 == NULL.  */
7925   if (code->expr1)
7926     {
7927       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
7928         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
7929                    "INTEGER expression", &code->expr1->where);
7930       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
7931           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
7932         gfc_error ("Imageset argument at %L must between 1 and num_images()",
7933                    &code->expr1->where);
7934       else if (code->expr1->expr_type == EXPR_ARRAY
7935                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
7936         {
7937            gfc_constructor *cons;
7938            cons = gfc_constructor_first (code->expr1->value.constructor);
7939            for (; cons; cons = gfc_constructor_next (cons))
7940              if (cons->expr->expr_type == EXPR_CONSTANT
7941                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
7942                gfc_error ("Imageset argument at %L must between 1 and "
7943                           "num_images()", &cons->expr->where);
7944         }
7945     }
7946
7947   /* Check STAT.  */
7948   if (code->expr2
7949       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
7950           || code->expr2->expr_type != EXPR_VARIABLE))
7951     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
7952                &code->expr2->where);
7953
7954   /* Check ERRMSG.  */
7955   if (code->expr3
7956       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
7957           || code->expr3->expr_type != EXPR_VARIABLE))
7958     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
7959                &code->expr3->where);
7960 }
7961
7962
7963 /* Given a branch to a label, see if the branch is conforming.
7964    The code node describes where the branch is located.  */
7965
7966 static void
7967 resolve_branch (gfc_st_label *label, gfc_code *code)
7968 {
7969   code_stack *stack;
7970
7971   if (label == NULL)
7972     return;
7973
7974   /* Step one: is this a valid branching target?  */
7975
7976   if (label->defined == ST_LABEL_UNKNOWN)
7977     {
7978       gfc_error ("Label %d referenced at %L is never defined", label->value,
7979                  &label->where);
7980       return;
7981     }
7982
7983   if (label->defined != ST_LABEL_TARGET)
7984     {
7985       gfc_error ("Statement at %L is not a valid branch target statement "
7986                  "for the branch statement at %L", &label->where, &code->loc);
7987       return;
7988     }
7989
7990   /* Step two: make sure this branch is not a branch to itself ;-)  */
7991
7992   if (code->here == label)
7993     {
7994       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
7995       return;
7996     }
7997
7998   /* Step three:  See if the label is in the same block as the
7999      branching statement.  The hard work has been done by setting up
8000      the bitmap reachable_labels.  */
8001
8002   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8003     {
8004       /* Check now whether there is a CRITICAL construct; if so, check
8005          whether the label is still visible outside of the CRITICAL block,
8006          which is invalid.  */
8007       for (stack = cs_base; stack; stack = stack->prev)
8008         if (stack->current->op == EXEC_CRITICAL
8009             && bitmap_bit_p (stack->reachable_labels, label->value))
8010           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8011                       " at %L", &code->loc, &label->where);
8012
8013       return;
8014     }
8015
8016   /* Step four:  If we haven't found the label in the bitmap, it may
8017     still be the label of the END of the enclosing block, in which
8018     case we find it by going up the code_stack.  */
8019
8020   for (stack = cs_base; stack; stack = stack->prev)
8021     {
8022       if (stack->current->next && stack->current->next->here == label)
8023         break;
8024       if (stack->current->op == EXEC_CRITICAL)
8025         {
8026           /* Note: A label at END CRITICAL does not leave the CRITICAL
8027              construct as END CRITICAL is still part of it.  */
8028           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8029                       " at %L", &code->loc, &label->where);
8030           return;
8031         }
8032     }
8033
8034   if (stack)
8035     {
8036       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
8037       return;
8038     }
8039
8040   /* The label is not in an enclosing block, so illegal.  This was
8041      allowed in Fortran 66, so we allow it as extension.  No
8042      further checks are necessary in this case.  */
8043   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
8044                   "as the GOTO statement at %L", &label->where,
8045                   &code->loc);
8046   return;
8047 }
8048
8049
8050 /* Check whether EXPR1 has the same shape as EXPR2.  */
8051
8052 static gfc_try
8053 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8054 {
8055   mpz_t shape[GFC_MAX_DIMENSIONS];
8056   mpz_t shape2[GFC_MAX_DIMENSIONS];
8057   gfc_try result = FAILURE;
8058   int i;
8059
8060   /* Compare the rank.  */
8061   if (expr1->rank != expr2->rank)
8062     return result;
8063
8064   /* Compare the size of each dimension.  */
8065   for (i=0; i<expr1->rank; i++)
8066     {
8067       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
8068         goto ignore;
8069
8070       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
8071         goto ignore;
8072
8073       if (mpz_cmp (shape[i], shape2[i]))
8074         goto over;
8075     }
8076
8077   /* When either of the two expression is an assumed size array, we
8078      ignore the comparison of dimension sizes.  */
8079 ignore:
8080   result = SUCCESS;
8081
8082 over:
8083   for (i--; i >= 0; i--)
8084     {
8085       mpz_clear (shape[i]);
8086       mpz_clear (shape2[i]);
8087     }
8088   return result;
8089 }
8090
8091
8092 /* Check whether a WHERE assignment target or a WHERE mask expression
8093    has the same shape as the outmost WHERE mask expression.  */
8094
8095 static void
8096 resolve_where (gfc_code *code, gfc_expr *mask)
8097 {
8098   gfc_code *cblock;
8099   gfc_code *cnext;
8100   gfc_expr *e = NULL;
8101
8102   cblock = code->block;
8103
8104   /* Store the first WHERE mask-expr of the WHERE statement or construct.
8105      In case of nested WHERE, only the outmost one is stored.  */
8106   if (mask == NULL) /* outmost WHERE */
8107     e = cblock->expr1;
8108   else /* inner WHERE */
8109     e = mask;
8110
8111   while (cblock)
8112     {
8113       if (cblock->expr1)
8114         {
8115           /* Check if the mask-expr has a consistent shape with the
8116              outmost WHERE mask-expr.  */
8117           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
8118             gfc_error ("WHERE mask at %L has inconsistent shape",
8119                        &cblock->expr1->where);
8120          }
8121
8122       /* the assignment statement of a WHERE statement, or the first
8123          statement in where-body-construct of a WHERE construct */
8124       cnext = cblock->next;
8125       while (cnext)
8126         {
8127           switch (cnext->op)
8128             {
8129             /* WHERE assignment statement */
8130             case EXEC_ASSIGN:
8131
8132               /* Check shape consistent for WHERE assignment target.  */
8133               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
8134                gfc_error ("WHERE assignment target at %L has "
8135                           "inconsistent shape", &cnext->expr1->where);
8136               break;
8137
8138   
8139             case EXEC_ASSIGN_CALL:
8140               resolve_call (cnext);
8141               if (!cnext->resolved_sym->attr.elemental)
8142                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8143                           &cnext->ext.actual->expr->where);
8144               break;
8145
8146             /* WHERE or WHERE construct is part of a where-body-construct */
8147             case EXEC_WHERE:
8148               resolve_where (cnext, e);
8149               break;
8150
8151             default:
8152               gfc_error ("Unsupported statement inside WHERE at %L",
8153                          &cnext->loc);
8154             }
8155          /* the next statement within the same where-body-construct */
8156          cnext = cnext->next;
8157        }
8158     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8159     cblock = cblock->block;
8160   }
8161 }
8162
8163
8164 /* Resolve assignment in FORALL construct.
8165    NVAR is the number of FORALL index variables, and VAR_EXPR records the
8166    FORALL index variables.  */
8167
8168 static void
8169 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8170 {
8171   int n;
8172
8173   for (n = 0; n < nvar; n++)
8174     {
8175       gfc_symbol *forall_index;
8176
8177       forall_index = var_expr[n]->symtree->n.sym;
8178
8179       /* Check whether the assignment target is one of the FORALL index
8180          variable.  */
8181       if ((code->expr1->expr_type == EXPR_VARIABLE)
8182           && (code->expr1->symtree->n.sym == forall_index))
8183         gfc_error ("Assignment to a FORALL index variable at %L",
8184                    &code->expr1->where);
8185       else
8186         {
8187           /* If one of the FORALL index variables doesn't appear in the
8188              assignment variable, then there could be a many-to-one
8189              assignment.  Emit a warning rather than an error because the
8190              mask could be resolving this problem.  */
8191           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
8192             gfc_warning ("The FORALL with index '%s' is not used on the "
8193                          "left side of the assignment at %L and so might "
8194                          "cause multiple assignment to this object",
8195                          var_expr[n]->symtree->name, &code->expr1->where);
8196         }
8197     }
8198 }
8199
8200
8201 /* Resolve WHERE statement in FORALL construct.  */
8202
8203 static void
8204 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
8205                                   gfc_expr **var_expr)
8206 {
8207   gfc_code *cblock;
8208   gfc_code *cnext;
8209
8210   cblock = code->block;
8211   while (cblock)
8212     {
8213       /* the assignment statement of a WHERE statement, or the first
8214          statement in where-body-construct of a WHERE construct */
8215       cnext = cblock->next;
8216       while (cnext)
8217         {
8218           switch (cnext->op)
8219             {
8220             /* WHERE assignment statement */
8221             case EXEC_ASSIGN:
8222               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
8223               break;
8224   
8225             /* WHERE operator assignment statement */
8226             case EXEC_ASSIGN_CALL:
8227               resolve_call (cnext);
8228               if (!cnext->resolved_sym->attr.elemental)
8229                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8230                           &cnext->ext.actual->expr->where);
8231               break;
8232
8233             /* WHERE or WHERE construct is part of a where-body-construct */
8234             case EXEC_WHERE:
8235               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
8236               break;
8237
8238             default:
8239               gfc_error ("Unsupported statement inside WHERE at %L",
8240                          &cnext->loc);
8241             }
8242           /* the next statement within the same where-body-construct */
8243           cnext = cnext->next;
8244         }
8245       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8246       cblock = cblock->block;
8247     }
8248 }
8249
8250
8251 /* Traverse the FORALL body to check whether the following errors exist:
8252    1. For assignment, check if a many-to-one assignment happens.
8253    2. For WHERE statement, check the WHERE body to see if there is any
8254       many-to-one assignment.  */
8255
8256 static void
8257 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
8258 {
8259   gfc_code *c;
8260
8261   c = code->block->next;
8262   while (c)
8263     {
8264       switch (c->op)
8265         {
8266         case EXEC_ASSIGN:
8267         case EXEC_POINTER_ASSIGN:
8268           gfc_resolve_assign_in_forall (c, nvar, var_expr);
8269           break;
8270
8271         case EXEC_ASSIGN_CALL:
8272           resolve_call (c);
8273           break;
8274
8275         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
8276            there is no need to handle it here.  */
8277         case EXEC_FORALL:
8278           break;
8279         case EXEC_WHERE:
8280           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
8281           break;
8282         default:
8283           break;
8284         }
8285       /* The next statement in the FORALL body.  */
8286       c = c->next;
8287     }
8288 }
8289
8290
8291 /* Counts the number of iterators needed inside a forall construct, including
8292    nested forall constructs. This is used to allocate the needed memory 
8293    in gfc_resolve_forall.  */
8294
8295 static int 
8296 gfc_count_forall_iterators (gfc_code *code)
8297 {
8298   int max_iters, sub_iters, current_iters;
8299   gfc_forall_iterator *fa;
8300
8301   gcc_assert(code->op == EXEC_FORALL);
8302   max_iters = 0;
8303   current_iters = 0;
8304
8305   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8306     current_iters ++;
8307   
8308   code = code->block->next;
8309
8310   while (code)
8311     {          
8312       if (code->op == EXEC_FORALL)
8313         {
8314           sub_iters = gfc_count_forall_iterators (code);
8315           if (sub_iters > max_iters)
8316             max_iters = sub_iters;
8317         }
8318       code = code->next;
8319     }
8320
8321   return current_iters + max_iters;
8322 }
8323
8324
8325 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8326    gfc_resolve_forall_body to resolve the FORALL body.  */
8327
8328 static void
8329 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8330 {
8331   static gfc_expr **var_expr;
8332   static int total_var = 0;
8333   static int nvar = 0;
8334   int old_nvar, tmp;
8335   gfc_forall_iterator *fa;
8336   int i;
8337
8338   old_nvar = nvar;
8339
8340   /* Start to resolve a FORALL construct   */
8341   if (forall_save == 0)
8342     {
8343       /* Count the total number of FORALL index in the nested FORALL
8344          construct in order to allocate the VAR_EXPR with proper size.  */
8345       total_var = gfc_count_forall_iterators (code);
8346
8347       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8348       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
8349     }
8350
8351   /* The information about FORALL iterator, including FORALL index start, end
8352      and stride. The FORALL index can not appear in start, end or stride.  */
8353   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8354     {
8355       /* Check if any outer FORALL index name is the same as the current
8356          one.  */
8357       for (i = 0; i < nvar; i++)
8358         {
8359           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8360             {
8361               gfc_error ("An outer FORALL construct already has an index "
8362                          "with this name %L", &fa->var->where);
8363             }
8364         }
8365
8366       /* Record the current FORALL index.  */
8367       var_expr[nvar] = gfc_copy_expr (fa->var);
8368
8369       nvar++;
8370
8371       /* No memory leak.  */
8372       gcc_assert (nvar <= total_var);
8373     }
8374
8375   /* Resolve the FORALL body.  */
8376   gfc_resolve_forall_body (code, nvar, var_expr);
8377
8378   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8379   gfc_resolve_blocks (code->block, ns);
8380
8381   tmp = nvar;
8382   nvar = old_nvar;
8383   /* Free only the VAR_EXPRs allocated in this frame.  */
8384   for (i = nvar; i < tmp; i++)
8385      gfc_free_expr (var_expr[i]);
8386
8387   if (nvar == 0)
8388     {
8389       /* We are in the outermost FORALL construct.  */
8390       gcc_assert (forall_save == 0);
8391
8392       /* VAR_EXPR is not needed any more.  */
8393       gfc_free (var_expr);
8394       total_var = 0;
8395     }
8396 }
8397
8398
8399 /* Resolve a BLOCK construct statement.  */
8400
8401 static void
8402 resolve_block_construct (gfc_code* code)
8403 {
8404   /* Resolve the BLOCK's namespace.  */
8405   gfc_resolve (code->ext.block.ns);
8406
8407   /* For an ASSOCIATE block, the associations (and their targets) are already
8408      resolved during gfc_resolve_symbol.  */
8409 }
8410
8411
8412 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
8413    DO code nodes.  */
8414
8415 static void resolve_code (gfc_code *, gfc_namespace *);
8416
8417 void
8418 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8419 {
8420   gfc_try t;
8421
8422   for (; b; b = b->block)
8423     {
8424       t = gfc_resolve_expr (b->expr1);
8425       if (gfc_resolve_expr (b->expr2) == FAILURE)
8426         t = FAILURE;
8427
8428       switch (b->op)
8429         {
8430         case EXEC_IF:
8431           if (t == SUCCESS && b->expr1 != NULL
8432               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8433             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8434                        &b->expr1->where);
8435           break;
8436
8437         case EXEC_WHERE:
8438           if (t == SUCCESS
8439               && b->expr1 != NULL
8440               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8441             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8442                        &b->expr1->where);
8443           break;
8444
8445         case EXEC_GOTO:
8446           resolve_branch (b->label1, b);
8447           break;
8448
8449         case EXEC_BLOCK:
8450           resolve_block_construct (b);
8451           break;
8452
8453         case EXEC_SELECT:
8454         case EXEC_SELECT_TYPE:
8455         case EXEC_FORALL:
8456         case EXEC_DO:
8457         case EXEC_DO_WHILE:
8458         case EXEC_CRITICAL:
8459         case EXEC_READ:
8460         case EXEC_WRITE:
8461         case EXEC_IOLENGTH:
8462         case EXEC_WAIT:
8463           break;
8464
8465         case EXEC_OMP_ATOMIC:
8466         case EXEC_OMP_CRITICAL:
8467         case EXEC_OMP_DO:
8468         case EXEC_OMP_MASTER:
8469         case EXEC_OMP_ORDERED:
8470         case EXEC_OMP_PARALLEL:
8471         case EXEC_OMP_PARALLEL_DO:
8472         case EXEC_OMP_PARALLEL_SECTIONS:
8473         case EXEC_OMP_PARALLEL_WORKSHARE:
8474         case EXEC_OMP_SECTIONS:
8475         case EXEC_OMP_SINGLE:
8476         case EXEC_OMP_TASK:
8477         case EXEC_OMP_TASKWAIT:
8478         case EXEC_OMP_WORKSHARE:
8479           break;
8480
8481         default:
8482           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
8483         }
8484
8485       resolve_code (b->next, ns);
8486     }
8487 }
8488
8489
8490 /* Does everything to resolve an ordinary assignment.  Returns true
8491    if this is an interface assignment.  */
8492 static bool
8493 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
8494 {
8495   bool rval = false;
8496   gfc_expr *lhs;
8497   gfc_expr *rhs;
8498   int llen = 0;
8499   int rlen = 0;
8500   int n;
8501   gfc_ref *ref;
8502
8503   if (gfc_extend_assign (code, ns) == SUCCESS)
8504     {
8505       gfc_expr** rhsptr;
8506
8507       if (code->op == EXEC_ASSIGN_CALL)
8508         {
8509           lhs = code->ext.actual->expr;
8510           rhsptr = &code->ext.actual->next->expr;
8511         }
8512       else
8513         {
8514           gfc_actual_arglist* args;
8515           gfc_typebound_proc* tbp;
8516
8517           gcc_assert (code->op == EXEC_COMPCALL);
8518
8519           args = code->expr1->value.compcall.actual;
8520           lhs = args->expr;
8521           rhsptr = &args->next->expr;
8522
8523           tbp = code->expr1->value.compcall.tbp;
8524           gcc_assert (!tbp->is_generic);
8525         }
8526
8527       /* Make a temporary rhs when there is a default initializer
8528          and rhs is the same symbol as the lhs.  */
8529       if ((*rhsptr)->expr_type == EXPR_VARIABLE
8530             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
8531             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
8532             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
8533         *rhsptr = gfc_get_parentheses (*rhsptr);
8534
8535       return true;
8536     }
8537
8538   lhs = code->expr1;
8539   rhs = code->expr2;
8540
8541   if (rhs->is_boz
8542       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
8543                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
8544                          &code->loc) == FAILURE)
8545     return false;
8546
8547   /* Handle the case of a BOZ literal on the RHS.  */
8548   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
8549     {
8550       int rc;
8551       if (gfc_option.warn_surprising)
8552         gfc_warning ("BOZ literal at %L is bitwise transferred "
8553                      "non-integer symbol '%s'", &code->loc,
8554                      lhs->symtree->n.sym->name);
8555
8556       if (!gfc_convert_boz (rhs, &lhs->ts))
8557         return false;
8558       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
8559         {
8560           if (rc == ARITH_UNDERFLOW)
8561             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
8562                        ". This check can be disabled with the option "
8563                        "-fno-range-check", &rhs->where);
8564           else if (rc == ARITH_OVERFLOW)
8565             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
8566                        ". This check can be disabled with the option "
8567                        "-fno-range-check", &rhs->where);
8568           else if (rc == ARITH_NAN)
8569             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
8570                        ". This check can be disabled with the option "
8571                        "-fno-range-check", &rhs->where);
8572           return false;
8573         }
8574     }
8575
8576
8577   if (lhs->ts.type == BT_CHARACTER
8578         && gfc_option.warn_character_truncation)
8579     {
8580       if (lhs->ts.u.cl != NULL
8581             && lhs->ts.u.cl->length != NULL
8582             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8583         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
8584
8585       if (rhs->expr_type == EXPR_CONSTANT)
8586         rlen = rhs->value.character.length;
8587
8588       else if (rhs->ts.u.cl != NULL
8589                  && rhs->ts.u.cl->length != NULL
8590                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8591         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
8592
8593       if (rlen && llen && rlen > llen)
8594         gfc_warning_now ("CHARACTER expression will be truncated "
8595                          "in assignment (%d/%d) at %L",
8596                          llen, rlen, &code->loc);
8597     }
8598
8599   /* Ensure that a vector index expression for the lvalue is evaluated
8600      to a temporary if the lvalue symbol is referenced in it.  */
8601   if (lhs->rank)
8602     {
8603       for (ref = lhs->ref; ref; ref= ref->next)
8604         if (ref->type == REF_ARRAY)
8605           {
8606             for (n = 0; n < ref->u.ar.dimen; n++)
8607               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
8608                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
8609                                            ref->u.ar.start[n]))
8610                 ref->u.ar.start[n]
8611                         = gfc_get_parentheses (ref->u.ar.start[n]);
8612           }
8613     }
8614
8615   if (gfc_pure (NULL))
8616     {
8617       if (gfc_impure_variable (lhs->symtree->n.sym))
8618         {
8619           gfc_error ("Cannot assign to variable '%s' in PURE "
8620                      "procedure at %L",
8621                       lhs->symtree->n.sym->name,
8622                       &lhs->where);
8623           return rval;
8624         }
8625
8626       if (lhs->ts.type == BT_DERIVED
8627             && lhs->expr_type == EXPR_VARIABLE
8628             && lhs->ts.u.derived->attr.pointer_comp
8629             && rhs->expr_type == EXPR_VARIABLE
8630             && (gfc_impure_variable (rhs->symtree->n.sym)
8631                 || gfc_is_coindexed (rhs)))
8632         {
8633           /* F2008, C1283.  */
8634           if (gfc_is_coindexed (rhs))
8635             gfc_error ("Coindexed expression at %L is assigned to "
8636                         "a derived type variable with a POINTER "
8637                         "component in a PURE procedure",
8638                         &rhs->where);
8639           else
8640             gfc_error ("The impure variable at %L is assigned to "
8641                         "a derived type variable with a POINTER "
8642                         "component in a PURE procedure (12.6)",
8643                         &rhs->where);
8644           return rval;
8645         }
8646
8647       /* Fortran 2008, C1283.  */
8648       if (gfc_is_coindexed (lhs))
8649         {
8650           gfc_error ("Assignment to coindexed variable at %L in a PURE "
8651                      "procedure", &rhs->where);
8652           return rval;
8653         }
8654     }
8655
8656   /* F03:7.4.1.2.  */
8657   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
8658      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
8659   if (lhs->ts.type == BT_CLASS)
8660     {
8661       gfc_error ("Variable must not be polymorphic in assignment at %L",
8662                  &lhs->where);
8663       return false;
8664     }
8665
8666   /* F2008, Section 7.2.1.2.  */
8667   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
8668     {
8669       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
8670                  "component in assignment at %L", &lhs->where);
8671       return false;
8672     }
8673
8674   gfc_check_assign (lhs, rhs, 1);
8675   return false;
8676 }
8677
8678
8679 /* Given a block of code, recursively resolve everything pointed to by this
8680    code block.  */
8681
8682 static void
8683 resolve_code (gfc_code *code, gfc_namespace *ns)
8684 {
8685   int omp_workshare_save;
8686   int forall_save;
8687   code_stack frame;
8688   gfc_try t;
8689
8690   frame.prev = cs_base;
8691   frame.head = code;
8692   cs_base = &frame;
8693
8694   find_reachable_labels (code);
8695
8696   for (; code; code = code->next)
8697     {
8698       frame.current = code;
8699       forall_save = forall_flag;
8700
8701       if (code->op == EXEC_FORALL)
8702         {
8703           forall_flag = 1;
8704           gfc_resolve_forall (code, ns, forall_save);
8705           forall_flag = 2;
8706         }
8707       else if (code->block)
8708         {
8709           omp_workshare_save = -1;
8710           switch (code->op)
8711             {
8712             case EXEC_OMP_PARALLEL_WORKSHARE:
8713               omp_workshare_save = omp_workshare_flag;
8714               omp_workshare_flag = 1;
8715               gfc_resolve_omp_parallel_blocks (code, ns);
8716               break;
8717             case EXEC_OMP_PARALLEL:
8718             case EXEC_OMP_PARALLEL_DO:
8719             case EXEC_OMP_PARALLEL_SECTIONS:
8720             case EXEC_OMP_TASK:
8721               omp_workshare_save = omp_workshare_flag;
8722               omp_workshare_flag = 0;
8723               gfc_resolve_omp_parallel_blocks (code, ns);
8724               break;
8725             case EXEC_OMP_DO:
8726               gfc_resolve_omp_do_blocks (code, ns);
8727               break;
8728             case EXEC_SELECT_TYPE:
8729               gfc_current_ns = code->ext.block.ns;
8730               gfc_resolve_blocks (code->block, gfc_current_ns);
8731               gfc_current_ns = ns;
8732               break;
8733             case EXEC_OMP_WORKSHARE:
8734               omp_workshare_save = omp_workshare_flag;
8735               omp_workshare_flag = 1;
8736               /* FALLTHROUGH */
8737             default:
8738               gfc_resolve_blocks (code->block, ns);
8739               break;
8740             }
8741
8742           if (omp_workshare_save != -1)
8743             omp_workshare_flag = omp_workshare_save;
8744         }
8745
8746       t = SUCCESS;
8747       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
8748         t = gfc_resolve_expr (code->expr1);
8749       forall_flag = forall_save;
8750
8751       if (gfc_resolve_expr (code->expr2) == FAILURE)
8752         t = FAILURE;
8753
8754       if (code->op == EXEC_ALLOCATE
8755           && gfc_resolve_expr (code->expr3) == FAILURE)
8756         t = FAILURE;
8757
8758       switch (code->op)
8759         {
8760         case EXEC_NOP:
8761         case EXEC_END_BLOCK:
8762         case EXEC_CYCLE:
8763         case EXEC_PAUSE:
8764         case EXEC_STOP:
8765         case EXEC_ERROR_STOP:
8766         case EXEC_EXIT:
8767         case EXEC_CONTINUE:
8768         case EXEC_DT_END:
8769         case EXEC_ASSIGN_CALL:
8770         case EXEC_CRITICAL:
8771           break;
8772
8773         case EXEC_SYNC_ALL:
8774         case EXEC_SYNC_IMAGES:
8775         case EXEC_SYNC_MEMORY:
8776           resolve_sync (code);
8777           break;
8778
8779         case EXEC_ENTRY:
8780           /* Keep track of which entry we are up to.  */
8781           current_entry_id = code->ext.entry->id;
8782           break;
8783
8784         case EXEC_WHERE:
8785           resolve_where (code, NULL);
8786           break;
8787
8788         case EXEC_GOTO:
8789           if (code->expr1 != NULL)
8790             {
8791               if (code->expr1->ts.type != BT_INTEGER)
8792                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
8793                            "INTEGER variable", &code->expr1->where);
8794               else if (code->expr1->symtree->n.sym->attr.assign != 1)
8795                 gfc_error ("Variable '%s' has not been assigned a target "
8796                            "label at %L", code->expr1->symtree->n.sym->name,
8797                            &code->expr1->where);
8798             }
8799           else
8800             resolve_branch (code->label1, code);
8801           break;
8802
8803         case EXEC_RETURN:
8804           if (code->expr1 != NULL
8805                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
8806             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
8807                        "INTEGER return specifier", &code->expr1->where);
8808           break;
8809
8810         case EXEC_INIT_ASSIGN:
8811         case EXEC_END_PROCEDURE:
8812           break;
8813
8814         case EXEC_ASSIGN:
8815           if (t == FAILURE)
8816             break;
8817
8818           if (resolve_ordinary_assign (code, ns))
8819             {
8820               if (code->op == EXEC_COMPCALL)
8821                 goto compcall;
8822               else
8823                 goto call;
8824             }
8825           break;
8826
8827         case EXEC_LABEL_ASSIGN:
8828           if (code->label1->defined == ST_LABEL_UNKNOWN)
8829             gfc_error ("Label %d referenced at %L is never defined",
8830                        code->label1->value, &code->label1->where);
8831           if (t == SUCCESS
8832               && (code->expr1->expr_type != EXPR_VARIABLE
8833                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
8834                   || code->expr1->symtree->n.sym->ts.kind
8835                      != gfc_default_integer_kind
8836                   || code->expr1->symtree->n.sym->as != NULL))
8837             gfc_error ("ASSIGN statement at %L requires a scalar "
8838                        "default INTEGER variable", &code->expr1->where);
8839           break;
8840
8841         case EXEC_POINTER_ASSIGN:
8842           if (t == FAILURE)
8843             break;
8844
8845           gfc_check_pointer_assign (code->expr1, code->expr2);
8846           break;
8847
8848         case EXEC_ARITHMETIC_IF:
8849           if (t == SUCCESS
8850               && code->expr1->ts.type != BT_INTEGER
8851               && code->expr1->ts.type != BT_REAL)
8852             gfc_error ("Arithmetic IF statement at %L requires a numeric "
8853                        "expression", &code->expr1->where);
8854
8855           resolve_branch (code->label1, code);
8856           resolve_branch (code->label2, code);
8857           resolve_branch (code->label3, code);
8858           break;
8859
8860         case EXEC_IF:
8861           if (t == SUCCESS && code->expr1 != NULL
8862               && (code->expr1->ts.type != BT_LOGICAL
8863                   || code->expr1->rank != 0))
8864             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8865                        &code->expr1->where);
8866           break;
8867
8868         case EXEC_CALL:
8869         call:
8870           resolve_call (code);
8871           break;
8872
8873         case EXEC_COMPCALL:
8874         compcall:
8875           resolve_typebound_subroutine (code);
8876           break;
8877
8878         case EXEC_CALL_PPC:
8879           resolve_ppc_call (code);
8880           break;
8881
8882         case EXEC_SELECT:
8883           /* Select is complicated. Also, a SELECT construct could be
8884              a transformed computed GOTO.  */
8885           resolve_select (code);
8886           break;
8887
8888         case EXEC_SELECT_TYPE:
8889           resolve_select_type (code);
8890           break;
8891
8892         case EXEC_BLOCK:
8893           resolve_block_construct (code);
8894           break;
8895
8896         case EXEC_DO:
8897           if (code->ext.iterator != NULL)
8898             {
8899               gfc_iterator *iter = code->ext.iterator;
8900               if (gfc_resolve_iterator (iter, true) != FAILURE)
8901                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
8902             }
8903           break;
8904
8905         case EXEC_DO_WHILE:
8906           if (code->expr1 == NULL)
8907             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
8908           if (t == SUCCESS
8909               && (code->expr1->rank != 0
8910                   || code->expr1->ts.type != BT_LOGICAL))
8911             gfc_error ("Exit condition of DO WHILE loop at %L must be "
8912                        "a scalar LOGICAL expression", &code->expr1->where);
8913           break;
8914
8915         case EXEC_ALLOCATE:
8916           if (t == SUCCESS)
8917             resolve_allocate_deallocate (code, "ALLOCATE");
8918
8919           break;
8920
8921         case EXEC_DEALLOCATE:
8922           if (t == SUCCESS)
8923             resolve_allocate_deallocate (code, "DEALLOCATE");
8924
8925           break;
8926
8927         case EXEC_OPEN:
8928           if (gfc_resolve_open (code->ext.open) == FAILURE)
8929             break;
8930
8931           resolve_branch (code->ext.open->err, code);
8932           break;
8933
8934         case EXEC_CLOSE:
8935           if (gfc_resolve_close (code->ext.close) == FAILURE)
8936             break;
8937
8938           resolve_branch (code->ext.close->err, code);
8939           break;
8940
8941         case EXEC_BACKSPACE:
8942         case EXEC_ENDFILE:
8943         case EXEC_REWIND:
8944         case EXEC_FLUSH:
8945           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
8946             break;
8947
8948           resolve_branch (code->ext.filepos->err, code);
8949           break;
8950
8951         case EXEC_INQUIRE:
8952           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8953               break;
8954
8955           resolve_branch (code->ext.inquire->err, code);
8956           break;
8957
8958         case EXEC_IOLENGTH:
8959           gcc_assert (code->ext.inquire != NULL);
8960           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8961             break;
8962
8963           resolve_branch (code->ext.inquire->err, code);
8964           break;
8965
8966         case EXEC_WAIT:
8967           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
8968             break;
8969
8970           resolve_branch (code->ext.wait->err, code);
8971           resolve_branch (code->ext.wait->end, code);
8972           resolve_branch (code->ext.wait->eor, code);
8973           break;
8974
8975         case EXEC_READ:
8976         case EXEC_WRITE:
8977           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
8978             break;
8979
8980           resolve_branch (code->ext.dt->err, code);
8981           resolve_branch (code->ext.dt->end, code);
8982           resolve_branch (code->ext.dt->eor, code);
8983           break;
8984
8985         case EXEC_TRANSFER:
8986           resolve_transfer (code);
8987           break;
8988
8989         case EXEC_FORALL:
8990           resolve_forall_iterators (code->ext.forall_iterator);
8991
8992           if (code->expr1 != NULL && code->expr1->ts.type != BT_LOGICAL)
8993             gfc_error ("FORALL mask clause at %L requires a LOGICAL "
8994                        "expression", &code->expr1->where);
8995           break;
8996
8997         case EXEC_OMP_ATOMIC:
8998         case EXEC_OMP_BARRIER:
8999         case EXEC_OMP_CRITICAL:
9000         case EXEC_OMP_FLUSH:
9001         case EXEC_OMP_DO:
9002         case EXEC_OMP_MASTER:
9003         case EXEC_OMP_ORDERED:
9004         case EXEC_OMP_SECTIONS:
9005         case EXEC_OMP_SINGLE:
9006         case EXEC_OMP_TASKWAIT:
9007         case EXEC_OMP_WORKSHARE:
9008           gfc_resolve_omp_directive (code, ns);
9009           break;
9010
9011         case EXEC_OMP_PARALLEL:
9012         case EXEC_OMP_PARALLEL_DO:
9013         case EXEC_OMP_PARALLEL_SECTIONS:
9014         case EXEC_OMP_PARALLEL_WORKSHARE:
9015         case EXEC_OMP_TASK:
9016           omp_workshare_save = omp_workshare_flag;
9017           omp_workshare_flag = 0;
9018           gfc_resolve_omp_directive (code, ns);
9019           omp_workshare_flag = omp_workshare_save;
9020           break;
9021
9022         default:
9023           gfc_internal_error ("resolve_code(): Bad statement code");
9024         }
9025     }
9026
9027   cs_base = frame.prev;
9028 }
9029
9030
9031 /* Resolve initial values and make sure they are compatible with
9032    the variable.  */
9033
9034 static void
9035 resolve_values (gfc_symbol *sym)
9036 {
9037   gfc_try t;
9038
9039   if (sym->value == NULL)
9040     return;
9041
9042   if (sym->value->expr_type == EXPR_STRUCTURE)
9043     t= resolve_structure_cons (sym->value, 1);
9044   else 
9045     t = gfc_resolve_expr (sym->value);
9046
9047   if (t == FAILURE)
9048     return;
9049
9050   gfc_check_assign_symbol (sym, sym->value);
9051 }
9052
9053
9054 /* Verify the binding labels for common blocks that are BIND(C).  The label
9055    for a BIND(C) common block must be identical in all scoping units in which
9056    the common block is declared.  Further, the binding label can not collide
9057    with any other global entity in the program.  */
9058
9059 static void
9060 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
9061 {
9062   if (comm_block_tree->n.common->is_bind_c == 1)
9063     {
9064       gfc_gsymbol *binding_label_gsym;
9065       gfc_gsymbol *comm_name_gsym;
9066
9067       /* See if a global symbol exists by the common block's name.  It may
9068          be NULL if the common block is use-associated.  */
9069       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
9070                                          comm_block_tree->n.common->name);
9071       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
9072         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
9073                    "with the global entity '%s' at %L",
9074                    comm_block_tree->n.common->binding_label,
9075                    comm_block_tree->n.common->name,
9076                    &(comm_block_tree->n.common->where),
9077                    comm_name_gsym->name, &(comm_name_gsym->where));
9078       else if (comm_name_gsym != NULL
9079                && strcmp (comm_name_gsym->name,
9080                           comm_block_tree->n.common->name) == 0)
9081         {
9082           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
9083              as expected.  */
9084           if (comm_name_gsym->binding_label == NULL)
9085             /* No binding label for common block stored yet; save this one.  */
9086             comm_name_gsym->binding_label =
9087               comm_block_tree->n.common->binding_label;
9088           else
9089             if (strcmp (comm_name_gsym->binding_label,
9090                         comm_block_tree->n.common->binding_label) != 0)
9091               {
9092                 /* Common block names match but binding labels do not.  */
9093                 gfc_error ("Binding label '%s' for common block '%s' at %L "
9094                            "does not match the binding label '%s' for common "
9095                            "block '%s' at %L",
9096                            comm_block_tree->n.common->binding_label,
9097                            comm_block_tree->n.common->name,
9098                            &(comm_block_tree->n.common->where),
9099                            comm_name_gsym->binding_label,
9100                            comm_name_gsym->name,
9101                            &(comm_name_gsym->where));
9102                 return;
9103               }
9104         }
9105
9106       /* There is no binding label (NAME="") so we have nothing further to
9107          check and nothing to add as a global symbol for the label.  */
9108       if (comm_block_tree->n.common->binding_label[0] == '\0' )
9109         return;
9110       
9111       binding_label_gsym =
9112         gfc_find_gsymbol (gfc_gsym_root,
9113                           comm_block_tree->n.common->binding_label);
9114       if (binding_label_gsym == NULL)
9115         {
9116           /* Need to make a global symbol for the binding label to prevent
9117              it from colliding with another.  */
9118           binding_label_gsym =
9119             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
9120           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
9121           binding_label_gsym->type = GSYM_COMMON;
9122         }
9123       else
9124         {
9125           /* If comm_name_gsym is NULL, the name common block is use
9126              associated and the name could be colliding.  */
9127           if (binding_label_gsym->type != GSYM_COMMON)
9128             gfc_error ("Binding label '%s' for common block '%s' at %L "
9129                        "collides with the global entity '%s' at %L",
9130                        comm_block_tree->n.common->binding_label,
9131                        comm_block_tree->n.common->name,
9132                        &(comm_block_tree->n.common->where),
9133                        binding_label_gsym->name,
9134                        &(binding_label_gsym->where));
9135           else if (comm_name_gsym != NULL
9136                    && (strcmp (binding_label_gsym->name,
9137                                comm_name_gsym->binding_label) != 0)
9138                    && (strcmp (binding_label_gsym->sym_name,
9139                                comm_name_gsym->name) != 0))
9140             gfc_error ("Binding label '%s' for common block '%s' at %L "
9141                        "collides with global entity '%s' at %L",
9142                        binding_label_gsym->name, binding_label_gsym->sym_name,
9143                        &(comm_block_tree->n.common->where),
9144                        comm_name_gsym->name, &(comm_name_gsym->where));
9145         }
9146     }
9147   
9148   return;
9149 }
9150
9151
9152 /* Verify any BIND(C) derived types in the namespace so we can report errors
9153    for them once, rather than for each variable declared of that type.  */
9154
9155 static void
9156 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
9157 {
9158   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
9159       && derived_sym->attr.is_bind_c == 1)
9160     verify_bind_c_derived_type (derived_sym);
9161   
9162   return;
9163 }
9164
9165
9166 /* Verify that any binding labels used in a given namespace do not collide 
9167    with the names or binding labels of any global symbols.  */
9168
9169 static void
9170 gfc_verify_binding_labels (gfc_symbol *sym)
9171 {
9172   int has_error = 0;
9173   
9174   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
9175       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
9176     {
9177       gfc_gsymbol *bind_c_sym;
9178
9179       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
9180       if (bind_c_sym != NULL 
9181           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
9182         {
9183           if (sym->attr.if_source == IFSRC_DECL 
9184               && (bind_c_sym->type != GSYM_SUBROUTINE 
9185                   && bind_c_sym->type != GSYM_FUNCTION) 
9186               && ((sym->attr.contained == 1 
9187                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
9188                   || (sym->attr.use_assoc == 1 
9189                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
9190             {
9191               /* Make sure global procedures don't collide with anything.  */
9192               gfc_error ("Binding label '%s' at %L collides with the global "
9193                          "entity '%s' at %L", sym->binding_label,
9194                          &(sym->declared_at), bind_c_sym->name,
9195                          &(bind_c_sym->where));
9196               has_error = 1;
9197             }
9198           else if (sym->attr.contained == 0 
9199                    && (sym->attr.if_source == IFSRC_IFBODY 
9200                        && sym->attr.flavor == FL_PROCEDURE) 
9201                    && (bind_c_sym->sym_name != NULL 
9202                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
9203             {
9204               /* Make sure procedures in interface bodies don't collide.  */
9205               gfc_error ("Binding label '%s' in interface body at %L collides "
9206                          "with the global entity '%s' at %L",
9207                          sym->binding_label,
9208                          &(sym->declared_at), bind_c_sym->name,
9209                          &(bind_c_sym->where));
9210               has_error = 1;
9211             }
9212           else if (sym->attr.contained == 0 
9213                    && sym->attr.if_source == IFSRC_UNKNOWN)
9214             if ((sym->attr.use_assoc && bind_c_sym->mod_name
9215                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
9216                 || sym->attr.use_assoc == 0)
9217               {
9218                 gfc_error ("Binding label '%s' at %L collides with global "
9219                            "entity '%s' at %L", sym->binding_label,
9220                            &(sym->declared_at), bind_c_sym->name,
9221                            &(bind_c_sym->where));
9222                 has_error = 1;
9223               }
9224
9225           if (has_error != 0)
9226             /* Clear the binding label to prevent checking multiple times.  */
9227             sym->binding_label[0] = '\0';
9228         }
9229       else if (bind_c_sym == NULL)
9230         {
9231           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
9232           bind_c_sym->where = sym->declared_at;
9233           bind_c_sym->sym_name = sym->name;
9234
9235           if (sym->attr.use_assoc == 1)
9236             bind_c_sym->mod_name = sym->module;
9237           else
9238             if (sym->ns->proc_name != NULL)
9239               bind_c_sym->mod_name = sym->ns->proc_name->name;
9240
9241           if (sym->attr.contained == 0)
9242             {
9243               if (sym->attr.subroutine)
9244                 bind_c_sym->type = GSYM_SUBROUTINE;
9245               else if (sym->attr.function)
9246                 bind_c_sym->type = GSYM_FUNCTION;
9247             }
9248         }
9249     }
9250   return;
9251 }
9252
9253
9254 /* Resolve an index expression.  */
9255
9256 static gfc_try
9257 resolve_index_expr (gfc_expr *e)
9258 {
9259   if (gfc_resolve_expr (e) == FAILURE)
9260     return FAILURE;
9261
9262   if (gfc_simplify_expr (e, 0) == FAILURE)
9263     return FAILURE;
9264
9265   if (gfc_specification_expr (e) == FAILURE)
9266     return FAILURE;
9267
9268   return SUCCESS;
9269 }
9270
9271 /* Resolve a charlen structure.  */
9272
9273 static gfc_try
9274 resolve_charlen (gfc_charlen *cl)
9275 {
9276   int i, k;
9277
9278   if (cl->resolved)
9279     return SUCCESS;
9280
9281   cl->resolved = 1;
9282
9283   specification_expr = 1;
9284
9285   if (resolve_index_expr (cl->length) == FAILURE)
9286     {
9287       specification_expr = 0;
9288       return FAILURE;
9289     }
9290
9291   /* "If the character length parameter value evaluates to a negative
9292      value, the length of character entities declared is zero."  */
9293   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
9294     {
9295       if (gfc_option.warn_surprising)
9296         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
9297                          " the length has been set to zero",
9298                          &cl->length->where, i);
9299       gfc_replace_expr (cl->length,
9300                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
9301     }
9302
9303   /* Check that the character length is not too large.  */
9304   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
9305   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
9306       && cl->length->ts.type == BT_INTEGER
9307       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
9308     {
9309       gfc_error ("String length at %L is too large", &cl->length->where);
9310       return FAILURE;
9311     }
9312
9313   return SUCCESS;
9314 }
9315
9316
9317 /* Test for non-constant shape arrays.  */
9318
9319 static bool
9320 is_non_constant_shape_array (gfc_symbol *sym)
9321 {
9322   gfc_expr *e;
9323   int i;
9324   bool not_constant;
9325
9326   not_constant = false;
9327   if (sym->as != NULL)
9328     {
9329       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
9330          has not been simplified; parameter array references.  Do the
9331          simplification now.  */
9332       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
9333         {
9334           e = sym->as->lower[i];
9335           if (e && (resolve_index_expr (e) == FAILURE
9336                     || !gfc_is_constant_expr (e)))
9337             not_constant = true;
9338           e = sym->as->upper[i];
9339           if (e && (resolve_index_expr (e) == FAILURE
9340                     || !gfc_is_constant_expr (e)))
9341             not_constant = true;
9342         }
9343     }
9344   return not_constant;
9345 }
9346
9347 /* Given a symbol and an initialization expression, add code to initialize
9348    the symbol to the function entry.  */
9349 static void
9350 build_init_assign (gfc_symbol *sym, gfc_expr *init)
9351 {
9352   gfc_expr *lval;
9353   gfc_code *init_st;
9354   gfc_namespace *ns = sym->ns;
9355
9356   /* Search for the function namespace if this is a contained
9357      function without an explicit result.  */
9358   if (sym->attr.function && sym == sym->result
9359       && sym->name != sym->ns->proc_name->name)
9360     {
9361       ns = ns->contained;
9362       for (;ns; ns = ns->sibling)
9363         if (strcmp (ns->proc_name->name, sym->name) == 0)
9364           break;
9365     }
9366
9367   if (ns == NULL)
9368     {
9369       gfc_free_expr (init);
9370       return;
9371     }
9372
9373   /* Build an l-value expression for the result.  */
9374   lval = gfc_lval_expr_from_sym (sym);
9375
9376   /* Add the code at scope entry.  */
9377   init_st = gfc_get_code ();
9378   init_st->next = ns->code;
9379   ns->code = init_st;
9380
9381   /* Assign the default initializer to the l-value.  */
9382   init_st->loc = sym->declared_at;
9383   init_st->op = EXEC_INIT_ASSIGN;
9384   init_st->expr1 = lval;
9385   init_st->expr2 = init;
9386 }
9387
9388 /* Assign the default initializer to a derived type variable or result.  */
9389
9390 static void
9391 apply_default_init (gfc_symbol *sym)
9392 {
9393   gfc_expr *init = NULL;
9394
9395   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9396     return;
9397
9398   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
9399     init = gfc_default_initializer (&sym->ts);
9400
9401   if (init == NULL)
9402     return;
9403
9404   build_init_assign (sym, init);
9405 }
9406
9407 /* Build an initializer for a local integer, real, complex, logical, or
9408    character variable, based on the command line flags finit-local-zero,
9409    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
9410    null if the symbol should not have a default initialization.  */
9411 static gfc_expr *
9412 build_default_init_expr (gfc_symbol *sym)
9413 {
9414   int char_len;
9415   gfc_expr *init_expr;
9416   int i;
9417
9418   /* These symbols should never have a default initialization.  */
9419   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
9420       || sym->attr.external
9421       || sym->attr.dummy
9422       || sym->attr.pointer
9423       || sym->attr.in_equivalence
9424       || sym->attr.in_common
9425       || sym->attr.data
9426       || sym->module
9427       || sym->attr.cray_pointee
9428       || sym->attr.cray_pointer)
9429     return NULL;
9430
9431   /* Now we'll try to build an initializer expression.  */
9432   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
9433                                      &sym->declared_at);
9434
9435   /* We will only initialize integers, reals, complex, logicals, and
9436      characters, and only if the corresponding command-line flags
9437      were set.  Otherwise, we free init_expr and return null.  */
9438   switch (sym->ts.type)
9439     {    
9440     case BT_INTEGER:
9441       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
9442         mpz_set_si (init_expr->value.integer, 
9443                          gfc_option.flag_init_integer_value);
9444       else
9445         {
9446           gfc_free_expr (init_expr);
9447           init_expr = NULL;
9448         }
9449       break;
9450
9451     case BT_REAL:
9452       switch (gfc_option.flag_init_real)
9453         {
9454         case GFC_INIT_REAL_SNAN:
9455           init_expr->is_snan = 1;
9456           /* Fall through.  */
9457         case GFC_INIT_REAL_NAN:
9458           mpfr_set_nan (init_expr->value.real);
9459           break;
9460
9461         case GFC_INIT_REAL_INF:
9462           mpfr_set_inf (init_expr->value.real, 1);
9463           break;
9464
9465         case GFC_INIT_REAL_NEG_INF:
9466           mpfr_set_inf (init_expr->value.real, -1);
9467           break;
9468
9469         case GFC_INIT_REAL_ZERO:
9470           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
9471           break;
9472
9473         default:
9474           gfc_free_expr (init_expr);
9475           init_expr = NULL;
9476           break;
9477         }
9478       break;
9479           
9480     case BT_COMPLEX:
9481       switch (gfc_option.flag_init_real)
9482         {
9483         case GFC_INIT_REAL_SNAN:
9484           init_expr->is_snan = 1;
9485           /* Fall through.  */
9486         case GFC_INIT_REAL_NAN:
9487           mpfr_set_nan (mpc_realref (init_expr->value.complex));
9488           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
9489           break;
9490
9491         case GFC_INIT_REAL_INF:
9492           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
9493           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
9494           break;
9495
9496         case GFC_INIT_REAL_NEG_INF:
9497           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
9498           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
9499           break;
9500
9501         case GFC_INIT_REAL_ZERO:
9502           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
9503           break;
9504
9505         default:
9506           gfc_free_expr (init_expr);
9507           init_expr = NULL;
9508           break;
9509         }
9510       break;
9511           
9512     case BT_LOGICAL:
9513       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
9514         init_expr->value.logical = 0;
9515       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
9516         init_expr->value.logical = 1;
9517       else
9518         {
9519           gfc_free_expr (init_expr);
9520           init_expr = NULL;
9521         }
9522       break;
9523           
9524     case BT_CHARACTER:
9525       /* For characters, the length must be constant in order to 
9526          create a default initializer.  */
9527       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
9528           && sym->ts.u.cl->length
9529           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9530         {
9531           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
9532           init_expr->value.character.length = char_len;
9533           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
9534           for (i = 0; i < char_len; i++)
9535             init_expr->value.character.string[i]
9536               = (unsigned char) gfc_option.flag_init_character_value;
9537         }
9538       else
9539         {
9540           gfc_free_expr (init_expr);
9541           init_expr = NULL;
9542         }
9543       break;
9544           
9545     default:
9546      gfc_free_expr (init_expr);
9547      init_expr = NULL;
9548     }
9549   return init_expr;
9550 }
9551
9552 /* Add an initialization expression to a local variable.  */
9553 static void
9554 apply_default_init_local (gfc_symbol *sym)
9555 {
9556   gfc_expr *init = NULL;
9557
9558   /* The symbol should be a variable or a function return value.  */
9559   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9560       || (sym->attr.function && sym->result != sym))
9561     return;
9562
9563   /* Try to build the initializer expression.  If we can't initialize
9564      this symbol, then init will be NULL.  */
9565   init = build_default_init_expr (sym);
9566   if (init == NULL)
9567     return;
9568
9569   /* For saved variables, we don't want to add an initializer at 
9570      function entry, so we just add a static initializer.  */
9571   if (sym->attr.save || sym->ns->save_all 
9572       || gfc_option.flag_max_stack_var_size == 0)
9573     {
9574       /* Don't clobber an existing initializer!  */
9575       gcc_assert (sym->value == NULL);
9576       sym->value = init;
9577       return;
9578     }
9579
9580   build_init_assign (sym, init);
9581 }
9582
9583 /* Resolution of common features of flavors variable and procedure.  */
9584
9585 static gfc_try
9586 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
9587 {
9588   /* Constraints on deferred shape variable.  */
9589   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
9590     {
9591       if (sym->attr.allocatable)
9592         {
9593           if (sym->attr.dimension)
9594             {
9595               gfc_error ("Allocatable array '%s' at %L must have "
9596                          "a deferred shape", sym->name, &sym->declared_at);
9597               return FAILURE;
9598             }
9599           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
9600                                    "may not be ALLOCATABLE", sym->name,
9601                                    &sym->declared_at) == FAILURE)
9602             return FAILURE;
9603         }
9604
9605       if (sym->attr.pointer && sym->attr.dimension)
9606         {
9607           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
9608                      sym->name, &sym->declared_at);
9609           return FAILURE;
9610         }
9611     }
9612   else
9613     {
9614       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
9615           && !sym->attr.dummy && sym->ts.type != BT_CLASS && !sym->assoc)
9616         {
9617           gfc_error ("Array '%s' at %L cannot have a deferred shape",
9618                      sym->name, &sym->declared_at);
9619           return FAILURE;
9620          }
9621     }
9622
9623   /* Constraints on polymorphic variables.  */
9624   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
9625     {
9626       /* F03:C502.  */
9627       if (sym->attr.class_ok
9628           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
9629         {
9630           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
9631                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
9632                      &sym->declared_at);
9633           return FAILURE;
9634         }
9635
9636       /* F03:C509.  */
9637       /* Assume that use associated symbols were checked in the module ns.  */ 
9638       if (!sym->attr.class_ok && !sym->attr.use_assoc)
9639         {
9640           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
9641                      "or pointer", sym->name, &sym->declared_at);
9642           return FAILURE;
9643         }
9644     }
9645     
9646   return SUCCESS;
9647 }
9648
9649
9650 /* Additional checks for symbols with flavor variable and derived
9651    type.  To be called from resolve_fl_variable.  */
9652
9653 static gfc_try
9654 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
9655 {
9656   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
9657
9658   /* Check to see if a derived type is blocked from being host
9659      associated by the presence of another class I symbol in the same
9660      namespace.  14.6.1.3 of the standard and the discussion on
9661      comp.lang.fortran.  */
9662   if (sym->ns != sym->ts.u.derived->ns
9663       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
9664     {
9665       gfc_symbol *s;
9666       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
9667       if (s && s->attr.flavor != FL_DERIVED)
9668         {
9669           gfc_error ("The type '%s' cannot be host associated at %L "
9670                      "because it is blocked by an incompatible object "
9671                      "of the same name declared at %L",
9672                      sym->ts.u.derived->name, &sym->declared_at,
9673                      &s->declared_at);
9674           return FAILURE;
9675         }
9676     }
9677
9678   /* 4th constraint in section 11.3: "If an object of a type for which
9679      component-initialization is specified (R429) appears in the
9680      specification-part of a module and does not have the ALLOCATABLE
9681      or POINTER attribute, the object shall have the SAVE attribute."
9682
9683      The check for initializers is performed with
9684      gfc_has_default_initializer because gfc_default_initializer generates
9685      a hidden default for allocatable components.  */
9686   if (!(sym->value || no_init_flag) && sym->ns->proc_name
9687       && sym->ns->proc_name->attr.flavor == FL_MODULE
9688       && !sym->ns->save_all && !sym->attr.save
9689       && !sym->attr.pointer && !sym->attr.allocatable
9690       && gfc_has_default_initializer (sym->ts.u.derived)
9691       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
9692                          "module variable '%s' at %L, needed due to "
9693                          "the default initialization", sym->name,
9694                          &sym->declared_at) == FAILURE)
9695     return FAILURE;
9696
9697   /* Assign default initializer.  */
9698   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
9699       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
9700     {
9701       sym->value = gfc_default_initializer (&sym->ts);
9702     }
9703
9704   return SUCCESS;
9705 }
9706
9707
9708 /* Resolve symbols with flavor variable.  */
9709
9710 static gfc_try
9711 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
9712 {
9713   int no_init_flag, automatic_flag;
9714   gfc_expr *e;
9715   const char *auto_save_msg;
9716
9717   auto_save_msg = "Automatic object '%s' at %L cannot have the "
9718                   "SAVE attribute";
9719
9720   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9721     return FAILURE;
9722
9723   /* Set this flag to check that variables are parameters of all entries.
9724      This check is effected by the call to gfc_resolve_expr through
9725      is_non_constant_shape_array.  */
9726   specification_expr = 1;
9727
9728   if (sym->ns->proc_name
9729       && (sym->ns->proc_name->attr.flavor == FL_MODULE
9730           || sym->ns->proc_name->attr.is_main_program)
9731       && !sym->attr.use_assoc
9732       && !sym->attr.allocatable
9733       && !sym->attr.pointer
9734       && is_non_constant_shape_array (sym))
9735     {
9736       /* The shape of a main program or module array needs to be
9737          constant.  */
9738       gfc_error ("The module or main program array '%s' at %L must "
9739                  "have constant shape", sym->name, &sym->declared_at);
9740       specification_expr = 0;
9741       return FAILURE;
9742     }
9743
9744   if (sym->ts.type == BT_CHARACTER)
9745     {
9746       /* Make sure that character string variables with assumed length are
9747          dummy arguments.  */
9748       e = sym->ts.u.cl->length;
9749       if (e == NULL && !sym->attr.dummy && !sym->attr.result)
9750         {
9751           gfc_error ("Entity with assumed character length at %L must be a "
9752                      "dummy argument or a PARAMETER", &sym->declared_at);
9753           return FAILURE;
9754         }
9755
9756       if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
9757         {
9758           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9759           return FAILURE;
9760         }
9761
9762       if (!gfc_is_constant_expr (e)
9763           && !(e->expr_type == EXPR_VARIABLE
9764                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
9765           && sym->ns->proc_name
9766           && (sym->ns->proc_name->attr.flavor == FL_MODULE
9767               || sym->ns->proc_name->attr.is_main_program)
9768           && !sym->attr.use_assoc)
9769         {
9770           gfc_error ("'%s' at %L must have constant character length "
9771                      "in this context", sym->name, &sym->declared_at);
9772           return FAILURE;
9773         }
9774     }
9775
9776   if (sym->value == NULL && sym->attr.referenced)
9777     apply_default_init_local (sym); /* Try to apply a default initialization.  */
9778
9779   /* Determine if the symbol may not have an initializer.  */
9780   no_init_flag = automatic_flag = 0;
9781   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
9782       || sym->attr.intrinsic || sym->attr.result)
9783     no_init_flag = 1;
9784   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
9785            && is_non_constant_shape_array (sym))
9786     {
9787       no_init_flag = automatic_flag = 1;
9788
9789       /* Also, they must not have the SAVE attribute.
9790          SAVE_IMPLICIT is checked below.  */
9791       if (sym->attr.save == SAVE_EXPLICIT)
9792         {
9793           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9794           return FAILURE;
9795         }
9796     }
9797
9798   /* Ensure that any initializer is simplified.  */
9799   if (sym->value)
9800     gfc_simplify_expr (sym->value, 1);
9801
9802   /* Reject illegal initializers.  */
9803   if (!sym->mark && sym->value)
9804     {
9805       if (sym->attr.allocatable)
9806         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
9807                    sym->name, &sym->declared_at);
9808       else if (sym->attr.external)
9809         gfc_error ("External '%s' at %L cannot have an initializer",
9810                    sym->name, &sym->declared_at);
9811       else if (sym->attr.dummy
9812         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
9813         gfc_error ("Dummy '%s' at %L cannot have an initializer",
9814                    sym->name, &sym->declared_at);
9815       else if (sym->attr.intrinsic)
9816         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
9817                    sym->name, &sym->declared_at);
9818       else if (sym->attr.result)
9819         gfc_error ("Function result '%s' at %L cannot have an initializer",
9820                    sym->name, &sym->declared_at);
9821       else if (automatic_flag)
9822         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
9823                    sym->name, &sym->declared_at);
9824       else
9825         goto no_init_error;
9826       return FAILURE;
9827     }
9828
9829 no_init_error:
9830   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
9831     return resolve_fl_variable_derived (sym, no_init_flag);
9832
9833   return SUCCESS;
9834 }
9835
9836
9837 /* Resolve a procedure.  */
9838
9839 static gfc_try
9840 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
9841 {
9842   gfc_formal_arglist *arg;
9843
9844   if (sym->attr.function
9845       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9846     return FAILURE;
9847
9848   if (sym->ts.type == BT_CHARACTER)
9849     {
9850       gfc_charlen *cl = sym->ts.u.cl;
9851
9852       if (cl && cl->length && gfc_is_constant_expr (cl->length)
9853              && resolve_charlen (cl) == FAILURE)
9854         return FAILURE;
9855
9856       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
9857           && sym->attr.proc == PROC_ST_FUNCTION)
9858         {
9859           gfc_error ("Character-valued statement function '%s' at %L must "
9860                      "have constant length", sym->name, &sym->declared_at);
9861           return FAILURE;
9862         }
9863     }
9864
9865   /* Ensure that derived type for are not of a private type.  Internal
9866      module procedures are excluded by 2.2.3.3 - i.e., they are not
9867      externally accessible and can access all the objects accessible in
9868      the host.  */
9869   if (!(sym->ns->parent
9870         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
9871       && gfc_check_access(sym->attr.access, sym->ns->default_access))
9872     {
9873       gfc_interface *iface;
9874
9875       for (arg = sym->formal; arg; arg = arg->next)
9876         {
9877           if (arg->sym
9878               && arg->sym->ts.type == BT_DERIVED
9879               && !arg->sym->ts.u.derived->attr.use_assoc
9880               && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9881                                     arg->sym->ts.u.derived->ns->default_access)
9882               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
9883                                  "PRIVATE type and cannot be a dummy argument"
9884                                  " of '%s', which is PUBLIC at %L",
9885                                  arg->sym->name, sym->name, &sym->declared_at)
9886                  == FAILURE)
9887             {
9888               /* Stop this message from recurring.  */
9889               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9890               return FAILURE;
9891             }
9892         }
9893
9894       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9895          PRIVATE to the containing module.  */
9896       for (iface = sym->generic; iface; iface = iface->next)
9897         {
9898           for (arg = iface->sym->formal; arg; arg = arg->next)
9899             {
9900               if (arg->sym
9901                   && arg->sym->ts.type == BT_DERIVED
9902                   && !arg->sym->ts.u.derived->attr.use_assoc
9903                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9904                                         arg->sym->ts.u.derived->ns->default_access)
9905                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9906                                      "'%s' in PUBLIC interface '%s' at %L "
9907                                      "takes dummy arguments of '%s' which is "
9908                                      "PRIVATE", iface->sym->name, sym->name,
9909                                      &iface->sym->declared_at,
9910                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9911                 {
9912                   /* Stop this message from recurring.  */
9913                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9914                   return FAILURE;
9915                 }
9916              }
9917         }
9918
9919       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9920          PRIVATE to the containing module.  */
9921       for (iface = sym->generic; iface; iface = iface->next)
9922         {
9923           for (arg = iface->sym->formal; arg; arg = arg->next)
9924             {
9925               if (arg->sym
9926                   && arg->sym->ts.type == BT_DERIVED
9927                   && !arg->sym->ts.u.derived->attr.use_assoc
9928                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9929                                         arg->sym->ts.u.derived->ns->default_access)
9930                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9931                                      "'%s' in PUBLIC interface '%s' at %L "
9932                                      "takes dummy arguments of '%s' which is "
9933                                      "PRIVATE", iface->sym->name, sym->name,
9934                                      &iface->sym->declared_at,
9935                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9936                 {
9937                   /* Stop this message from recurring.  */
9938                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9939                   return FAILURE;
9940                 }
9941              }
9942         }
9943     }
9944
9945   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
9946       && !sym->attr.proc_pointer)
9947     {
9948       gfc_error ("Function '%s' at %L cannot have an initializer",
9949                  sym->name, &sym->declared_at);
9950       return FAILURE;
9951     }
9952
9953   /* An external symbol may not have an initializer because it is taken to be
9954      a procedure. Exception: Procedure Pointers.  */
9955   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
9956     {
9957       gfc_error ("External object '%s' at %L may not have an initializer",
9958                  sym->name, &sym->declared_at);
9959       return FAILURE;
9960     }
9961
9962   /* An elemental function is required to return a scalar 12.7.1  */
9963   if (sym->attr.elemental && sym->attr.function && sym->as)
9964     {
9965       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
9966                  "result", sym->name, &sym->declared_at);
9967       /* Reset so that the error only occurs once.  */
9968       sym->attr.elemental = 0;
9969       return FAILURE;
9970     }
9971
9972   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
9973      char-len-param shall not be array-valued, pointer-valued, recursive
9974      or pure.  ....snip... A character value of * may only be used in the
9975      following ways: (i) Dummy arg of procedure - dummy associates with
9976      actual length; (ii) To declare a named constant; or (iii) External
9977      function - but length must be declared in calling scoping unit.  */
9978   if (sym->attr.function
9979       && sym->ts.type == BT_CHARACTER
9980       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
9981     {
9982       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
9983           || (sym->attr.recursive) || (sym->attr.pure))
9984         {
9985           if (sym->as && sym->as->rank)
9986             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9987                        "array-valued", sym->name, &sym->declared_at);
9988
9989           if (sym->attr.pointer)
9990             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9991                        "pointer-valued", sym->name, &sym->declared_at);
9992
9993           if (sym->attr.pure)
9994             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9995                        "pure", sym->name, &sym->declared_at);
9996
9997           if (sym->attr.recursive)
9998             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9999                        "recursive", sym->name, &sym->declared_at);
10000
10001           return FAILURE;
10002         }
10003
10004       /* Appendix B.2 of the standard.  Contained functions give an
10005          error anyway.  Fixed-form is likely to be F77/legacy.  */
10006       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
10007         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
10008                         "CHARACTER(*) function '%s' at %L",
10009                         sym->name, &sym->declared_at);
10010     }
10011
10012   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
10013     {
10014       gfc_formal_arglist *curr_arg;
10015       int has_non_interop_arg = 0;
10016
10017       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10018                              sym->common_block) == FAILURE)
10019         {
10020           /* Clear these to prevent looking at them again if there was an
10021              error.  */
10022           sym->attr.is_bind_c = 0;
10023           sym->attr.is_c_interop = 0;
10024           sym->ts.is_c_interop = 0;
10025         }
10026       else
10027         {
10028           /* So far, no errors have been found.  */
10029           sym->attr.is_c_interop = 1;
10030           sym->ts.is_c_interop = 1;
10031         }
10032       
10033       curr_arg = sym->formal;
10034       while (curr_arg != NULL)
10035         {
10036           /* Skip implicitly typed dummy args here.  */
10037           if (curr_arg->sym->attr.implicit_type == 0)
10038             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
10039               /* If something is found to fail, record the fact so we
10040                  can mark the symbol for the procedure as not being
10041                  BIND(C) to try and prevent multiple errors being
10042                  reported.  */
10043               has_non_interop_arg = 1;
10044           
10045           curr_arg = curr_arg->next;
10046         }
10047
10048       /* See if any of the arguments were not interoperable and if so, clear
10049          the procedure symbol to prevent duplicate error messages.  */
10050       if (has_non_interop_arg != 0)
10051         {
10052           sym->attr.is_c_interop = 0;
10053           sym->ts.is_c_interop = 0;
10054           sym->attr.is_bind_c = 0;
10055         }
10056     }
10057   
10058   if (!sym->attr.proc_pointer)
10059     {
10060       if (sym->attr.save == SAVE_EXPLICIT)
10061         {
10062           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
10063                      "in '%s' at %L", sym->name, &sym->declared_at);
10064           return FAILURE;
10065         }
10066       if (sym->attr.intent)
10067         {
10068           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
10069                      "in '%s' at %L", sym->name, &sym->declared_at);
10070           return FAILURE;
10071         }
10072       if (sym->attr.subroutine && sym->attr.result)
10073         {
10074           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
10075                      "in '%s' at %L", sym->name, &sym->declared_at);
10076           return FAILURE;
10077         }
10078       if (sym->attr.external && sym->attr.function
10079           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
10080               || sym->attr.contained))
10081         {
10082           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
10083                      "in '%s' at %L", sym->name, &sym->declared_at);
10084           return FAILURE;
10085         }
10086       if (strcmp ("ppr@", sym->name) == 0)
10087         {
10088           gfc_error ("Procedure pointer result '%s' at %L "
10089                      "is missing the pointer attribute",
10090                      sym->ns->proc_name->name, &sym->declared_at);
10091           return FAILURE;
10092         }
10093     }
10094
10095   return SUCCESS;
10096 }
10097
10098
10099 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
10100    been defined and we now know their defined arguments, check that they fulfill
10101    the requirements of the standard for procedures used as finalizers.  */
10102
10103 static gfc_try
10104 gfc_resolve_finalizers (gfc_symbol* derived)
10105 {
10106   gfc_finalizer* list;
10107   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
10108   gfc_try result = SUCCESS;
10109   bool seen_scalar = false;
10110
10111   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
10112     return SUCCESS;
10113
10114   /* Walk over the list of finalizer-procedures, check them, and if any one
10115      does not fit in with the standard's definition, print an error and remove
10116      it from the list.  */
10117   prev_link = &derived->f2k_derived->finalizers;
10118   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
10119     {
10120       gfc_symbol* arg;
10121       gfc_finalizer* i;
10122       int my_rank;
10123
10124       /* Skip this finalizer if we already resolved it.  */
10125       if (list->proc_tree)
10126         {
10127           prev_link = &(list->next);
10128           continue;
10129         }
10130
10131       /* Check this exists and is a SUBROUTINE.  */
10132       if (!list->proc_sym->attr.subroutine)
10133         {
10134           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
10135                      list->proc_sym->name, &list->where);
10136           goto error;
10137         }
10138
10139       /* We should have exactly one argument.  */
10140       if (!list->proc_sym->formal || list->proc_sym->formal->next)
10141         {
10142           gfc_error ("FINAL procedure at %L must have exactly one argument",
10143                      &list->where);
10144           goto error;
10145         }
10146       arg = list->proc_sym->formal->sym;
10147
10148       /* This argument must be of our type.  */
10149       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
10150         {
10151           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
10152                      &arg->declared_at, derived->name);
10153           goto error;
10154         }
10155
10156       /* It must neither be a pointer nor allocatable nor optional.  */
10157       if (arg->attr.pointer)
10158         {
10159           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
10160                      &arg->declared_at);
10161           goto error;
10162         }
10163       if (arg->attr.allocatable)
10164         {
10165           gfc_error ("Argument of FINAL procedure at %L must not be"
10166                      " ALLOCATABLE", &arg->declared_at);
10167           goto error;
10168         }
10169       if (arg->attr.optional)
10170         {
10171           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
10172                      &arg->declared_at);
10173           goto error;
10174         }
10175
10176       /* It must not be INTENT(OUT).  */
10177       if (arg->attr.intent == INTENT_OUT)
10178         {
10179           gfc_error ("Argument of FINAL procedure at %L must not be"
10180                      " INTENT(OUT)", &arg->declared_at);
10181           goto error;
10182         }
10183
10184       /* Warn if the procedure is non-scalar and not assumed shape.  */
10185       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
10186           && arg->as->type != AS_ASSUMED_SHAPE)
10187         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
10188                      " shape argument", &arg->declared_at);
10189
10190       /* Check that it does not match in kind and rank with a FINAL procedure
10191          defined earlier.  To really loop over the *earlier* declarations,
10192          we need to walk the tail of the list as new ones were pushed at the
10193          front.  */
10194       /* TODO: Handle kind parameters once they are implemented.  */
10195       my_rank = (arg->as ? arg->as->rank : 0);
10196       for (i = list->next; i; i = i->next)
10197         {
10198           /* Argument list might be empty; that is an error signalled earlier,
10199              but we nevertheless continued resolving.  */
10200           if (i->proc_sym->formal)
10201             {
10202               gfc_symbol* i_arg = i->proc_sym->formal->sym;
10203               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
10204               if (i_rank == my_rank)
10205                 {
10206                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
10207                              " rank (%d) as '%s'",
10208                              list->proc_sym->name, &list->where, my_rank, 
10209                              i->proc_sym->name);
10210                   goto error;
10211                 }
10212             }
10213         }
10214
10215         /* Is this the/a scalar finalizer procedure?  */
10216         if (!arg->as || arg->as->rank == 0)
10217           seen_scalar = true;
10218
10219         /* Find the symtree for this procedure.  */
10220         gcc_assert (!list->proc_tree);
10221         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
10222
10223         prev_link = &list->next;
10224         continue;
10225
10226         /* Remove wrong nodes immediately from the list so we don't risk any
10227            troubles in the future when they might fail later expectations.  */
10228 error:
10229         result = FAILURE;
10230         i = list;
10231         *prev_link = list->next;
10232         gfc_free_finalizer (i);
10233     }
10234
10235   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
10236      were nodes in the list, must have been for arrays.  It is surely a good
10237      idea to have a scalar version there if there's something to finalize.  */
10238   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
10239     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
10240                  " defined at %L, suggest also scalar one",
10241                  derived->name, &derived->declared_at);
10242
10243   /* TODO:  Remove this error when finalization is finished.  */
10244   gfc_error ("Finalization at %L is not yet implemented",
10245              &derived->declared_at);
10246
10247   return result;
10248 }
10249
10250
10251 /* Check that it is ok for the typebound procedure proc to override the
10252    procedure old.  */
10253
10254 static gfc_try
10255 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
10256 {
10257   locus where;
10258   const gfc_symbol* proc_target;
10259   const gfc_symbol* old_target;
10260   unsigned proc_pass_arg, old_pass_arg, argpos;
10261   gfc_formal_arglist* proc_formal;
10262   gfc_formal_arglist* old_formal;
10263
10264   /* This procedure should only be called for non-GENERIC proc.  */
10265   gcc_assert (!proc->n.tb->is_generic);
10266
10267   /* If the overwritten procedure is GENERIC, this is an error.  */
10268   if (old->n.tb->is_generic)
10269     {
10270       gfc_error ("Can't overwrite GENERIC '%s' at %L",
10271                  old->name, &proc->n.tb->where);
10272       return FAILURE;
10273     }
10274
10275   where = proc->n.tb->where;
10276   proc_target = proc->n.tb->u.specific->n.sym;
10277   old_target = old->n.tb->u.specific->n.sym;
10278
10279   /* Check that overridden binding is not NON_OVERRIDABLE.  */
10280   if (old->n.tb->non_overridable)
10281     {
10282       gfc_error ("'%s' at %L overrides a procedure binding declared"
10283                  " NON_OVERRIDABLE", proc->name, &where);
10284       return FAILURE;
10285     }
10286
10287   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
10288   if (!old->n.tb->deferred && proc->n.tb->deferred)
10289     {
10290       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
10291                  " non-DEFERRED binding", proc->name, &where);
10292       return FAILURE;
10293     }
10294
10295   /* If the overridden binding is PURE, the overriding must be, too.  */
10296   if (old_target->attr.pure && !proc_target->attr.pure)
10297     {
10298       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
10299                  proc->name, &where);
10300       return FAILURE;
10301     }
10302
10303   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
10304      is not, the overriding must not be either.  */
10305   if (old_target->attr.elemental && !proc_target->attr.elemental)
10306     {
10307       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
10308                  " ELEMENTAL", proc->name, &where);
10309       return FAILURE;
10310     }
10311   if (!old_target->attr.elemental && proc_target->attr.elemental)
10312     {
10313       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
10314                  " be ELEMENTAL, either", proc->name, &where);
10315       return FAILURE;
10316     }
10317
10318   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
10319      SUBROUTINE.  */
10320   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
10321     {
10322       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
10323                  " SUBROUTINE", proc->name, &where);
10324       return FAILURE;
10325     }
10326
10327   /* If the overridden binding is a FUNCTION, the overriding must also be a
10328      FUNCTION and have the same characteristics.  */
10329   if (old_target->attr.function)
10330     {
10331       if (!proc_target->attr.function)
10332         {
10333           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
10334                      " FUNCTION", proc->name, &where);
10335           return FAILURE;
10336         }
10337
10338       /* FIXME:  Do more comprehensive checking (including, for instance, the
10339          rank and array-shape).  */
10340       gcc_assert (proc_target->result && old_target->result);
10341       if (!gfc_compare_types (&proc_target->result->ts,
10342                               &old_target->result->ts))
10343         {
10344           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
10345                      " matching result types", proc->name, &where);
10346           return FAILURE;
10347         }
10348     }
10349
10350   /* If the overridden binding is PUBLIC, the overriding one must not be
10351      PRIVATE.  */
10352   if (old->n.tb->access == ACCESS_PUBLIC
10353       && proc->n.tb->access == ACCESS_PRIVATE)
10354     {
10355       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
10356                  " PRIVATE", proc->name, &where);
10357       return FAILURE;
10358     }
10359
10360   /* Compare the formal argument lists of both procedures.  This is also abused
10361      to find the position of the passed-object dummy arguments of both
10362      bindings as at least the overridden one might not yet be resolved and we
10363      need those positions in the check below.  */
10364   proc_pass_arg = old_pass_arg = 0;
10365   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
10366     proc_pass_arg = 1;
10367   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
10368     old_pass_arg = 1;
10369   argpos = 1;
10370   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
10371        proc_formal && old_formal;
10372        proc_formal = proc_formal->next, old_formal = old_formal->next)
10373     {
10374       if (proc->n.tb->pass_arg
10375           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
10376         proc_pass_arg = argpos;
10377       if (old->n.tb->pass_arg
10378           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
10379         old_pass_arg = argpos;
10380
10381       /* Check that the names correspond.  */
10382       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
10383         {
10384           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
10385                      " to match the corresponding argument of the overridden"
10386                      " procedure", proc_formal->sym->name, proc->name, &where,
10387                      old_formal->sym->name);
10388           return FAILURE;
10389         }
10390
10391       /* Check that the types correspond if neither is the passed-object
10392          argument.  */
10393       /* FIXME:  Do more comprehensive testing here.  */
10394       if (proc_pass_arg != argpos && old_pass_arg != argpos
10395           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
10396         {
10397           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L "
10398                      "in respect to the overridden procedure",
10399                      proc_formal->sym->name, proc->name, &where);
10400           return FAILURE;
10401         }
10402
10403       ++argpos;
10404     }
10405   if (proc_formal || old_formal)
10406     {
10407       gfc_error ("'%s' at %L must have the same number of formal arguments as"
10408                  " the overridden procedure", proc->name, &where);
10409       return FAILURE;
10410     }
10411
10412   /* If the overridden binding is NOPASS, the overriding one must also be
10413      NOPASS.  */
10414   if (old->n.tb->nopass && !proc->n.tb->nopass)
10415     {
10416       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
10417                  " NOPASS", proc->name, &where);
10418       return FAILURE;
10419     }
10420
10421   /* If the overridden binding is PASS(x), the overriding one must also be
10422      PASS and the passed-object dummy arguments must correspond.  */
10423   if (!old->n.tb->nopass)
10424     {
10425       if (proc->n.tb->nopass)
10426         {
10427           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
10428                      " PASS", proc->name, &where);
10429           return FAILURE;
10430         }
10431
10432       if (proc_pass_arg != old_pass_arg)
10433         {
10434           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
10435                      " the same position as the passed-object dummy argument of"
10436                      " the overridden procedure", proc->name, &where);
10437           return FAILURE;
10438         }
10439     }
10440
10441   return SUCCESS;
10442 }
10443
10444
10445 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10446
10447 static gfc_try
10448 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10449                              const char* generic_name, locus where)
10450 {
10451   gfc_symbol* sym1;
10452   gfc_symbol* sym2;
10453
10454   gcc_assert (t1->specific && t2->specific);
10455   gcc_assert (!t1->specific->is_generic);
10456   gcc_assert (!t2->specific->is_generic);
10457
10458   sym1 = t1->specific->u.specific->n.sym;
10459   sym2 = t2->specific->u.specific->n.sym;
10460
10461   if (sym1 == sym2)
10462     return SUCCESS;
10463
10464   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10465   if (sym1->attr.subroutine != sym2->attr.subroutine
10466       || sym1->attr.function != sym2->attr.function)
10467     {
10468       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10469                  " GENERIC '%s' at %L",
10470                  sym1->name, sym2->name, generic_name, &where);
10471       return FAILURE;
10472     }
10473
10474   /* Compare the interfaces.  */
10475   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10476     {
10477       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10478                  sym1->name, sym2->name, generic_name, &where);
10479       return FAILURE;
10480     }
10481
10482   return SUCCESS;
10483 }
10484
10485
10486 /* Worker function for resolving a generic procedure binding; this is used to
10487    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10488
10489    The difference between those cases is finding possible inherited bindings
10490    that are overridden, as one has to look for them in tb_sym_root,
10491    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10492    the super-type and set p->overridden correctly.  */
10493
10494 static gfc_try
10495 resolve_tb_generic_targets (gfc_symbol* super_type,
10496                             gfc_typebound_proc* p, const char* name)
10497 {
10498   gfc_tbp_generic* target;
10499   gfc_symtree* first_target;
10500   gfc_symtree* inherited;
10501
10502   gcc_assert (p && p->is_generic);
10503
10504   /* Try to find the specific bindings for the symtrees in our target-list.  */
10505   gcc_assert (p->u.generic);
10506   for (target = p->u.generic; target; target = target->next)
10507     if (!target->specific)
10508       {
10509         gfc_typebound_proc* overridden_tbp;
10510         gfc_tbp_generic* g;
10511         const char* target_name;
10512
10513         target_name = target->specific_st->name;
10514
10515         /* Defined for this type directly.  */
10516         if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
10517           {
10518             target->specific = target->specific_st->n.tb;
10519             goto specific_found;
10520           }
10521
10522         /* Look for an inherited specific binding.  */
10523         if (super_type)
10524           {
10525             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10526                                                  true, NULL);
10527
10528             if (inherited)
10529               {
10530                 gcc_assert (inherited->n.tb);
10531                 target->specific = inherited->n.tb;
10532                 goto specific_found;
10533               }
10534           }
10535
10536         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10537                    " at %L", target_name, name, &p->where);
10538         return FAILURE;
10539
10540         /* Once we've found the specific binding, check it is not ambiguous with
10541            other specifics already found or inherited for the same GENERIC.  */
10542 specific_found:
10543         gcc_assert (target->specific);
10544
10545         /* This must really be a specific binding!  */
10546         if (target->specific->is_generic)
10547           {
10548             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
10549                        " '%s' is GENERIC, too", name, &p->where, target_name);
10550             return FAILURE;
10551           }
10552
10553         /* Check those already resolved on this type directly.  */
10554         for (g = p->u.generic; g; g = g->next)
10555           if (g != target && g->specific
10556               && check_generic_tbp_ambiguity (target, g, name, p->where)
10557                   == FAILURE)
10558             return FAILURE;
10559
10560         /* Check for ambiguity with inherited specific targets.  */
10561         for (overridden_tbp = p->overridden; overridden_tbp;
10562              overridden_tbp = overridden_tbp->overridden)
10563           if (overridden_tbp->is_generic)
10564             {
10565               for (g = overridden_tbp->u.generic; g; g = g->next)
10566                 {
10567                   gcc_assert (g->specific);
10568                   if (check_generic_tbp_ambiguity (target, g,
10569                                                    name, p->where) == FAILURE)
10570                     return FAILURE;
10571                 }
10572             }
10573       }
10574
10575   /* If we attempt to "overwrite" a specific binding, this is an error.  */
10576   if (p->overridden && !p->overridden->is_generic)
10577     {
10578       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
10579                  " the same name", name, &p->where);
10580       return FAILURE;
10581     }
10582
10583   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
10584      all must have the same attributes here.  */
10585   first_target = p->u.generic->specific->u.specific;
10586   gcc_assert (first_target);
10587   p->subroutine = first_target->n.sym->attr.subroutine;
10588   p->function = first_target->n.sym->attr.function;
10589
10590   return SUCCESS;
10591 }
10592
10593
10594 /* Resolve a GENERIC procedure binding for a derived type.  */
10595
10596 static gfc_try
10597 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
10598 {
10599   gfc_symbol* super_type;
10600
10601   /* Find the overridden binding if any.  */
10602   st->n.tb->overridden = NULL;
10603   super_type = gfc_get_derived_super_type (derived);
10604   if (super_type)
10605     {
10606       gfc_symtree* overridden;
10607       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
10608                                             true, NULL);
10609
10610       if (overridden && overridden->n.tb)
10611         st->n.tb->overridden = overridden->n.tb;
10612     }
10613
10614   /* Resolve using worker function.  */
10615   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
10616 }
10617
10618
10619 /* Retrieve the target-procedure of an operator binding and do some checks in
10620    common for intrinsic and user-defined type-bound operators.  */
10621
10622 static gfc_symbol*
10623 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
10624 {
10625   gfc_symbol* target_proc;
10626
10627   gcc_assert (target->specific && !target->specific->is_generic);
10628   target_proc = target->specific->u.specific->n.sym;
10629   gcc_assert (target_proc);
10630
10631   /* All operator bindings must have a passed-object dummy argument.  */
10632   if (target->specific->nopass)
10633     {
10634       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
10635       return NULL;
10636     }
10637
10638   return target_proc;
10639 }
10640
10641
10642 /* Resolve a type-bound intrinsic operator.  */
10643
10644 static gfc_try
10645 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
10646                                 gfc_typebound_proc* p)
10647 {
10648   gfc_symbol* super_type;
10649   gfc_tbp_generic* target;
10650   
10651   /* If there's already an error here, do nothing (but don't fail again).  */
10652   if (p->error)
10653     return SUCCESS;
10654
10655   /* Operators should always be GENERIC bindings.  */
10656   gcc_assert (p->is_generic);
10657
10658   /* Look for an overridden binding.  */
10659   super_type = gfc_get_derived_super_type (derived);
10660   if (super_type && super_type->f2k_derived)
10661     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
10662                                                      op, true, NULL);
10663   else
10664     p->overridden = NULL;
10665
10666   /* Resolve general GENERIC properties using worker function.  */
10667   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
10668     goto error;
10669
10670   /* Check the targets to be procedures of correct interface.  */
10671   for (target = p->u.generic; target; target = target->next)
10672     {
10673       gfc_symbol* target_proc;
10674
10675       target_proc = get_checked_tb_operator_target (target, p->where);
10676       if (!target_proc)
10677         goto error;
10678
10679       if (!gfc_check_operator_interface (target_proc, op, p->where))
10680         goto error;
10681     }
10682
10683   return SUCCESS;
10684
10685 error:
10686   p->error = 1;
10687   return FAILURE;
10688 }
10689
10690
10691 /* Resolve a type-bound user operator (tree-walker callback).  */
10692
10693 static gfc_symbol* resolve_bindings_derived;
10694 static gfc_try resolve_bindings_result;
10695
10696 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
10697
10698 static void
10699 resolve_typebound_user_op (gfc_symtree* stree)
10700 {
10701   gfc_symbol* super_type;
10702   gfc_tbp_generic* target;
10703
10704   gcc_assert (stree && stree->n.tb);
10705
10706   if (stree->n.tb->error)
10707     return;
10708
10709   /* Operators should always be GENERIC bindings.  */
10710   gcc_assert (stree->n.tb->is_generic);
10711
10712   /* Find overridden procedure, if any.  */
10713   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10714   if (super_type && super_type->f2k_derived)
10715     {
10716       gfc_symtree* overridden;
10717       overridden = gfc_find_typebound_user_op (super_type, NULL,
10718                                                stree->name, true, NULL);
10719
10720       if (overridden && overridden->n.tb)
10721         stree->n.tb->overridden = overridden->n.tb;
10722     }
10723   else
10724     stree->n.tb->overridden = NULL;
10725
10726   /* Resolve basically using worker function.  */
10727   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
10728         == FAILURE)
10729     goto error;
10730
10731   /* Check the targets to be functions of correct interface.  */
10732   for (target = stree->n.tb->u.generic; target; target = target->next)
10733     {
10734       gfc_symbol* target_proc;
10735
10736       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
10737       if (!target_proc)
10738         goto error;
10739
10740       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
10741         goto error;
10742     }
10743
10744   return;
10745
10746 error:
10747   resolve_bindings_result = FAILURE;
10748   stree->n.tb->error = 1;
10749 }
10750
10751
10752 /* Resolve the type-bound procedures for a derived type.  */
10753
10754 static void
10755 resolve_typebound_procedure (gfc_symtree* stree)
10756 {
10757   gfc_symbol* proc;
10758   locus where;
10759   gfc_symbol* me_arg;
10760   gfc_symbol* super_type;
10761   gfc_component* comp;
10762
10763   gcc_assert (stree);
10764
10765   /* Undefined specific symbol from GENERIC target definition.  */
10766   if (!stree->n.tb)
10767     return;
10768
10769   if (stree->n.tb->error)
10770     return;
10771
10772   /* If this is a GENERIC binding, use that routine.  */
10773   if (stree->n.tb->is_generic)
10774     {
10775       if (resolve_typebound_generic (resolve_bindings_derived, stree)
10776             == FAILURE)
10777         goto error;
10778       return;
10779     }
10780
10781   /* Get the target-procedure to check it.  */
10782   gcc_assert (!stree->n.tb->is_generic);
10783   gcc_assert (stree->n.tb->u.specific);
10784   proc = stree->n.tb->u.specific->n.sym;
10785   where = stree->n.tb->where;
10786
10787   /* Default access should already be resolved from the parser.  */
10788   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
10789
10790   /* It should be a module procedure or an external procedure with explicit
10791      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
10792   if ((!proc->attr.subroutine && !proc->attr.function)
10793       || (proc->attr.proc != PROC_MODULE
10794           && proc->attr.if_source != IFSRC_IFBODY)
10795       || (proc->attr.abstract && !stree->n.tb->deferred))
10796     {
10797       gfc_error ("'%s' must be a module procedure or an external procedure with"
10798                  " an explicit interface at %L", proc->name, &where);
10799       goto error;
10800     }
10801   stree->n.tb->subroutine = proc->attr.subroutine;
10802   stree->n.tb->function = proc->attr.function;
10803
10804   /* Find the super-type of the current derived type.  We could do this once and
10805      store in a global if speed is needed, but as long as not I believe this is
10806      more readable and clearer.  */
10807   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10808
10809   /* If PASS, resolve and check arguments if not already resolved / loaded
10810      from a .mod file.  */
10811   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
10812     {
10813       if (stree->n.tb->pass_arg)
10814         {
10815           gfc_formal_arglist* i;
10816
10817           /* If an explicit passing argument name is given, walk the arg-list
10818              and look for it.  */
10819
10820           me_arg = NULL;
10821           stree->n.tb->pass_arg_num = 1;
10822           for (i = proc->formal; i; i = i->next)
10823             {
10824               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
10825                 {
10826                   me_arg = i->sym;
10827                   break;
10828                 }
10829               ++stree->n.tb->pass_arg_num;
10830             }
10831
10832           if (!me_arg)
10833             {
10834               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
10835                          " argument '%s'",
10836                          proc->name, stree->n.tb->pass_arg, &where,
10837                          stree->n.tb->pass_arg);
10838               goto error;
10839             }
10840         }
10841       else
10842         {
10843           /* Otherwise, take the first one; there should in fact be at least
10844              one.  */
10845           stree->n.tb->pass_arg_num = 1;
10846           if (!proc->formal)
10847             {
10848               gfc_error ("Procedure '%s' with PASS at %L must have at"
10849                          " least one argument", proc->name, &where);
10850               goto error;
10851             }
10852           me_arg = proc->formal->sym;
10853         }
10854
10855       /* Now check that the argument-type matches and the passed-object
10856          dummy argument is generally fine.  */
10857
10858       gcc_assert (me_arg);
10859
10860       if (me_arg->ts.type != BT_CLASS)
10861         {
10862           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10863                      " at %L", proc->name, &where);
10864           goto error;
10865         }
10866
10867       if (CLASS_DATA (me_arg)->ts.u.derived
10868           != resolve_bindings_derived)
10869         {
10870           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10871                      " the derived-type '%s'", me_arg->name, proc->name,
10872                      me_arg->name, &where, resolve_bindings_derived->name);
10873           goto error;
10874         }
10875   
10876       gcc_assert (me_arg->ts.type == BT_CLASS);
10877       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
10878         {
10879           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
10880                      " scalar", proc->name, &where);
10881           goto error;
10882         }
10883       if (CLASS_DATA (me_arg)->attr.allocatable)
10884         {
10885           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10886                      " be ALLOCATABLE", proc->name, &where);
10887           goto error;
10888         }
10889       if (CLASS_DATA (me_arg)->attr.class_pointer)
10890         {
10891           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10892                      " be POINTER", proc->name, &where);
10893           goto error;
10894         }
10895     }
10896
10897   /* If we are extending some type, check that we don't override a procedure
10898      flagged NON_OVERRIDABLE.  */
10899   stree->n.tb->overridden = NULL;
10900   if (super_type)
10901     {
10902       gfc_symtree* overridden;
10903       overridden = gfc_find_typebound_proc (super_type, NULL,
10904                                             stree->name, true, NULL);
10905
10906       if (overridden && overridden->n.tb)
10907         stree->n.tb->overridden = overridden->n.tb;
10908
10909       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
10910         goto error;
10911     }
10912
10913   /* See if there's a name collision with a component directly in this type.  */
10914   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
10915     if (!strcmp (comp->name, stree->name))
10916       {
10917         gfc_error ("Procedure '%s' at %L has the same name as a component of"
10918                    " '%s'",
10919                    stree->name, &where, resolve_bindings_derived->name);
10920         goto error;
10921       }
10922
10923   /* Try to find a name collision with an inherited component.  */
10924   if (super_type && gfc_find_component (super_type, stree->name, true, true))
10925     {
10926       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
10927                  " component of '%s'",
10928                  stree->name, &where, resolve_bindings_derived->name);
10929       goto error;
10930     }
10931
10932   stree->n.tb->error = 0;
10933   return;
10934
10935 error:
10936   resolve_bindings_result = FAILURE;
10937   stree->n.tb->error = 1;
10938 }
10939
10940 static gfc_try
10941 resolve_typebound_procedures (gfc_symbol* derived)
10942 {
10943   int op;
10944
10945   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
10946     return SUCCESS;
10947
10948   resolve_bindings_derived = derived;
10949   resolve_bindings_result = SUCCESS;
10950
10951   if (derived->f2k_derived->tb_sym_root)
10952     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
10953                           &resolve_typebound_procedure);
10954
10955   if (derived->f2k_derived->tb_uop_root)
10956     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
10957                           &resolve_typebound_user_op);
10958
10959   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
10960     {
10961       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
10962       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
10963                                                p) == FAILURE)
10964         resolve_bindings_result = FAILURE;
10965     }
10966
10967   return resolve_bindings_result;
10968 }
10969
10970
10971 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
10972    to give all identical derived types the same backend_decl.  */
10973 static void
10974 add_dt_to_dt_list (gfc_symbol *derived)
10975 {
10976   gfc_dt_list *dt_list;
10977
10978   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
10979     if (derived == dt_list->derived)
10980       break;
10981
10982   if (dt_list == NULL)
10983     {
10984       dt_list = gfc_get_dt_list ();
10985       dt_list->next = gfc_derived_types;
10986       dt_list->derived = derived;
10987       gfc_derived_types = dt_list;
10988     }
10989 }
10990
10991
10992 /* Ensure that a derived-type is really not abstract, meaning that every
10993    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
10994
10995 static gfc_try
10996 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
10997 {
10998   if (!st)
10999     return SUCCESS;
11000
11001   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
11002     return FAILURE;
11003   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
11004     return FAILURE;
11005
11006   if (st->n.tb && st->n.tb->deferred)
11007     {
11008       gfc_symtree* overriding;
11009       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
11010       if (!overriding)
11011         return FAILURE;
11012       gcc_assert (overriding->n.tb);
11013       if (overriding->n.tb->deferred)
11014         {
11015           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
11016                      " '%s' is DEFERRED and not overridden",
11017                      sub->name, &sub->declared_at, st->name);
11018           return FAILURE;
11019         }
11020     }
11021
11022   return SUCCESS;
11023 }
11024
11025 static gfc_try
11026 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
11027 {
11028   /* The algorithm used here is to recursively travel up the ancestry of sub
11029      and for each ancestor-type, check all bindings.  If any of them is
11030      DEFERRED, look it up starting from sub and see if the found (overriding)
11031      binding is not DEFERRED.
11032      This is not the most efficient way to do this, but it should be ok and is
11033      clearer than something sophisticated.  */
11034
11035   gcc_assert (ancestor && !sub->attr.abstract);
11036   
11037   if (!ancestor->attr.abstract)
11038     return SUCCESS;
11039
11040   /* Walk bindings of this ancestor.  */
11041   if (ancestor->f2k_derived)
11042     {
11043       gfc_try t;
11044       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
11045       if (t == FAILURE)
11046         return FAILURE;
11047     }
11048
11049   /* Find next ancestor type and recurse on it.  */
11050   ancestor = gfc_get_derived_super_type (ancestor);
11051   if (ancestor)
11052     return ensure_not_abstract (sub, ancestor);
11053
11054   return SUCCESS;
11055 }
11056
11057
11058 /* Resolve the components of a derived type.  */
11059
11060 static gfc_try
11061 resolve_fl_derived (gfc_symbol *sym)
11062 {
11063   gfc_symbol* super_type;
11064   gfc_component *c;
11065
11066   super_type = gfc_get_derived_super_type (sym);
11067   
11068   if (sym->attr.is_class && sym->ts.u.derived == NULL)
11069     {
11070       /* Fix up incomplete CLASS symbols.  */
11071       gfc_component *data = gfc_find_component (sym, "$data", true, true);
11072       gfc_component *vptr = gfc_find_component (sym, "$vptr", true, true);
11073       if (vptr->ts.u.derived == NULL)
11074         {
11075           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
11076           gcc_assert (vtab);
11077           vptr->ts.u.derived = vtab->ts.u.derived;
11078         }
11079     }
11080
11081   /* F2008, C432. */
11082   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
11083     {
11084       gfc_error ("As extending type '%s' at %L has a coarray component, "
11085                  "parent type '%s' shall also have one", sym->name,
11086                  &sym->declared_at, super_type->name);
11087       return FAILURE;
11088     }
11089
11090   /* Ensure the extended type gets resolved before we do.  */
11091   if (super_type && resolve_fl_derived (super_type) == FAILURE)
11092     return FAILURE;
11093
11094   /* An ABSTRACT type must be extensible.  */
11095   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
11096     {
11097       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
11098                  sym->name, &sym->declared_at);
11099       return FAILURE;
11100     }
11101
11102   for (c = sym->components; c != NULL; c = c->next)
11103     {
11104       /* F2008, C442.  */
11105       if (c->attr.codimension /* FIXME: c->as check due to PR 43412.  */
11106           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
11107         {
11108           gfc_error ("Coarray component '%s' at %L must be allocatable with "
11109                      "deferred shape", c->name, &c->loc);
11110           return FAILURE;
11111         }
11112
11113       /* F2008, C443.  */
11114       if (c->attr.codimension && c->ts.type == BT_DERIVED
11115           && c->ts.u.derived->ts.is_iso_c)
11116         {
11117           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11118                      "shall not be a coarray", c->name, &c->loc);
11119           return FAILURE;
11120         }
11121
11122       /* F2008, C444.  */
11123       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
11124           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
11125               || c->attr.allocatable))
11126         {
11127           gfc_error ("Component '%s' at %L with coarray component "
11128                      "shall be a nonpointer, nonallocatable scalar",
11129                      c->name, &c->loc);
11130           return FAILURE;
11131         }
11132
11133       /* F2008, C448.  */
11134       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
11135         {
11136           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
11137                      "is not an array pointer", c->name, &c->loc);
11138           return FAILURE;
11139         }
11140
11141       if (c->attr.proc_pointer && c->ts.interface)
11142         {
11143           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
11144             gfc_error ("Interface '%s', used by procedure pointer component "
11145                        "'%s' at %L, is declared in a later PROCEDURE statement",
11146                        c->ts.interface->name, c->name, &c->loc);
11147
11148           /* Get the attributes from the interface (now resolved).  */
11149           if (c->ts.interface->attr.if_source
11150               || c->ts.interface->attr.intrinsic)
11151             {
11152               gfc_symbol *ifc = c->ts.interface;
11153
11154               if (ifc->formal && !ifc->formal_ns)
11155                 resolve_symbol (ifc);
11156
11157               if (ifc->attr.intrinsic)
11158                 resolve_intrinsic (ifc, &ifc->declared_at);
11159
11160               if (ifc->result)
11161                 {
11162                   c->ts = ifc->result->ts;
11163                   c->attr.allocatable = ifc->result->attr.allocatable;
11164                   c->attr.pointer = ifc->result->attr.pointer;
11165                   c->attr.dimension = ifc->result->attr.dimension;
11166                   c->as = gfc_copy_array_spec (ifc->result->as);
11167                 }
11168               else
11169                 {   
11170                   c->ts = ifc->ts;
11171                   c->attr.allocatable = ifc->attr.allocatable;
11172                   c->attr.pointer = ifc->attr.pointer;
11173                   c->attr.dimension = ifc->attr.dimension;
11174                   c->as = gfc_copy_array_spec (ifc->as);
11175                 }
11176               c->ts.interface = ifc;
11177               c->attr.function = ifc->attr.function;
11178               c->attr.subroutine = ifc->attr.subroutine;
11179               gfc_copy_formal_args_ppc (c, ifc);
11180
11181               c->attr.pure = ifc->attr.pure;
11182               c->attr.elemental = ifc->attr.elemental;
11183               c->attr.recursive = ifc->attr.recursive;
11184               c->attr.always_explicit = ifc->attr.always_explicit;
11185               c->attr.ext_attr |= ifc->attr.ext_attr;
11186               /* Replace symbols in array spec.  */
11187               if (c->as)
11188                 {
11189                   int i;
11190                   for (i = 0; i < c->as->rank; i++)
11191                     {
11192                       gfc_expr_replace_comp (c->as->lower[i], c);
11193                       gfc_expr_replace_comp (c->as->upper[i], c);
11194                     }
11195                 }
11196               /* Copy char length.  */
11197               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11198                 {
11199                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11200                   gfc_expr_replace_comp (cl->length, c);
11201                   if (cl->length && !cl->resolved
11202                         && gfc_resolve_expr (cl->length) == FAILURE)
11203                     return FAILURE;
11204                   c->ts.u.cl = cl;
11205                 }
11206             }
11207           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
11208             {
11209               gfc_error ("Interface '%s' of procedure pointer component "
11210                          "'%s' at %L must be explicit", c->ts.interface->name,
11211                          c->name, &c->loc);
11212               return FAILURE;
11213             }
11214         }
11215       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
11216         {
11217           /* Since PPCs are not implicitly typed, a PPC without an explicit
11218              interface must be a subroutine.  */
11219           gfc_add_subroutine (&c->attr, c->name, &c->loc);
11220         }
11221
11222       /* Procedure pointer components: Check PASS arg.  */
11223       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
11224           && !sym->attr.vtype)
11225         {
11226           gfc_symbol* me_arg;
11227
11228           if (c->tb->pass_arg)
11229             {
11230               gfc_formal_arglist* i;
11231
11232               /* If an explicit passing argument name is given, walk the arg-list
11233                 and look for it.  */
11234
11235               me_arg = NULL;
11236               c->tb->pass_arg_num = 1;
11237               for (i = c->formal; i; i = i->next)
11238                 {
11239                   if (!strcmp (i->sym->name, c->tb->pass_arg))
11240                     {
11241                       me_arg = i->sym;
11242                       break;
11243                     }
11244                   c->tb->pass_arg_num++;
11245                 }
11246
11247               if (!me_arg)
11248                 {
11249                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
11250                              "at %L has no argument '%s'", c->name,
11251                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
11252                   c->tb->error = 1;
11253                   return FAILURE;
11254                 }
11255             }
11256           else
11257             {
11258               /* Otherwise, take the first one; there should in fact be at least
11259                 one.  */
11260               c->tb->pass_arg_num = 1;
11261               if (!c->formal)
11262                 {
11263                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
11264                              "must have at least one argument",
11265                              c->name, &c->loc);
11266                   c->tb->error = 1;
11267                   return FAILURE;
11268                 }
11269               me_arg = c->formal->sym;
11270             }
11271
11272           /* Now check that the argument-type matches.  */
11273           gcc_assert (me_arg);
11274           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
11275               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
11276               || (me_arg->ts.type == BT_CLASS
11277                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
11278             {
11279               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11280                          " the derived type '%s'", me_arg->name, c->name,
11281                          me_arg->name, &c->loc, sym->name);
11282               c->tb->error = 1;
11283               return FAILURE;
11284             }
11285
11286           /* Check for C453.  */
11287           if (me_arg->attr.dimension)
11288             {
11289               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11290                          "must be scalar", me_arg->name, c->name, me_arg->name,
11291                          &c->loc);
11292               c->tb->error = 1;
11293               return FAILURE;
11294             }
11295
11296           if (me_arg->attr.pointer)
11297             {
11298               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11299                          "may not have the POINTER attribute", me_arg->name,
11300                          c->name, me_arg->name, &c->loc);
11301               c->tb->error = 1;
11302               return FAILURE;
11303             }
11304
11305           if (me_arg->attr.allocatable)
11306             {
11307               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11308                          "may not be ALLOCATABLE", me_arg->name, c->name,
11309                          me_arg->name, &c->loc);
11310               c->tb->error = 1;
11311               return FAILURE;
11312             }
11313
11314           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11315             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11316                        " at %L", c->name, &c->loc);
11317
11318         }
11319
11320       /* Check type-spec if this is not the parent-type component.  */
11321       if ((!sym->attr.extension || c != sym->components)
11322           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11323         return FAILURE;
11324
11325       /* If this type is an extension, set the accessibility of the parent
11326          component.  */
11327       if (super_type && c == sym->components
11328           && strcmp (super_type->name, c->name) == 0)
11329         c->attr.access = super_type->attr.access;
11330       
11331       /* If this type is an extension, see if this component has the same name
11332          as an inherited type-bound procedure.  */
11333       if (super_type && !sym->attr.is_class
11334           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11335         {
11336           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11337                      " inherited type-bound procedure",
11338                      c->name, sym->name, &c->loc);
11339           return FAILURE;
11340         }
11341
11342       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer)
11343         {
11344          if (c->ts.u.cl->length == NULL
11345              || (resolve_charlen (c->ts.u.cl) == FAILURE)
11346              || !gfc_is_constant_expr (c->ts.u.cl->length))
11347            {
11348              gfc_error ("Character length of component '%s' needs to "
11349                         "be a constant specification expression at %L",
11350                         c->name,
11351                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
11352              return FAILURE;
11353            }
11354         }
11355
11356       if (c->ts.type == BT_DERIVED
11357           && sym->component_access != ACCESS_PRIVATE
11358           && gfc_check_access (sym->attr.access, sym->ns->default_access)
11359           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11360           && !c->ts.u.derived->attr.use_assoc
11361           && !gfc_check_access (c->ts.u.derived->attr.access,
11362                                 c->ts.u.derived->ns->default_access)
11363           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11364                              "is a PRIVATE type and cannot be a component of "
11365                              "'%s', which is PUBLIC at %L", c->name,
11366                              sym->name, &sym->declared_at) == FAILURE)
11367         return FAILURE;
11368
11369       if (sym->attr.sequence)
11370         {
11371           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
11372             {
11373               gfc_error ("Component %s of SEQUENCE type declared at %L does "
11374                          "not have the SEQUENCE attribute",
11375                          c->ts.u.derived->name, &sym->declared_at);
11376               return FAILURE;
11377             }
11378         }
11379
11380       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && c->attr.pointer
11381           && c->ts.u.derived->components == NULL
11382           && !c->ts.u.derived->attr.zero_comp)
11383         {
11384           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11385                      "that has not been declared", c->name, sym->name,
11386                      &c->loc);
11387           return FAILURE;
11388         }
11389
11390       if (c->ts.type == BT_CLASS && CLASS_DATA (c)->attr.class_pointer
11391           && CLASS_DATA (c)->ts.u.derived->components == NULL
11392           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
11393         {
11394           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11395                      "that has not been declared", c->name, sym->name,
11396                      &c->loc);
11397           return FAILURE;
11398         }
11399
11400       /* C437.  */
11401       if (c->ts.type == BT_CLASS
11402           && !(CLASS_DATA (c)->attr.class_pointer
11403                || CLASS_DATA (c)->attr.allocatable))
11404         {
11405           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
11406                      "or pointer", c->name, &c->loc);
11407           return FAILURE;
11408         }
11409
11410       /* Ensure that all the derived type components are put on the
11411          derived type list; even in formal namespaces, where derived type
11412          pointer components might not have been declared.  */
11413       if (c->ts.type == BT_DERIVED
11414             && c->ts.u.derived
11415             && c->ts.u.derived->components
11416             && c->attr.pointer
11417             && sym != c->ts.u.derived)
11418         add_dt_to_dt_list (c->ts.u.derived);
11419
11420       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
11421                                            || c->attr.proc_pointer
11422                                            || c->attr.allocatable)) == FAILURE)
11423         return FAILURE;
11424     }
11425
11426   /* Resolve the type-bound procedures.  */
11427   if (resolve_typebound_procedures (sym) == FAILURE)
11428     return FAILURE;
11429
11430   /* Resolve the finalizer procedures.  */
11431   if (gfc_resolve_finalizers (sym) == FAILURE)
11432     return FAILURE;
11433
11434   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11435      all DEFERRED bindings are overridden.  */
11436   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11437       && !sym->attr.is_class
11438       && ensure_not_abstract (sym, super_type) == FAILURE)
11439     return FAILURE;
11440
11441   /* Add derived type to the derived type list.  */
11442   add_dt_to_dt_list (sym);
11443
11444   return SUCCESS;
11445 }
11446
11447
11448 static gfc_try
11449 resolve_fl_namelist (gfc_symbol *sym)
11450 {
11451   gfc_namelist *nl;
11452   gfc_symbol *nlsym;
11453
11454   /* Reject PRIVATE objects in a PUBLIC namelist.  */
11455   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
11456     {
11457       for (nl = sym->namelist; nl; nl = nl->next)
11458         {
11459           if (!nl->sym->attr.use_assoc
11460               && !is_sym_host_assoc (nl->sym, sym->ns)
11461               && !gfc_check_access(nl->sym->attr.access,
11462                                 nl->sym->ns->default_access))
11463             {
11464               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
11465                          "cannot be member of PUBLIC namelist '%s' at %L",
11466                          nl->sym->name, sym->name, &sym->declared_at);
11467               return FAILURE;
11468             }
11469
11470           /* Types with private components that came here by USE-association.  */
11471           if (nl->sym->ts.type == BT_DERIVED
11472               && derived_inaccessible (nl->sym->ts.u.derived))
11473             {
11474               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
11475                          "components and cannot be member of namelist '%s' at %L",
11476                          nl->sym->name, sym->name, &sym->declared_at);
11477               return FAILURE;
11478             }
11479
11480           /* Types with private components that are defined in the same module.  */
11481           if (nl->sym->ts.type == BT_DERIVED
11482               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
11483               && !gfc_check_access (nl->sym->ts.u.derived->attr.private_comp
11484                                         ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
11485                                         nl->sym->ns->default_access))
11486             {
11487               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
11488                          "cannot be a member of PUBLIC namelist '%s' at %L",
11489                          nl->sym->name, sym->name, &sym->declared_at);
11490               return FAILURE;
11491             }
11492         }
11493     }
11494
11495   for (nl = sym->namelist; nl; nl = nl->next)
11496     {
11497       /* Reject namelist arrays of assumed shape.  */
11498       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
11499           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
11500                              "must not have assumed shape in namelist "
11501                              "'%s' at %L", nl->sym->name, sym->name,
11502                              &sym->declared_at) == FAILURE)
11503             return FAILURE;
11504
11505       /* Reject namelist arrays that are not constant shape.  */
11506       if (is_non_constant_shape_array (nl->sym))
11507         {
11508           gfc_error ("NAMELIST array object '%s' must have constant "
11509                      "shape in namelist '%s' at %L", nl->sym->name,
11510                      sym->name, &sym->declared_at);
11511           return FAILURE;
11512         }
11513
11514       /* Namelist objects cannot have allocatable or pointer components.  */
11515       if (nl->sym->ts.type != BT_DERIVED)
11516         continue;
11517
11518       if (nl->sym->ts.u.derived->attr.alloc_comp)
11519         {
11520           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11521                      "have ALLOCATABLE components",
11522                      nl->sym->name, sym->name, &sym->declared_at);
11523           return FAILURE;
11524         }
11525
11526       if (nl->sym->ts.u.derived->attr.pointer_comp)
11527         {
11528           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11529                      "have POINTER components", 
11530                      nl->sym->name, sym->name, &sym->declared_at);
11531           return FAILURE;
11532         }
11533     }
11534
11535
11536   /* 14.1.2 A module or internal procedure represent local entities
11537      of the same type as a namelist member and so are not allowed.  */
11538   for (nl = sym->namelist; nl; nl = nl->next)
11539     {
11540       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
11541         continue;
11542
11543       if (nl->sym->attr.function && nl->sym == nl->sym->result)
11544         if ((nl->sym == sym->ns->proc_name)
11545                ||
11546             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
11547           continue;
11548
11549       nlsym = NULL;
11550       if (nl->sym && nl->sym->name)
11551         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
11552       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
11553         {
11554           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
11555                      "attribute in '%s' at %L", nlsym->name,
11556                      &sym->declared_at);
11557           return FAILURE;
11558         }
11559     }
11560
11561   return SUCCESS;
11562 }
11563
11564
11565 static gfc_try
11566 resolve_fl_parameter (gfc_symbol *sym)
11567 {
11568   /* A parameter array's shape needs to be constant.  */
11569   if (sym->as != NULL 
11570       && (sym->as->type == AS_DEFERRED
11571           || is_non_constant_shape_array (sym)))
11572     {
11573       gfc_error ("Parameter array '%s' at %L cannot be automatic "
11574                  "or of deferred shape", sym->name, &sym->declared_at);
11575       return FAILURE;
11576     }
11577
11578   /* Make sure a parameter that has been implicitly typed still
11579      matches the implicit type, since PARAMETER statements can precede
11580      IMPLICIT statements.  */
11581   if (sym->attr.implicit_type
11582       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
11583                                                              sym->ns)))
11584     {
11585       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
11586                  "later IMPLICIT type", sym->name, &sym->declared_at);
11587       return FAILURE;
11588     }
11589
11590   /* Make sure the types of derived parameters are consistent.  This
11591      type checking is deferred until resolution because the type may
11592      refer to a derived type from the host.  */
11593   if (sym->ts.type == BT_DERIVED
11594       && !gfc_compare_types (&sym->ts, &sym->value->ts))
11595     {
11596       gfc_error ("Incompatible derived type in PARAMETER at %L",
11597                  &sym->value->where);
11598       return FAILURE;
11599     }
11600   return SUCCESS;
11601 }
11602
11603
11604 /* Do anything necessary to resolve a symbol.  Right now, we just
11605    assume that an otherwise unknown symbol is a variable.  This sort
11606    of thing commonly happens for symbols in module.  */
11607
11608 static void
11609 resolve_symbol (gfc_symbol *sym)
11610 {
11611   int check_constant, mp_flag;
11612   gfc_symtree *symtree;
11613   gfc_symtree *this_symtree;
11614   gfc_namespace *ns;
11615   gfc_component *c;
11616
11617   /* Avoid double resolution of function result symbols.  */
11618   if ((sym->result || sym->attr.result) && !sym->attr.dummy
11619       && (sym->ns != gfc_current_ns))
11620     return;
11621   
11622   if (sym->attr.flavor == FL_UNKNOWN)
11623     {
11624
11625     /* If we find that a flavorless symbol is an interface in one of the
11626        parent namespaces, find its symtree in this namespace, free the
11627        symbol and set the symtree to point to the interface symbol.  */
11628       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
11629         {
11630           symtree = gfc_find_symtree (ns->sym_root, sym->name);
11631           if (symtree && symtree->n.sym->generic)
11632             {
11633               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
11634                                                sym->name);
11635               gfc_release_symbol (sym);
11636               symtree->n.sym->refs++;
11637               this_symtree->n.sym = symtree->n.sym;
11638               return;
11639             }
11640         }
11641
11642       /* Otherwise give it a flavor according to such attributes as
11643          it has.  */
11644       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
11645         sym->attr.flavor = FL_VARIABLE;
11646       else
11647         {
11648           sym->attr.flavor = FL_PROCEDURE;
11649           if (sym->attr.dimension)
11650             sym->attr.function = 1;
11651         }
11652     }
11653
11654   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
11655     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
11656
11657   if (sym->attr.procedure && sym->ts.interface
11658       && sym->attr.if_source != IFSRC_DECL
11659       && resolve_procedure_interface (sym) == FAILURE)
11660     return;
11661
11662   if (sym->attr.is_protected && !sym->attr.proc_pointer
11663       && (sym->attr.procedure || sym->attr.external))
11664     {
11665       if (sym->attr.external)
11666         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
11667                    "at %L", &sym->declared_at);
11668       else
11669         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
11670                    "at %L", &sym->declared_at);
11671
11672       return;
11673     }
11674
11675
11676   /* F2008, C530. */
11677   if (sym->attr.contiguous
11678       && (!sym->attr.dimension || (sym->as->type != AS_ASSUMED_SHAPE
11679                                    && !sym->attr.pointer)))
11680     {
11681       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
11682                   "array pointer or an assumed-shape array", sym->name,
11683                   &sym->declared_at);
11684       return;
11685     }
11686
11687   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
11688     return;
11689
11690   /* Symbols that are module procedures with results (functions) have
11691      the types and array specification copied for type checking in
11692      procedures that call them, as well as for saving to a module
11693      file.  These symbols can't stand the scrutiny that their results
11694      can.  */
11695   mp_flag = (sym->result != NULL && sym->result != sym);
11696
11697   /* Make sure that the intrinsic is consistent with its internal 
11698      representation. This needs to be done before assigning a default 
11699      type to avoid spurious warnings.  */
11700   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
11701       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
11702     return;
11703
11704   /* For associate names, resolve corresponding expression and make sure
11705      they get their type-spec set this way.  */
11706   if (sym->assoc)
11707     {
11708       gfc_expr* target;
11709       bool to_var;
11710
11711       gcc_assert (sym->attr.flavor == FL_VARIABLE);
11712
11713       target = sym->assoc->target;
11714       if (gfc_resolve_expr (target) != SUCCESS)
11715         return;
11716
11717       /* For variable targets, we get some attributes from the target.  */
11718       if (target->expr_type == EXPR_VARIABLE)
11719         {
11720           gfc_symbol* tsym;
11721
11722           gcc_assert (target->symtree);
11723           tsym = target->symtree->n.sym;
11724
11725           sym->attr.asynchronous = tsym->attr.asynchronous;
11726           sym->attr.volatile_ = tsym->attr.volatile_;
11727
11728           sym->attr.target = (tsym->attr.target || tsym->attr.pointer);
11729         }
11730
11731       sym->ts = target->ts;
11732       gcc_assert (sym->ts.type != BT_UNKNOWN);
11733
11734       /* See if this is a valid association-to-variable.  */
11735       to_var = (target->expr_type == EXPR_VARIABLE
11736                 && !gfc_has_vector_subscript (target));
11737       if (sym->assoc->variable && !to_var)
11738         {
11739           if (target->expr_type == EXPR_VARIABLE)
11740             gfc_error ("'%s' at %L associated to vector-indexed target can not"
11741                        " be used in a variable definition context",
11742                        sym->name, &sym->declared_at);
11743           else
11744             gfc_error ("'%s' at %L associated to expression can not"
11745                        " be used in a variable definition context",
11746                        sym->name, &sym->declared_at);
11747
11748           return;
11749         }
11750       sym->assoc->variable = to_var;
11751
11752       /* Finally resolve if this is an array or not.  */
11753       if (sym->attr.dimension && target->rank == 0)
11754         {
11755           gfc_error ("Associate-name '%s' at %L is used as array",
11756                      sym->name, &sym->declared_at);
11757           sym->attr.dimension = 0;
11758           return;
11759         }
11760       if (target->rank > 0)
11761         sym->attr.dimension = 1;
11762
11763       if (sym->attr.dimension)
11764         {
11765           sym->as = gfc_get_array_spec ();
11766           sym->as->rank = target->rank;
11767           sym->as->type = AS_DEFERRED;
11768
11769           /* Target must not be coindexed, thus the associate-variable
11770              has no corank.  */
11771           sym->as->corank = 0;
11772         }
11773     }
11774
11775   /* Assign default type to symbols that need one and don't have one.  */
11776   if (sym->ts.type == BT_UNKNOWN)
11777     {
11778       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
11779         gfc_set_default_type (sym, 1, NULL);
11780
11781       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
11782           && !sym->attr.function && !sym->attr.subroutine
11783           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
11784         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
11785
11786       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
11787         {
11788           /* The specific case of an external procedure should emit an error
11789              in the case that there is no implicit type.  */
11790           if (!mp_flag)
11791             gfc_set_default_type (sym, sym->attr.external, NULL);
11792           else
11793             {
11794               /* Result may be in another namespace.  */
11795               resolve_symbol (sym->result);
11796
11797               if (!sym->result->attr.proc_pointer)
11798                 {
11799                   sym->ts = sym->result->ts;
11800                   sym->as = gfc_copy_array_spec (sym->result->as);
11801                   sym->attr.dimension = sym->result->attr.dimension;
11802                   sym->attr.pointer = sym->result->attr.pointer;
11803                   sym->attr.allocatable = sym->result->attr.allocatable;
11804                   sym->attr.contiguous = sym->result->attr.contiguous;
11805                 }
11806             }
11807         }
11808     }
11809
11810   /* Assumed size arrays and assumed shape arrays must be dummy
11811      arguments.  Array-spec's of implied-shape should have been resolved to
11812      AS_EXPLICIT already.  */
11813
11814   if (sym->as)
11815     {
11816       gcc_assert (sym->as->type != AS_IMPLIED_SHAPE);
11817       if (((sym->as->type == AS_ASSUMED_SIZE && !sym->as->cp_was_assumed)
11818            || sym->as->type == AS_ASSUMED_SHAPE)
11819           && sym->attr.dummy == 0)
11820         {
11821           if (sym->as->type == AS_ASSUMED_SIZE)
11822             gfc_error ("Assumed size array at %L must be a dummy argument",
11823                        &sym->declared_at);
11824           else
11825             gfc_error ("Assumed shape array at %L must be a dummy argument",
11826                        &sym->declared_at);
11827           return;
11828         }
11829     }
11830
11831   /* Make sure symbols with known intent or optional are really dummy
11832      variable.  Because of ENTRY statement, this has to be deferred
11833      until resolution time.  */
11834
11835   if (!sym->attr.dummy
11836       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
11837     {
11838       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
11839       return;
11840     }
11841
11842   if (sym->attr.value && !sym->attr.dummy)
11843     {
11844       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
11845                  "it is not a dummy argument", sym->name, &sym->declared_at);
11846       return;
11847     }
11848
11849   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
11850     {
11851       gfc_charlen *cl = sym->ts.u.cl;
11852       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
11853         {
11854           gfc_error ("Character dummy variable '%s' at %L with VALUE "
11855                      "attribute must have constant length",
11856                      sym->name, &sym->declared_at);
11857           return;
11858         }
11859
11860       if (sym->ts.is_c_interop
11861           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
11862         {
11863           gfc_error ("C interoperable character dummy variable '%s' at %L "
11864                      "with VALUE attribute must have length one",
11865                      sym->name, &sym->declared_at);
11866           return;
11867         }
11868     }
11869
11870   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
11871      do this for something that was implicitly typed because that is handled
11872      in gfc_set_default_type.  Handle dummy arguments and procedure
11873      definitions separately.  Also, anything that is use associated is not
11874      handled here but instead is handled in the module it is declared in.
11875      Finally, derived type definitions are allowed to be BIND(C) since that
11876      only implies that they're interoperable, and they are checked fully for
11877      interoperability when a variable is declared of that type.  */
11878   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
11879       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
11880       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
11881     {
11882       gfc_try t = SUCCESS;
11883       
11884       /* First, make sure the variable is declared at the
11885          module-level scope (J3/04-007, Section 15.3).  */
11886       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
11887           sym->attr.in_common == 0)
11888         {
11889           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
11890                      "is neither a COMMON block nor declared at the "
11891                      "module level scope", sym->name, &(sym->declared_at));
11892           t = FAILURE;
11893         }
11894       else if (sym->common_head != NULL)
11895         {
11896           t = verify_com_block_vars_c_interop (sym->common_head);
11897         }
11898       else
11899         {
11900           /* If type() declaration, we need to verify that the components
11901              of the given type are all C interoperable, etc.  */
11902           if (sym->ts.type == BT_DERIVED &&
11903               sym->ts.u.derived->attr.is_c_interop != 1)
11904             {
11905               /* Make sure the user marked the derived type as BIND(C).  If
11906                  not, call the verify routine.  This could print an error
11907                  for the derived type more than once if multiple variables
11908                  of that type are declared.  */
11909               if (sym->ts.u.derived->attr.is_bind_c != 1)
11910                 verify_bind_c_derived_type (sym->ts.u.derived);
11911               t = FAILURE;
11912             }
11913           
11914           /* Verify the variable itself as C interoperable if it
11915              is BIND(C).  It is not possible for this to succeed if
11916              the verify_bind_c_derived_type failed, so don't have to handle
11917              any error returned by verify_bind_c_derived_type.  */
11918           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
11919                                  sym->common_block);
11920         }
11921
11922       if (t == FAILURE)
11923         {
11924           /* clear the is_bind_c flag to prevent reporting errors more than
11925              once if something failed.  */
11926           sym->attr.is_bind_c = 0;
11927           return;
11928         }
11929     }
11930
11931   /* If a derived type symbol has reached this point, without its
11932      type being declared, we have an error.  Notice that most
11933      conditions that produce undefined derived types have already
11934      been dealt with.  However, the likes of:
11935      implicit type(t) (t) ..... call foo (t) will get us here if
11936      the type is not declared in the scope of the implicit
11937      statement. Change the type to BT_UNKNOWN, both because it is so
11938      and to prevent an ICE.  */
11939   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
11940       && !sym->ts.u.derived->attr.zero_comp)
11941     {
11942       gfc_error ("The derived type '%s' at %L is of type '%s', "
11943                  "which has not been defined", sym->name,
11944                   &sym->declared_at, sym->ts.u.derived->name);
11945       sym->ts.type = BT_UNKNOWN;
11946       return;
11947     }
11948
11949   /* Make sure that the derived type has been resolved and that the
11950      derived type is visible in the symbol's namespace, if it is a
11951      module function and is not PRIVATE.  */
11952   if (sym->ts.type == BT_DERIVED
11953         && sym->ts.u.derived->attr.use_assoc
11954         && sym->ns->proc_name
11955         && sym->ns->proc_name->attr.flavor == FL_MODULE)
11956     {
11957       gfc_symbol *ds;
11958
11959       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
11960         return;
11961
11962       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
11963       if (!ds && sym->attr.function
11964             && gfc_check_access (sym->attr.access, sym->ns->default_access))
11965         {
11966           symtree = gfc_new_symtree (&sym->ns->sym_root,
11967                                      sym->ts.u.derived->name);
11968           symtree->n.sym = sym->ts.u.derived;
11969           sym->ts.u.derived->refs++;
11970         }
11971     }
11972
11973   /* Unless the derived-type declaration is use associated, Fortran 95
11974      does not allow public entries of private derived types.
11975      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
11976      161 in 95-006r3.  */
11977   if (sym->ts.type == BT_DERIVED
11978       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
11979       && !sym->ts.u.derived->attr.use_assoc
11980       && gfc_check_access (sym->attr.access, sym->ns->default_access)
11981       && !gfc_check_access (sym->ts.u.derived->attr.access,
11982                             sym->ts.u.derived->ns->default_access)
11983       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
11984                          "of PRIVATE derived type '%s'",
11985                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
11986                          : "variable", sym->name, &sym->declared_at,
11987                          sym->ts.u.derived->name) == FAILURE)
11988     return;
11989
11990   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
11991      default initialization is defined (5.1.2.4.4).  */
11992   if (sym->ts.type == BT_DERIVED
11993       && sym->attr.dummy
11994       && sym->attr.intent == INTENT_OUT
11995       && sym->as
11996       && sym->as->type == AS_ASSUMED_SIZE)
11997     {
11998       for (c = sym->ts.u.derived->components; c; c = c->next)
11999         {
12000           if (c->initializer)
12001             {
12002               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
12003                          "ASSUMED SIZE and so cannot have a default initializer",
12004                          sym->name, &sym->declared_at);
12005               return;
12006             }
12007         }
12008     }
12009
12010   /* F2008, C526.  */
12011   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12012        || sym->attr.codimension)
12013       && sym->attr.result)
12014     gfc_error ("Function result '%s' at %L shall not be a coarray or have "
12015                "a coarray component", sym->name, &sym->declared_at);
12016
12017   /* F2008, C524.  */
12018   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
12019       && sym->ts.u.derived->ts.is_iso_c)
12020     gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12021                "shall not be a coarray", sym->name, &sym->declared_at);
12022
12023   /* F2008, C525.  */
12024   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp
12025       && (sym->attr.codimension || sym->attr.pointer || sym->attr.dimension
12026           || sym->attr.allocatable))
12027     gfc_error ("Variable '%s' at %L with coarray component "
12028                "shall be a nonpointer, nonallocatable scalar",
12029                sym->name, &sym->declared_at);
12030
12031   /* F2008, C526.  The function-result case was handled above.  */
12032   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12033        || sym->attr.codimension)
12034       && !(sym->attr.allocatable || sym->attr.dummy || sym->attr.save
12035            || sym->ns->proc_name->attr.flavor == FL_MODULE
12036            || sym->ns->proc_name->attr.is_main_program
12037            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
12038     gfc_error ("Variable '%s' at %L is a coarray or has a coarray "
12039                "component and is not ALLOCATABLE, SAVE nor a "
12040                "dummy argument", sym->name, &sym->declared_at);
12041   /* F2008, C528.  */  /* FIXME: sym->as check due to PR 43412.  */
12042   else if (sym->attr.codimension && !sym->attr.allocatable
12043       && sym->as && sym->as->cotype == AS_DEFERRED)
12044     gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
12045                 "deferred shape", sym->name, &sym->declared_at);
12046   else if (sym->attr.codimension && sym->attr.allocatable
12047       && (sym->as->type != AS_DEFERRED || sym->as->cotype != AS_DEFERRED))
12048     gfc_error ("Allocatable coarray variable '%s' at %L must have "
12049                "deferred shape", sym->name, &sym->declared_at);
12050
12051
12052   /* F2008, C541.  */
12053   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12054        || (sym->attr.codimension && sym->attr.allocatable))
12055       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
12056     gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
12057                "allocatable coarray or have coarray components",
12058                sym->name, &sym->declared_at);
12059
12060   if (sym->attr.codimension && sym->attr.dummy
12061       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
12062     gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
12063                "procedure '%s'", sym->name, &sym->declared_at,
12064                sym->ns->proc_name->name);
12065
12066   switch (sym->attr.flavor)
12067     {
12068     case FL_VARIABLE:
12069       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
12070         return;
12071       break;
12072
12073     case FL_PROCEDURE:
12074       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
12075         return;
12076       break;
12077
12078     case FL_NAMELIST:
12079       if (resolve_fl_namelist (sym) == FAILURE)
12080         return;
12081       break;
12082
12083     case FL_PARAMETER:
12084       if (resolve_fl_parameter (sym) == FAILURE)
12085         return;
12086       break;
12087
12088     default:
12089       break;
12090     }
12091
12092   /* Resolve array specifier. Check as well some constraints
12093      on COMMON blocks.  */
12094
12095   check_constant = sym->attr.in_common && !sym->attr.pointer;
12096
12097   /* Set the formal_arg_flag so that check_conflict will not throw
12098      an error for host associated variables in the specification
12099      expression for an array_valued function.  */
12100   if (sym->attr.function && sym->as)
12101     formal_arg_flag = 1;
12102
12103   gfc_resolve_array_spec (sym->as, check_constant);
12104
12105   formal_arg_flag = 0;
12106
12107   /* Resolve formal namespaces.  */
12108   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
12109       && !sym->attr.contained && !sym->attr.intrinsic)
12110     gfc_resolve (sym->formal_ns);
12111
12112   /* Make sure the formal namespace is present.  */
12113   if (sym->formal && !sym->formal_ns)
12114     {
12115       gfc_formal_arglist *formal = sym->formal;
12116       while (formal && !formal->sym)
12117         formal = formal->next;
12118
12119       if (formal)
12120         {
12121           sym->formal_ns = formal->sym->ns;
12122           sym->formal_ns->refs++;
12123         }
12124     }
12125
12126   /* Check threadprivate restrictions.  */
12127   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
12128       && (!sym->attr.in_common
12129           && sym->module == NULL
12130           && (sym->ns->proc_name == NULL
12131               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
12132     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
12133
12134   /* If we have come this far we can apply default-initializers, as
12135      described in 14.7.5, to those variables that have not already
12136      been assigned one.  */
12137   if (sym->ts.type == BT_DERIVED
12138       && sym->attr.referenced
12139       && sym->ns == gfc_current_ns
12140       && !sym->value
12141       && !sym->attr.allocatable
12142       && !sym->attr.alloc_comp)
12143     {
12144       symbol_attribute *a = &sym->attr;
12145
12146       if ((!a->save && !a->dummy && !a->pointer
12147            && !a->in_common && !a->use_assoc
12148            && !(a->function && sym != sym->result))
12149           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
12150         apply_default_init (sym);
12151     }
12152
12153   /* If this symbol has a type-spec, check it.  */
12154   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
12155       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
12156     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
12157           == FAILURE)
12158       return;
12159 }
12160
12161
12162 /************* Resolve DATA statements *************/
12163
12164 static struct
12165 {
12166   gfc_data_value *vnode;
12167   mpz_t left;
12168 }
12169 values;
12170
12171
12172 /* Advance the values structure to point to the next value in the data list.  */
12173
12174 static gfc_try
12175 next_data_value (void)
12176 {
12177   while (mpz_cmp_ui (values.left, 0) == 0)
12178     {
12179
12180       if (values.vnode->next == NULL)
12181         return FAILURE;
12182
12183       values.vnode = values.vnode->next;
12184       mpz_set (values.left, values.vnode->repeat);
12185     }
12186
12187   return SUCCESS;
12188 }
12189
12190
12191 static gfc_try
12192 check_data_variable (gfc_data_variable *var, locus *where)
12193 {
12194   gfc_expr *e;
12195   mpz_t size;
12196   mpz_t offset;
12197   gfc_try t;
12198   ar_type mark = AR_UNKNOWN;
12199   int i;
12200   mpz_t section_index[GFC_MAX_DIMENSIONS];
12201   gfc_ref *ref;
12202   gfc_array_ref *ar;
12203   gfc_symbol *sym;
12204   int has_pointer;
12205
12206   if (gfc_resolve_expr (var->expr) == FAILURE)
12207     return FAILURE;
12208
12209   ar = NULL;
12210   mpz_init_set_si (offset, 0);
12211   e = var->expr;
12212
12213   if (e->expr_type != EXPR_VARIABLE)
12214     gfc_internal_error ("check_data_variable(): Bad expression");
12215
12216   sym = e->symtree->n.sym;
12217
12218   if (sym->ns->is_block_data && !sym->attr.in_common)
12219     {
12220       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
12221                  sym->name, &sym->declared_at);
12222     }
12223
12224   if (e->ref == NULL && sym->as)
12225     {
12226       gfc_error ("DATA array '%s' at %L must be specified in a previous"
12227                  " declaration", sym->name, where);
12228       return FAILURE;
12229     }
12230
12231   has_pointer = sym->attr.pointer;
12232
12233   for (ref = e->ref; ref; ref = ref->next)
12234     {
12235       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
12236         has_pointer = 1;
12237
12238       if (ref->type == REF_ARRAY && ref->u.ar.codimen)
12239         {
12240           gfc_error ("DATA element '%s' at %L cannot have a coindex",
12241                      sym->name, where);
12242           return FAILURE;
12243         }
12244
12245       if (has_pointer
12246             && ref->type == REF_ARRAY
12247             && ref->u.ar.type != AR_FULL)
12248           {
12249             gfc_error ("DATA element '%s' at %L is a pointer and so must "
12250                         "be a full array", sym->name, where);
12251             return FAILURE;
12252           }
12253     }
12254
12255   if (e->rank == 0 || has_pointer)
12256     {
12257       mpz_init_set_ui (size, 1);
12258       ref = NULL;
12259     }
12260   else
12261     {
12262       ref = e->ref;
12263
12264       /* Find the array section reference.  */
12265       for (ref = e->ref; ref; ref = ref->next)
12266         {
12267           if (ref->type != REF_ARRAY)
12268             continue;
12269           if (ref->u.ar.type == AR_ELEMENT)
12270             continue;
12271           break;
12272         }
12273       gcc_assert (ref);
12274
12275       /* Set marks according to the reference pattern.  */
12276       switch (ref->u.ar.type)
12277         {
12278         case AR_FULL:
12279           mark = AR_FULL;
12280           break;
12281
12282         case AR_SECTION:
12283           ar = &ref->u.ar;
12284           /* Get the start position of array section.  */
12285           gfc_get_section_index (ar, section_index, &offset);
12286           mark = AR_SECTION;
12287           break;
12288
12289         default:
12290           gcc_unreachable ();
12291         }
12292
12293       if (gfc_array_size (e, &size) == FAILURE)
12294         {
12295           gfc_error ("Nonconstant array section at %L in DATA statement",
12296                      &e->where);
12297           mpz_clear (offset);
12298           return FAILURE;
12299         }
12300     }
12301
12302   t = SUCCESS;
12303
12304   while (mpz_cmp_ui (size, 0) > 0)
12305     {
12306       if (next_data_value () == FAILURE)
12307         {
12308           gfc_error ("DATA statement at %L has more variables than values",
12309                      where);
12310           t = FAILURE;
12311           break;
12312         }
12313
12314       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
12315       if (t == FAILURE)
12316         break;
12317
12318       /* If we have more than one element left in the repeat count,
12319          and we have more than one element left in the target variable,
12320          then create a range assignment.  */
12321       /* FIXME: Only done for full arrays for now, since array sections
12322          seem tricky.  */
12323       if (mark == AR_FULL && ref && ref->next == NULL
12324           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
12325         {
12326           mpz_t range;
12327
12328           if (mpz_cmp (size, values.left) >= 0)
12329             {
12330               mpz_init_set (range, values.left);
12331               mpz_sub (size, size, values.left);
12332               mpz_set_ui (values.left, 0);
12333             }
12334           else
12335             {
12336               mpz_init_set (range, size);
12337               mpz_sub (values.left, values.left, size);
12338               mpz_set_ui (size, 0);
12339             }
12340
12341           t = gfc_assign_data_value_range (var->expr, values.vnode->expr,
12342                                            offset, range);
12343
12344           mpz_add (offset, offset, range);
12345           mpz_clear (range);
12346
12347           if (t == FAILURE)
12348             break;
12349         }
12350
12351       /* Assign initial value to symbol.  */
12352       else
12353         {
12354           mpz_sub_ui (values.left, values.left, 1);
12355           mpz_sub_ui (size, size, 1);
12356
12357           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
12358           if (t == FAILURE)
12359             break;
12360
12361           if (mark == AR_FULL)
12362             mpz_add_ui (offset, offset, 1);
12363
12364           /* Modify the array section indexes and recalculate the offset
12365              for next element.  */
12366           else if (mark == AR_SECTION)
12367             gfc_advance_section (section_index, ar, &offset);
12368         }
12369     }
12370
12371   if (mark == AR_SECTION)
12372     {
12373       for (i = 0; i < ar->dimen; i++)
12374         mpz_clear (section_index[i]);
12375     }
12376
12377   mpz_clear (size);
12378   mpz_clear (offset);
12379
12380   return t;
12381 }
12382
12383
12384 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
12385
12386 /* Iterate over a list of elements in a DATA statement.  */
12387
12388 static gfc_try
12389 traverse_data_list (gfc_data_variable *var, locus *where)
12390 {
12391   mpz_t trip;
12392   iterator_stack frame;
12393   gfc_expr *e, *start, *end, *step;
12394   gfc_try retval = SUCCESS;
12395
12396   mpz_init (frame.value);
12397   mpz_init (trip);
12398
12399   start = gfc_copy_expr (var->iter.start);
12400   end = gfc_copy_expr (var->iter.end);
12401   step = gfc_copy_expr (var->iter.step);
12402
12403   if (gfc_simplify_expr (start, 1) == FAILURE
12404       || start->expr_type != EXPR_CONSTANT)
12405     {
12406       gfc_error ("start of implied-do loop at %L could not be "
12407                  "simplified to a constant value", &start->where);
12408       retval = FAILURE;
12409       goto cleanup;
12410     }
12411   if (gfc_simplify_expr (end, 1) == FAILURE
12412       || end->expr_type != EXPR_CONSTANT)
12413     {
12414       gfc_error ("end of implied-do loop at %L could not be "
12415                  "simplified to a constant value", &start->where);
12416       retval = FAILURE;
12417       goto cleanup;
12418     }
12419   if (gfc_simplify_expr (step, 1) == FAILURE
12420       || step->expr_type != EXPR_CONSTANT)
12421     {
12422       gfc_error ("step of implied-do loop at %L could not be "
12423                  "simplified to a constant value", &start->where);
12424       retval = FAILURE;
12425       goto cleanup;
12426     }
12427
12428   mpz_set (trip, end->value.integer);
12429   mpz_sub (trip, trip, start->value.integer);
12430   mpz_add (trip, trip, step->value.integer);
12431
12432   mpz_div (trip, trip, step->value.integer);
12433
12434   mpz_set (frame.value, start->value.integer);
12435
12436   frame.prev = iter_stack;
12437   frame.variable = var->iter.var->symtree;
12438   iter_stack = &frame;
12439
12440   while (mpz_cmp_ui (trip, 0) > 0)
12441     {
12442       if (traverse_data_var (var->list, where) == FAILURE)
12443         {
12444           retval = FAILURE;
12445           goto cleanup;
12446         }
12447
12448       e = gfc_copy_expr (var->expr);
12449       if (gfc_simplify_expr (e, 1) == FAILURE)
12450         {
12451           gfc_free_expr (e);
12452           retval = FAILURE;
12453           goto cleanup;
12454         }
12455
12456       mpz_add (frame.value, frame.value, step->value.integer);
12457
12458       mpz_sub_ui (trip, trip, 1);
12459     }
12460
12461 cleanup:
12462   mpz_clear (frame.value);
12463   mpz_clear (trip);
12464
12465   gfc_free_expr (start);
12466   gfc_free_expr (end);
12467   gfc_free_expr (step);
12468
12469   iter_stack = frame.prev;
12470   return retval;
12471 }
12472
12473
12474 /* Type resolve variables in the variable list of a DATA statement.  */
12475
12476 static gfc_try
12477 traverse_data_var (gfc_data_variable *var, locus *where)
12478 {
12479   gfc_try t;
12480
12481   for (; var; var = var->next)
12482     {
12483       if (var->expr == NULL)
12484         t = traverse_data_list (var, where);
12485       else
12486         t = check_data_variable (var, where);
12487
12488       if (t == FAILURE)
12489         return FAILURE;
12490     }
12491
12492   return SUCCESS;
12493 }
12494
12495
12496 /* Resolve the expressions and iterators associated with a data statement.
12497    This is separate from the assignment checking because data lists should
12498    only be resolved once.  */
12499
12500 static gfc_try
12501 resolve_data_variables (gfc_data_variable *d)
12502 {
12503   for (; d; d = d->next)
12504     {
12505       if (d->list == NULL)
12506         {
12507           if (gfc_resolve_expr (d->expr) == FAILURE)
12508             return FAILURE;
12509         }
12510       else
12511         {
12512           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
12513             return FAILURE;
12514
12515           if (resolve_data_variables (d->list) == FAILURE)
12516             return FAILURE;
12517         }
12518     }
12519
12520   return SUCCESS;
12521 }
12522
12523
12524 /* Resolve a single DATA statement.  We implement this by storing a pointer to
12525    the value list into static variables, and then recursively traversing the
12526    variables list, expanding iterators and such.  */
12527
12528 static void
12529 resolve_data (gfc_data *d)
12530 {
12531
12532   if (resolve_data_variables (d->var) == FAILURE)
12533     return;
12534
12535   values.vnode = d->value;
12536   if (d->value == NULL)
12537     mpz_set_ui (values.left, 0);
12538   else
12539     mpz_set (values.left, d->value->repeat);
12540
12541   if (traverse_data_var (d->var, &d->where) == FAILURE)
12542     return;
12543
12544   /* At this point, we better not have any values left.  */
12545
12546   if (next_data_value () == SUCCESS)
12547     gfc_error ("DATA statement at %L has more values than variables",
12548                &d->where);
12549 }
12550
12551
12552 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
12553    accessed by host or use association, is a dummy argument to a pure function,
12554    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
12555    is storage associated with any such variable, shall not be used in the
12556    following contexts: (clients of this function).  */
12557
12558 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
12559    procedure.  Returns zero if assignment is OK, nonzero if there is a
12560    problem.  */
12561 int
12562 gfc_impure_variable (gfc_symbol *sym)
12563 {
12564   gfc_symbol *proc;
12565   gfc_namespace *ns;
12566
12567   if (sym->attr.use_assoc || sym->attr.in_common)
12568     return 1;
12569
12570   /* Check if the symbol's ns is inside the pure procedure.  */
12571   for (ns = gfc_current_ns; ns; ns = ns->parent)
12572     {
12573       if (ns == sym->ns)
12574         break;
12575       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
12576         return 1;
12577     }
12578
12579   proc = sym->ns->proc_name;
12580   if (sym->attr.dummy && gfc_pure (proc)
12581         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
12582                 ||
12583              proc->attr.function))
12584     return 1;
12585
12586   /* TODO: Sort out what can be storage associated, if anything, and include
12587      it here.  In principle equivalences should be scanned but it does not
12588      seem to be possible to storage associate an impure variable this way.  */
12589   return 0;
12590 }
12591
12592
12593 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
12594    current namespace is inside a pure procedure.  */
12595
12596 int
12597 gfc_pure (gfc_symbol *sym)
12598 {
12599   symbol_attribute attr;
12600   gfc_namespace *ns;
12601
12602   if (sym == NULL)
12603     {
12604       /* Check if the current namespace or one of its parents
12605         belongs to a pure procedure.  */
12606       for (ns = gfc_current_ns; ns; ns = ns->parent)
12607         {
12608           sym = ns->proc_name;
12609           if (sym == NULL)
12610             return 0;
12611           attr = sym->attr;
12612           if (attr.flavor == FL_PROCEDURE && attr.pure)
12613             return 1;
12614         }
12615       return 0;
12616     }
12617
12618   attr = sym->attr;
12619
12620   return attr.flavor == FL_PROCEDURE && attr.pure;
12621 }
12622
12623
12624 /* Test whether the current procedure is elemental or not.  */
12625
12626 int
12627 gfc_elemental (gfc_symbol *sym)
12628 {
12629   symbol_attribute attr;
12630
12631   if (sym == NULL)
12632     sym = gfc_current_ns->proc_name;
12633   if (sym == NULL)
12634     return 0;
12635   attr = sym->attr;
12636
12637   return attr.flavor == FL_PROCEDURE && attr.elemental;
12638 }
12639
12640
12641 /* Warn about unused labels.  */
12642
12643 static void
12644 warn_unused_fortran_label (gfc_st_label *label)
12645 {
12646   if (label == NULL)
12647     return;
12648
12649   warn_unused_fortran_label (label->left);
12650
12651   if (label->defined == ST_LABEL_UNKNOWN)
12652     return;
12653
12654   switch (label->referenced)
12655     {
12656     case ST_LABEL_UNKNOWN:
12657       gfc_warning ("Label %d at %L defined but not used", label->value,
12658                    &label->where);
12659       break;
12660
12661     case ST_LABEL_BAD_TARGET:
12662       gfc_warning ("Label %d at %L defined but cannot be used",
12663                    label->value, &label->where);
12664       break;
12665
12666     default:
12667       break;
12668     }
12669
12670   warn_unused_fortran_label (label->right);
12671 }
12672
12673
12674 /* Returns the sequence type of a symbol or sequence.  */
12675
12676 static seq_type
12677 sequence_type (gfc_typespec ts)
12678 {
12679   seq_type result;
12680   gfc_component *c;
12681
12682   switch (ts.type)
12683   {
12684     case BT_DERIVED:
12685
12686       if (ts.u.derived->components == NULL)
12687         return SEQ_NONDEFAULT;
12688
12689       result = sequence_type (ts.u.derived->components->ts);
12690       for (c = ts.u.derived->components->next; c; c = c->next)
12691         if (sequence_type (c->ts) != result)
12692           return SEQ_MIXED;
12693
12694       return result;
12695
12696     case BT_CHARACTER:
12697       if (ts.kind != gfc_default_character_kind)
12698           return SEQ_NONDEFAULT;
12699
12700       return SEQ_CHARACTER;
12701
12702     case BT_INTEGER:
12703       if (ts.kind != gfc_default_integer_kind)
12704           return SEQ_NONDEFAULT;
12705
12706       return SEQ_NUMERIC;
12707
12708     case BT_REAL:
12709       if (!(ts.kind == gfc_default_real_kind
12710             || ts.kind == gfc_default_double_kind))
12711           return SEQ_NONDEFAULT;
12712
12713       return SEQ_NUMERIC;
12714
12715     case BT_COMPLEX:
12716       if (ts.kind != gfc_default_complex_kind)
12717           return SEQ_NONDEFAULT;
12718
12719       return SEQ_NUMERIC;
12720
12721     case BT_LOGICAL:
12722       if (ts.kind != gfc_default_logical_kind)
12723           return SEQ_NONDEFAULT;
12724
12725       return SEQ_NUMERIC;
12726
12727     default:
12728       return SEQ_NONDEFAULT;
12729   }
12730 }
12731
12732
12733 /* Resolve derived type EQUIVALENCE object.  */
12734
12735 static gfc_try
12736 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
12737 {
12738   gfc_component *c = derived->components;
12739
12740   if (!derived)
12741     return SUCCESS;
12742
12743   /* Shall not be an object of nonsequence derived type.  */
12744   if (!derived->attr.sequence)
12745     {
12746       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
12747                  "attribute to be an EQUIVALENCE object", sym->name,
12748                  &e->where);
12749       return FAILURE;
12750     }
12751
12752   /* Shall not have allocatable components.  */
12753   if (derived->attr.alloc_comp)
12754     {
12755       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
12756                  "components to be an EQUIVALENCE object",sym->name,
12757                  &e->where);
12758       return FAILURE;
12759     }
12760
12761   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
12762     {
12763       gfc_error ("Derived type variable '%s' at %L with default "
12764                  "initialization cannot be in EQUIVALENCE with a variable "
12765                  "in COMMON", sym->name, &e->where);
12766       return FAILURE;
12767     }
12768
12769   for (; c ; c = c->next)
12770     {
12771       if (c->ts.type == BT_DERIVED
12772           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
12773         return FAILURE;
12774
12775       /* Shall not be an object of sequence derived type containing a pointer
12776          in the structure.  */
12777       if (c->attr.pointer)
12778         {
12779           gfc_error ("Derived type variable '%s' at %L with pointer "
12780                      "component(s) cannot be an EQUIVALENCE object",
12781                      sym->name, &e->where);
12782           return FAILURE;
12783         }
12784     }
12785   return SUCCESS;
12786 }
12787
12788
12789 /* Resolve equivalence object. 
12790    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
12791    an allocatable array, an object of nonsequence derived type, an object of
12792    sequence derived type containing a pointer at any level of component
12793    selection, an automatic object, a function name, an entry name, a result
12794    name, a named constant, a structure component, or a subobject of any of
12795    the preceding objects.  A substring shall not have length zero.  A
12796    derived type shall not have components with default initialization nor
12797    shall two objects of an equivalence group be initialized.
12798    Either all or none of the objects shall have an protected attribute.
12799    The simple constraints are done in symbol.c(check_conflict) and the rest
12800    are implemented here.  */
12801
12802 static void
12803 resolve_equivalence (gfc_equiv *eq)
12804 {
12805   gfc_symbol *sym;
12806   gfc_symbol *first_sym;
12807   gfc_expr *e;
12808   gfc_ref *r;
12809   locus *last_where = NULL;
12810   seq_type eq_type, last_eq_type;
12811   gfc_typespec *last_ts;
12812   int object, cnt_protected;
12813   const char *msg;
12814
12815   last_ts = &eq->expr->symtree->n.sym->ts;
12816
12817   first_sym = eq->expr->symtree->n.sym;
12818
12819   cnt_protected = 0;
12820
12821   for (object = 1; eq; eq = eq->eq, object++)
12822     {
12823       e = eq->expr;
12824
12825       e->ts = e->symtree->n.sym->ts;
12826       /* match_varspec might not know yet if it is seeing
12827          array reference or substring reference, as it doesn't
12828          know the types.  */
12829       if (e->ref && e->ref->type == REF_ARRAY)
12830         {
12831           gfc_ref *ref = e->ref;
12832           sym = e->symtree->n.sym;
12833
12834           if (sym->attr.dimension)
12835             {
12836               ref->u.ar.as = sym->as;
12837               ref = ref->next;
12838             }
12839
12840           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
12841           if (e->ts.type == BT_CHARACTER
12842               && ref
12843               && ref->type == REF_ARRAY
12844               && ref->u.ar.dimen == 1
12845               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
12846               && ref->u.ar.stride[0] == NULL)
12847             {
12848               gfc_expr *start = ref->u.ar.start[0];
12849               gfc_expr *end = ref->u.ar.end[0];
12850               void *mem = NULL;
12851
12852               /* Optimize away the (:) reference.  */
12853               if (start == NULL && end == NULL)
12854                 {
12855                   if (e->ref == ref)
12856                     e->ref = ref->next;
12857                   else
12858                     e->ref->next = ref->next;
12859                   mem = ref;
12860                 }
12861               else
12862                 {
12863                   ref->type = REF_SUBSTRING;
12864                   if (start == NULL)
12865                     start = gfc_get_int_expr (gfc_default_integer_kind,
12866                                               NULL, 1);
12867                   ref->u.ss.start = start;
12868                   if (end == NULL && e->ts.u.cl)
12869                     end = gfc_copy_expr (e->ts.u.cl->length);
12870                   ref->u.ss.end = end;
12871                   ref->u.ss.length = e->ts.u.cl;
12872                   e->ts.u.cl = NULL;
12873                 }
12874               ref = ref->next;
12875               gfc_free (mem);
12876             }
12877
12878           /* Any further ref is an error.  */
12879           if (ref)
12880             {
12881               gcc_assert (ref->type == REF_ARRAY);
12882               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
12883                          &ref->u.ar.where);
12884               continue;
12885             }
12886         }
12887
12888       if (gfc_resolve_expr (e) == FAILURE)
12889         continue;
12890
12891       sym = e->symtree->n.sym;
12892
12893       if (sym->attr.is_protected)
12894         cnt_protected++;
12895       if (cnt_protected > 0 && cnt_protected != object)
12896         {
12897               gfc_error ("Either all or none of the objects in the "
12898                          "EQUIVALENCE set at %L shall have the "
12899                          "PROTECTED attribute",
12900                          &e->where);
12901               break;
12902         }
12903
12904       /* Shall not equivalence common block variables in a PURE procedure.  */
12905       if (sym->ns->proc_name
12906           && sym->ns->proc_name->attr.pure
12907           && sym->attr.in_common)
12908         {
12909           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
12910                      "object in the pure procedure '%s'",
12911                      sym->name, &e->where, sym->ns->proc_name->name);
12912           break;
12913         }
12914
12915       /* Shall not be a named constant.  */
12916       if (e->expr_type == EXPR_CONSTANT)
12917         {
12918           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
12919                      "object", sym->name, &e->where);
12920           continue;
12921         }
12922
12923       if (e->ts.type == BT_DERIVED
12924           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
12925         continue;
12926
12927       /* Check that the types correspond correctly:
12928          Note 5.28:
12929          A numeric sequence structure may be equivalenced to another sequence
12930          structure, an object of default integer type, default real type, double
12931          precision real type, default logical type such that components of the
12932          structure ultimately only become associated to objects of the same
12933          kind. A character sequence structure may be equivalenced to an object
12934          of default character kind or another character sequence structure.
12935          Other objects may be equivalenced only to objects of the same type and
12936          kind parameters.  */
12937
12938       /* Identical types are unconditionally OK.  */
12939       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
12940         goto identical_types;
12941
12942       last_eq_type = sequence_type (*last_ts);
12943       eq_type = sequence_type (sym->ts);
12944
12945       /* Since the pair of objects is not of the same type, mixed or
12946          non-default sequences can be rejected.  */
12947
12948       msg = "Sequence %s with mixed components in EQUIVALENCE "
12949             "statement at %L with different type objects";
12950       if ((object ==2
12951            && last_eq_type == SEQ_MIXED
12952            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
12953               == FAILURE)
12954           || (eq_type == SEQ_MIXED
12955               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12956                                  &e->where) == FAILURE))
12957         continue;
12958
12959       msg = "Non-default type object or sequence %s in EQUIVALENCE "
12960             "statement at %L with objects of different type";
12961       if ((object ==2
12962            && last_eq_type == SEQ_NONDEFAULT
12963            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
12964                               last_where) == FAILURE)
12965           || (eq_type == SEQ_NONDEFAULT
12966               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12967                                  &e->where) == FAILURE))
12968         continue;
12969
12970       msg ="Non-CHARACTER object '%s' in default CHARACTER "
12971            "EQUIVALENCE statement at %L";
12972       if (last_eq_type == SEQ_CHARACTER
12973           && eq_type != SEQ_CHARACTER
12974           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12975                              &e->where) == FAILURE)
12976                 continue;
12977
12978       msg ="Non-NUMERIC object '%s' in default NUMERIC "
12979            "EQUIVALENCE statement at %L";
12980       if (last_eq_type == SEQ_NUMERIC
12981           && eq_type != SEQ_NUMERIC
12982           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12983                              &e->where) == FAILURE)
12984                 continue;
12985
12986   identical_types:
12987       last_ts =&sym->ts;
12988       last_where = &e->where;
12989
12990       if (!e->ref)
12991         continue;
12992
12993       /* Shall not be an automatic array.  */
12994       if (e->ref->type == REF_ARRAY
12995           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
12996         {
12997           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
12998                      "an EQUIVALENCE object", sym->name, &e->where);
12999           continue;
13000         }
13001
13002       r = e->ref;
13003       while (r)
13004         {
13005           /* Shall not be a structure component.  */
13006           if (r->type == REF_COMPONENT)
13007             {
13008               gfc_error ("Structure component '%s' at %L cannot be an "
13009                          "EQUIVALENCE object",
13010                          r->u.c.component->name, &e->where);
13011               break;
13012             }
13013
13014           /* A substring shall not have length zero.  */
13015           if (r->type == REF_SUBSTRING)
13016             {
13017               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
13018                 {
13019                   gfc_error ("Substring at %L has length zero",
13020                              &r->u.ss.start->where);
13021                   break;
13022                 }
13023             }
13024           r = r->next;
13025         }
13026     }
13027 }
13028
13029
13030 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
13031
13032 static void
13033 resolve_fntype (gfc_namespace *ns)
13034 {
13035   gfc_entry_list *el;
13036   gfc_symbol *sym;
13037
13038   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
13039     return;
13040
13041   /* If there are any entries, ns->proc_name is the entry master
13042      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
13043   if (ns->entries)
13044     sym = ns->entries->sym;
13045   else
13046     sym = ns->proc_name;
13047   if (sym->result == sym
13048       && sym->ts.type == BT_UNKNOWN
13049       && gfc_set_default_type (sym, 0, NULL) == FAILURE
13050       && !sym->attr.untyped)
13051     {
13052       gfc_error ("Function '%s' at %L has no IMPLICIT type",
13053                  sym->name, &sym->declared_at);
13054       sym->attr.untyped = 1;
13055     }
13056
13057   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
13058       && !sym->attr.contained
13059       && !gfc_check_access (sym->ts.u.derived->attr.access,
13060                             sym->ts.u.derived->ns->default_access)
13061       && gfc_check_access (sym->attr.access, sym->ns->default_access))
13062     {
13063       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
13064                       "%L of PRIVATE type '%s'", sym->name,
13065                       &sym->declared_at, sym->ts.u.derived->name);
13066     }
13067
13068     if (ns->entries)
13069     for (el = ns->entries->next; el; el = el->next)
13070       {
13071         if (el->sym->result == el->sym
13072             && el->sym->ts.type == BT_UNKNOWN
13073             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
13074             && !el->sym->attr.untyped)
13075           {
13076             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
13077                        el->sym->name, &el->sym->declared_at);
13078             el->sym->attr.untyped = 1;
13079           }
13080       }
13081 }
13082
13083
13084 /* 12.3.2.1.1 Defined operators.  */
13085
13086 static gfc_try
13087 check_uop_procedure (gfc_symbol *sym, locus where)
13088 {
13089   gfc_formal_arglist *formal;
13090
13091   if (!sym->attr.function)
13092     {
13093       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
13094                  sym->name, &where);
13095       return FAILURE;
13096     }
13097
13098   if (sym->ts.type == BT_CHARACTER
13099       && !(sym->ts.u.cl && sym->ts.u.cl->length)
13100       && !(sym->result && sym->result->ts.u.cl
13101            && sym->result->ts.u.cl->length))
13102     {
13103       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
13104                  "character length", sym->name, &where);
13105       return FAILURE;
13106     }
13107
13108   formal = sym->formal;
13109   if (!formal || !formal->sym)
13110     {
13111       gfc_error ("User operator procedure '%s' at %L must have at least "
13112                  "one argument", sym->name, &where);
13113       return FAILURE;
13114     }
13115
13116   if (formal->sym->attr.intent != INTENT_IN)
13117     {
13118       gfc_error ("First argument of operator interface at %L must be "
13119                  "INTENT(IN)", &where);
13120       return FAILURE;
13121     }
13122
13123   if (formal->sym->attr.optional)
13124     {
13125       gfc_error ("First argument of operator interface at %L cannot be "
13126                  "optional", &where);
13127       return FAILURE;
13128     }
13129
13130   formal = formal->next;
13131   if (!formal || !formal->sym)
13132     return SUCCESS;
13133
13134   if (formal->sym->attr.intent != INTENT_IN)
13135     {
13136       gfc_error ("Second argument of operator interface at %L must be "
13137                  "INTENT(IN)", &where);
13138       return FAILURE;
13139     }
13140
13141   if (formal->sym->attr.optional)
13142     {
13143       gfc_error ("Second argument of operator interface at %L cannot be "
13144                  "optional", &where);
13145       return FAILURE;
13146     }
13147
13148   if (formal->next)
13149     {
13150       gfc_error ("Operator interface at %L must have, at most, two "
13151                  "arguments", &where);
13152       return FAILURE;
13153     }
13154
13155   return SUCCESS;
13156 }
13157
13158 static void
13159 gfc_resolve_uops (gfc_symtree *symtree)
13160 {
13161   gfc_interface *itr;
13162
13163   if (symtree == NULL)
13164     return;
13165
13166   gfc_resolve_uops (symtree->left);
13167   gfc_resolve_uops (symtree->right);
13168
13169   for (itr = symtree->n.uop->op; itr; itr = itr->next)
13170     check_uop_procedure (itr->sym, itr->sym->declared_at);
13171 }
13172
13173
13174 /* Examine all of the expressions associated with a program unit,
13175    assign types to all intermediate expressions, make sure that all
13176    assignments are to compatible types and figure out which names
13177    refer to which functions or subroutines.  It doesn't check code
13178    block, which is handled by resolve_code.  */
13179
13180 static void
13181 resolve_types (gfc_namespace *ns)
13182 {
13183   gfc_namespace *n;
13184   gfc_charlen *cl;
13185   gfc_data *d;
13186   gfc_equiv *eq;
13187   gfc_namespace* old_ns = gfc_current_ns;
13188
13189   /* Check that all IMPLICIT types are ok.  */
13190   if (!ns->seen_implicit_none)
13191     {
13192       unsigned letter;
13193       for (letter = 0; letter != GFC_LETTERS; ++letter)
13194         if (ns->set_flag[letter]
13195             && resolve_typespec_used (&ns->default_type[letter],
13196                                       &ns->implicit_loc[letter],
13197                                       NULL) == FAILURE)
13198           return;
13199     }
13200
13201   gfc_current_ns = ns;
13202
13203   resolve_entries (ns);
13204
13205   resolve_common_vars (ns->blank_common.head, false);
13206   resolve_common_blocks (ns->common_root);
13207
13208   resolve_contained_functions (ns);
13209
13210   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
13211
13212   for (cl = ns->cl_list; cl; cl = cl->next)
13213     resolve_charlen (cl);
13214
13215   gfc_traverse_ns (ns, resolve_symbol);
13216
13217   resolve_fntype (ns);
13218
13219   for (n = ns->contained; n; n = n->sibling)
13220     {
13221       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
13222         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
13223                    "also be PURE", n->proc_name->name,
13224                    &n->proc_name->declared_at);
13225
13226       resolve_types (n);
13227     }
13228
13229   forall_flag = 0;
13230   gfc_check_interfaces (ns);
13231
13232   gfc_traverse_ns (ns, resolve_values);
13233
13234   if (ns->save_all)
13235     gfc_save_all (ns);
13236
13237   iter_stack = NULL;
13238   for (d = ns->data; d; d = d->next)
13239     resolve_data (d);
13240
13241   iter_stack = NULL;
13242   gfc_traverse_ns (ns, gfc_formalize_init_value);
13243
13244   gfc_traverse_ns (ns, gfc_verify_binding_labels);
13245
13246   if (ns->common_root != NULL)
13247     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
13248
13249   for (eq = ns->equiv; eq; eq = eq->next)
13250     resolve_equivalence (eq);
13251
13252   /* Warn about unused labels.  */
13253   if (warn_unused_label)
13254     warn_unused_fortran_label (ns->st_labels);
13255
13256   gfc_resolve_uops (ns->uop_root);
13257
13258   gfc_current_ns = old_ns;
13259 }
13260
13261
13262 /* Call resolve_code recursively.  */
13263
13264 static void
13265 resolve_codes (gfc_namespace *ns)
13266 {
13267   gfc_namespace *n;
13268   bitmap_obstack old_obstack;
13269
13270   for (n = ns->contained; n; n = n->sibling)
13271     resolve_codes (n);
13272
13273   gfc_current_ns = ns;
13274
13275   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
13276   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
13277     cs_base = NULL;
13278
13279   /* Set to an out of range value.  */
13280   current_entry_id = -1;
13281
13282   old_obstack = labels_obstack;
13283   bitmap_obstack_initialize (&labels_obstack);
13284
13285   resolve_code (ns->code, ns);
13286
13287   bitmap_obstack_release (&labels_obstack);
13288   labels_obstack = old_obstack;
13289 }
13290
13291
13292 /* This function is called after a complete program unit has been compiled.
13293    Its purpose is to examine all of the expressions associated with a program
13294    unit, assign types to all intermediate expressions, make sure that all
13295    assignments are to compatible types and figure out which names refer to
13296    which functions or subroutines.  */
13297
13298 void
13299 gfc_resolve (gfc_namespace *ns)
13300 {
13301   gfc_namespace *old_ns;
13302   code_stack *old_cs_base;
13303
13304   if (ns->resolved)
13305     return;
13306
13307   ns->resolved = -1;
13308   old_ns = gfc_current_ns;
13309   old_cs_base = cs_base;
13310
13311   resolve_types (ns);
13312   resolve_codes (ns);
13313
13314   gfc_current_ns = old_ns;
13315   cs_base = old_cs_base;
13316   ns->resolved = 1;
13317
13318   gfc_run_passes (ns);
13319 }