OSDN Git Service

2010-11-23 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 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       sym->attr.is_bind_c = ifc->attr.is_bind_c;
180       /* Copy array spec.  */
181       sym->as = gfc_copy_array_spec (ifc->as);
182       if (sym->as)
183         {
184           int i;
185           for (i = 0; i < sym->as->rank; i++)
186             {
187               gfc_expr_replace_symbols (sym->as->lower[i], sym);
188               gfc_expr_replace_symbols (sym->as->upper[i], sym);
189             }
190         }
191       /* Copy char length.  */
192       if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
193         {
194           sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
195           gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
196           if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
197               && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
198             return FAILURE;
199         }
200     }
201   else if (sym->ts.interface->name[0] != '\0')
202     {
203       gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
204                  sym->ts.interface->name, sym->name, &sym->declared_at);
205       return FAILURE;
206     }
207
208   return SUCCESS;
209 }
210
211
212 /* Resolve types of formal argument lists.  These have to be done early so that
213    the formal argument lists of module procedures can be copied to the
214    containing module before the individual procedures are resolved
215    individually.  We also resolve argument lists of procedures in interface
216    blocks because they are self-contained scoping units.
217
218    Since a dummy argument cannot be a non-dummy procedure, the only
219    resort left for untyped names are the IMPLICIT types.  */
220
221 static void
222 resolve_formal_arglist (gfc_symbol *proc)
223 {
224   gfc_formal_arglist *f;
225   gfc_symbol *sym;
226   int i;
227
228   if (proc->result != NULL)
229     sym = proc->result;
230   else
231     sym = proc;
232
233   if (gfc_elemental (proc)
234       || sym->attr.pointer || sym->attr.allocatable
235       || (sym->as && sym->as->rank > 0))
236     {
237       proc->attr.always_explicit = 1;
238       sym->attr.always_explicit = 1;
239     }
240
241   formal_arg_flag = 1;
242
243   for (f = proc->formal; f; f = f->next)
244     {
245       sym = f->sym;
246
247       if (sym == NULL)
248         {
249           /* Alternate return placeholder.  */
250           if (gfc_elemental (proc))
251             gfc_error ("Alternate return specifier in elemental subroutine "
252                        "'%s' at %L is not allowed", proc->name,
253                        &proc->declared_at);
254           if (proc->attr.function)
255             gfc_error ("Alternate return specifier in function "
256                        "'%s' at %L is not allowed", proc->name,
257                        &proc->declared_at);
258           continue;
259         }
260       else if (sym->attr.procedure && sym->ts.interface
261                && sym->attr.if_source != IFSRC_DECL)
262         resolve_procedure_interface (sym);
263
264       if (sym->attr.if_source != IFSRC_UNKNOWN)
265         resolve_formal_arglist (sym);
266
267       if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
268         {
269           if (gfc_pure (proc) && !gfc_pure (sym))
270             {
271               gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
272                          "also be PURE", sym->name, &sym->declared_at);
273               continue;
274             }
275
276           if (gfc_elemental (proc))
277             {
278               gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
279                          "procedure", &sym->declared_at);
280               continue;
281             }
282
283           if (sym->attr.function
284                 && sym->ts.type == BT_UNKNOWN
285                 && sym->attr.intrinsic)
286             {
287               gfc_intrinsic_sym *isym;
288               isym = gfc_find_function (sym->name);
289               if (isym == NULL || !isym->specific)
290                 {
291                   gfc_error ("Unable to find a specific INTRINSIC procedure "
292                              "for the reference '%s' at %L", sym->name,
293                              &sym->declared_at);
294                 }
295               sym->ts = isym->ts;
296             }
297
298           continue;
299         }
300
301       if (sym->ts.type == BT_UNKNOWN && !proc->attr.intrinsic
302           && (!sym->attr.function || sym->result == sym))
303         gfc_set_default_type (sym, 1, sym->ns);
304
305       gfc_resolve_array_spec (sym->as, 0);
306
307       /* We can't tell if an array with dimension (:) is assumed or deferred
308          shape until we know if it has the pointer or allocatable attributes.
309       */
310       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
311           && !(sym->attr.pointer || sym->attr.allocatable))
312         {
313           sym->as->type = AS_ASSUMED_SHAPE;
314           for (i = 0; i < sym->as->rank; i++)
315             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
316                                                   NULL, 1);
317         }
318
319       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
320           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
321           || sym->attr.optional)
322         {
323           proc->attr.always_explicit = 1;
324           if (proc->result)
325             proc->result->attr.always_explicit = 1;
326         }
327
328       /* If the flavor is unknown at this point, it has to be a variable.
329          A procedure specification would have already set the type.  */
330
331       if (sym->attr.flavor == FL_UNKNOWN)
332         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
333
334       if (gfc_pure (proc) && !sym->attr.pointer
335           && sym->attr.flavor != FL_PROCEDURE)
336         {
337           if (proc->attr.function && sym->attr.intent != INTENT_IN)
338             gfc_error ("Argument '%s' of pure function '%s' at %L must be "
339                        "INTENT(IN)", sym->name, proc->name,
340                        &sym->declared_at);
341
342           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
343             gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
344                        "have its INTENT specified", sym->name, proc->name,
345                        &sym->declared_at);
346         }
347
348       if (gfc_elemental (proc))
349         {
350           /* F2008, C1289.  */
351           if (sym->attr.codimension)
352             {
353               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
354                          "procedure", sym->name, &sym->declared_at);
355               continue;
356             }
357
358           if (sym->as != NULL)
359             {
360               gfc_error ("Argument '%s' of elemental procedure at %L must "
361                          "be scalar", sym->name, &sym->declared_at);
362               continue;
363             }
364
365           if (sym->attr.allocatable)
366             {
367               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
368                          "have the ALLOCATABLE attribute", sym->name,
369                          &sym->declared_at);
370               continue;
371             }
372
373           if (sym->attr.pointer)
374             {
375               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
376                          "have the POINTER attribute", sym->name,
377                          &sym->declared_at);
378               continue;
379             }
380
381           if (sym->attr.flavor == FL_PROCEDURE)
382             {
383               gfc_error ("Dummy procedure '%s' not allowed in elemental "
384                          "procedure '%s' at %L", sym->name, proc->name,
385                          &sym->declared_at);
386               continue;
387             }
388
389           if (sym->attr.intent == INTENT_UNKNOWN)
390             {
391               gfc_error ("Argument '%s' of elemental procedure '%s' at %L must "
392                          "have its INTENT specified", sym->name, proc->name,
393                          &sym->declared_at);
394               continue;
395             }
396         }
397
398       /* Each dummy shall be specified to be scalar.  */
399       if (proc->attr.proc == PROC_ST_FUNCTION)
400         {
401           if (sym->as != NULL)
402             {
403               gfc_error ("Argument '%s' of statement function at %L must "
404                          "be scalar", sym->name, &sym->declared_at);
405               continue;
406             }
407
408           if (sym->ts.type == BT_CHARACTER)
409             {
410               gfc_charlen *cl = sym->ts.u.cl;
411               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
412                 {
413                   gfc_error ("Character-valued argument '%s' of statement "
414                              "function at %L must have constant length",
415                              sym->name, &sym->declared_at);
416                   continue;
417                 }
418             }
419         }
420     }
421   formal_arg_flag = 0;
422 }
423
424
425 /* Work function called when searching for symbols that have argument lists
426    associated with them.  */
427
428 static void
429 find_arglists (gfc_symbol *sym)
430 {
431   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
432     return;
433
434   resolve_formal_arglist (sym);
435 }
436
437
438 /* Given a namespace, resolve all formal argument lists within the namespace.
439  */
440
441 static void
442 resolve_formal_arglists (gfc_namespace *ns)
443 {
444   if (ns == NULL)
445     return;
446
447   gfc_traverse_ns (ns, find_arglists);
448 }
449
450
451 static void
452 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
453 {
454   gfc_try t;
455
456   /* If this namespace is not a function or an entry master function,
457      ignore it.  */
458   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
459       || sym->attr.entry_master)
460     return;
461
462   /* Try to find out of what the return type is.  */
463   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
464     {
465       t = gfc_set_default_type (sym->result, 0, ns);
466
467       if (t == FAILURE && !sym->result->attr.untyped)
468         {
469           if (sym->result == sym)
470             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
471                        sym->name, &sym->declared_at);
472           else if (!sym->result->attr.proc_pointer)
473             gfc_error ("Result '%s' of contained function '%s' at %L has "
474                        "no IMPLICIT type", sym->result->name, sym->name,
475                        &sym->result->declared_at);
476           sym->result->attr.untyped = 1;
477         }
478     }
479
480   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
481      type, lists the only ways a character length value of * can be used:
482      dummy arguments of procedures, named constants, and function results
483      in external functions.  Internal function results and results of module
484      procedures are not on this list, ergo, not permitted.  */
485
486   if (sym->result->ts.type == BT_CHARACTER)
487     {
488       gfc_charlen *cl = sym->result->ts.u.cl;
489       if (!cl || !cl->length)
490         {
491           /* See if this is a module-procedure and adapt error message
492              accordingly.  */
493           bool module_proc;
494           gcc_assert (ns->parent && ns->parent->proc_name);
495           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
496
497           gfc_error ("Character-valued %s '%s' at %L must not be"
498                      " assumed length",
499                      module_proc ? _("module procedure")
500                                  : _("internal function"),
501                      sym->name, &sym->declared_at);
502         }
503     }
504 }
505
506
507 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
508    introduce duplicates.  */
509
510 static void
511 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
512 {
513   gfc_formal_arglist *f, *new_arglist;
514   gfc_symbol *new_sym;
515
516   for (; new_args != NULL; new_args = new_args->next)
517     {
518       new_sym = new_args->sym;
519       /* See if this arg is already in the formal argument list.  */
520       for (f = proc->formal; f; f = f->next)
521         {
522           if (new_sym == f->sym)
523             break;
524         }
525
526       if (f)
527         continue;
528
529       /* Add a new argument.  Argument order is not important.  */
530       new_arglist = gfc_get_formal_arglist ();
531       new_arglist->sym = new_sym;
532       new_arglist->next = proc->formal;
533       proc->formal  = new_arglist;
534     }
535 }
536
537
538 /* Flag the arguments that are not present in all entries.  */
539
540 static void
541 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
542 {
543   gfc_formal_arglist *f, *head;
544   head = new_args;
545
546   for (f = proc->formal; f; f = f->next)
547     {
548       if (f->sym == NULL)
549         continue;
550
551       for (new_args = head; new_args; new_args = new_args->next)
552         {
553           if (new_args->sym == f->sym)
554             break;
555         }
556
557       if (new_args)
558         continue;
559
560       f->sym->attr.not_always_present = 1;
561     }
562 }
563
564
565 /* Resolve alternate entry points.  If a symbol has multiple entry points we
566    create a new master symbol for the main routine, and turn the existing
567    symbol into an entry point.  */
568
569 static void
570 resolve_entries (gfc_namespace *ns)
571 {
572   gfc_namespace *old_ns;
573   gfc_code *c;
574   gfc_symbol *proc;
575   gfc_entry_list *el;
576   char name[GFC_MAX_SYMBOL_LEN + 1];
577   static int master_count = 0;
578
579   if (ns->proc_name == NULL)
580     return;
581
582   /* No need to do anything if this procedure doesn't have alternate entry
583      points.  */
584   if (!ns->entries)
585     return;
586
587   /* We may already have resolved alternate entry points.  */
588   if (ns->proc_name->attr.entry_master)
589     return;
590
591   /* If this isn't a procedure something has gone horribly wrong.  */
592   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
593
594   /* Remember the current namespace.  */
595   old_ns = gfc_current_ns;
596
597   gfc_current_ns = ns;
598
599   /* Add the main entry point to the list of entry points.  */
600   el = gfc_get_entry_list ();
601   el->sym = ns->proc_name;
602   el->id = 0;
603   el->next = ns->entries;
604   ns->entries = el;
605   ns->proc_name->attr.entry = 1;
606
607   /* If it is a module function, it needs to be in the right namespace
608      so that gfc_get_fake_result_decl can gather up the results. The
609      need for this arose in get_proc_name, where these beasts were
610      left in their own namespace, to keep prior references linked to
611      the entry declaration.*/
612   if (ns->proc_name->attr.function
613       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
614     el->sym->ns = ns;
615
616   /* Do the same for entries where the master is not a module
617      procedure.  These are retained in the module namespace because
618      of the module procedure declaration.  */
619   for (el = el->next; el; el = el->next)
620     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
621           && el->sym->attr.mod_proc)
622       el->sym->ns = ns;
623   el = ns->entries;
624
625   /* Add an entry statement for it.  */
626   c = gfc_get_code ();
627   c->op = EXEC_ENTRY;
628   c->ext.entry = el;
629   c->next = ns->code;
630   ns->code = c;
631
632   /* Create a new symbol for the master function.  */
633   /* Give the internal function a unique name (within this file).
634      Also include the function name so the user has some hope of figuring
635      out what is going on.  */
636   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
637             master_count++, ns->proc_name->name);
638   gfc_get_ha_symbol (name, &proc);
639   gcc_assert (proc != NULL);
640
641   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
642   if (ns->proc_name->attr.subroutine)
643     gfc_add_subroutine (&proc->attr, proc->name, NULL);
644   else
645     {
646       gfc_symbol *sym;
647       gfc_typespec *ts, *fts;
648       gfc_array_spec *as, *fas;
649       gfc_add_function (&proc->attr, proc->name, NULL);
650       proc->result = proc;
651       fas = ns->entries->sym->as;
652       fas = fas ? fas : ns->entries->sym->result->as;
653       fts = &ns->entries->sym->result->ts;
654       if (fts->type == BT_UNKNOWN)
655         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
656       for (el = ns->entries->next; el; el = el->next)
657         {
658           ts = &el->sym->result->ts;
659           as = el->sym->as;
660           as = as ? as : el->sym->result->as;
661           if (ts->type == BT_UNKNOWN)
662             ts = gfc_get_default_type (el->sym->result->name, NULL);
663
664           if (! gfc_compare_types (ts, fts)
665               || (el->sym->result->attr.dimension
666                   != ns->entries->sym->result->attr.dimension)
667               || (el->sym->result->attr.pointer
668                   != ns->entries->sym->result->attr.pointer))
669             break;
670           else if (as && fas && ns->entries->sym->result != el->sym->result
671                       && gfc_compare_array_spec (as, fas) == 0)
672             gfc_error ("Function %s at %L has entries with mismatched "
673                        "array specifications", ns->entries->sym->name,
674                        &ns->entries->sym->declared_at);
675           /* The characteristics need to match and thus both need to have
676              the same string length, i.e. both len=*, or both len=4.
677              Having both len=<variable> is also possible, but difficult to
678              check at compile time.  */
679           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
680                    && (((ts->u.cl->length && !fts->u.cl->length)
681                         ||(!ts->u.cl->length && fts->u.cl->length))
682                        || (ts->u.cl->length
683                            && ts->u.cl->length->expr_type
684                               != fts->u.cl->length->expr_type)
685                        || (ts->u.cl->length
686                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
687                            && mpz_cmp (ts->u.cl->length->value.integer,
688                                        fts->u.cl->length->value.integer) != 0)))
689             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
690                             "entries returning variables of different "
691                             "string lengths", ns->entries->sym->name,
692                             &ns->entries->sym->declared_at);
693         }
694
695       if (el == NULL)
696         {
697           sym = ns->entries->sym->result;
698           /* All result types the same.  */
699           proc->ts = *fts;
700           if (sym->attr.dimension)
701             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
702           if (sym->attr.pointer)
703             gfc_add_pointer (&proc->attr, NULL);
704         }
705       else
706         {
707           /* Otherwise the result will be passed through a union by
708              reference.  */
709           proc->attr.mixed_entry_master = 1;
710           for (el = ns->entries; el; el = el->next)
711             {
712               sym = el->sym->result;
713               if (sym->attr.dimension)
714                 {
715                   if (el == ns->entries)
716                     gfc_error ("FUNCTION result %s can't be an array in "
717                                "FUNCTION %s at %L", sym->name,
718                                ns->entries->sym->name, &sym->declared_at);
719                   else
720                     gfc_error ("ENTRY result %s can't be an array in "
721                                "FUNCTION %s at %L", sym->name,
722                                ns->entries->sym->name, &sym->declared_at);
723                 }
724               else if (sym->attr.pointer)
725                 {
726                   if (el == ns->entries)
727                     gfc_error ("FUNCTION result %s can't be a POINTER in "
728                                "FUNCTION %s at %L", sym->name,
729                                ns->entries->sym->name, &sym->declared_at);
730                   else
731                     gfc_error ("ENTRY result %s can't be a POINTER in "
732                                "FUNCTION %s at %L", sym->name,
733                                ns->entries->sym->name, &sym->declared_at);
734                 }
735               else
736                 {
737                   ts = &sym->ts;
738                   if (ts->type == BT_UNKNOWN)
739                     ts = gfc_get_default_type (sym->name, NULL);
740                   switch (ts->type)
741                     {
742                     case BT_INTEGER:
743                       if (ts->kind == gfc_default_integer_kind)
744                         sym = NULL;
745                       break;
746                     case BT_REAL:
747                       if (ts->kind == gfc_default_real_kind
748                           || ts->kind == gfc_default_double_kind)
749                         sym = NULL;
750                       break;
751                     case BT_COMPLEX:
752                       if (ts->kind == gfc_default_complex_kind)
753                         sym = NULL;
754                       break;
755                     case BT_LOGICAL:
756                       if (ts->kind == gfc_default_logical_kind)
757                         sym = NULL;
758                       break;
759                     case BT_UNKNOWN:
760                       /* We will issue error elsewhere.  */
761                       sym = NULL;
762                       break;
763                     default:
764                       break;
765                     }
766                   if (sym)
767                     {
768                       if (el == ns->entries)
769                         gfc_error ("FUNCTION result %s can't be of type %s "
770                                    "in FUNCTION %s at %L", sym->name,
771                                    gfc_typename (ts), ns->entries->sym->name,
772                                    &sym->declared_at);
773                       else
774                         gfc_error ("ENTRY result %s can't be of type %s "
775                                    "in FUNCTION %s at %L", sym->name,
776                                    gfc_typename (ts), ns->entries->sym->name,
777                                    &sym->declared_at);
778                     }
779                 }
780             }
781         }
782     }
783   proc->attr.access = ACCESS_PRIVATE;
784   proc->attr.entry_master = 1;
785
786   /* Merge all the entry point arguments.  */
787   for (el = ns->entries; el; el = el->next)
788     merge_argument_lists (proc, el->sym->formal);
789
790   /* Check the master formal arguments for any that are not
791      present in all entry points.  */
792   for (el = ns->entries; el; el = el->next)
793     check_argument_lists (proc, el->sym->formal);
794
795   /* Use the master function for the function body.  */
796   ns->proc_name = proc;
797
798   /* Finalize the new symbols.  */
799   gfc_commit_symbols ();
800
801   /* Restore the original namespace.  */
802   gfc_current_ns = old_ns;
803 }
804
805
806 /* Resolve common variables.  */
807 static void
808 resolve_common_vars (gfc_symbol *sym, bool named_common)
809 {
810   gfc_symbol *csym = sym;
811
812   for (; csym; csym = csym->common_next)
813     {
814       if (csym->value || csym->attr.data)
815         {
816           if (!csym->ns->is_block_data)
817             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
818                             "but only in BLOCK DATA initialization is "
819                             "allowed", csym->name, &csym->declared_at);
820           else if (!named_common)
821             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
822                             "in a blank COMMON but initialization is only "
823                             "allowed in named common blocks", csym->name,
824                             &csym->declared_at);
825         }
826
827       if (csym->ts.type != BT_DERIVED)
828         continue;
829
830       if (!(csym->ts.u.derived->attr.sequence
831             || csym->ts.u.derived->attr.is_bind_c))
832         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
833                        "has neither the SEQUENCE nor the BIND(C) "
834                        "attribute", csym->name, &csym->declared_at);
835       if (csym->ts.u.derived->attr.alloc_comp)
836         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
837                        "has an ultimate component that is "
838                        "allocatable", csym->name, &csym->declared_at);
839       if (gfc_has_default_initializer (csym->ts.u.derived))
840         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
841                        "may not have default initializer", csym->name,
842                        &csym->declared_at);
843
844       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
845         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
846     }
847 }
848
849 /* Resolve common blocks.  */
850 static void
851 resolve_common_blocks (gfc_symtree *common_root)
852 {
853   gfc_symbol *sym;
854
855   if (common_root == NULL)
856     return;
857
858   if (common_root->left)
859     resolve_common_blocks (common_root->left);
860   if (common_root->right)
861     resolve_common_blocks (common_root->right);
862
863   resolve_common_vars (common_root->n.common->head, true);
864
865   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
866   if (sym == NULL)
867     return;
868
869   if (sym->attr.flavor == FL_PARAMETER)
870     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
871                sym->name, &common_root->n.common->where, &sym->declared_at);
872
873   if (sym->attr.intrinsic)
874     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
875                sym->name, &common_root->n.common->where);
876   else if (sym->attr.result
877            || gfc_is_function_return_value (sym, gfc_current_ns))
878     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
879                     "that is also a function result", sym->name,
880                     &common_root->n.common->where);
881   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
882            && sym->attr.proc != PROC_ST_FUNCTION)
883     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
884                     "that is also a global procedure", sym->name,
885                     &common_root->n.common->where);
886 }
887
888
889 /* Resolve contained function types.  Because contained functions can call one
890    another, they have to be worked out before any of the contained procedures
891    can be resolved.
892
893    The good news is that if a function doesn't already have a type, the only
894    way it can get one is through an IMPLICIT type or a RESULT variable, because
895    by definition contained functions are contained namespace they're contained
896    in, not in a sibling or parent namespace.  */
897
898 static void
899 resolve_contained_functions (gfc_namespace *ns)
900 {
901   gfc_namespace *child;
902   gfc_entry_list *el;
903
904   resolve_formal_arglists (ns);
905
906   for (child = ns->contained; child; child = child->sibling)
907     {
908       /* Resolve alternate entry points first.  */
909       resolve_entries (child);
910
911       /* Then check function return types.  */
912       resolve_contained_fntype (child->proc_name, child);
913       for (el = child->entries; el; el = el->next)
914         resolve_contained_fntype (el->sym, child);
915     }
916 }
917
918
919 /* Resolve all of the elements of a structure constructor and make sure that
920    the types are correct. The 'init' flag indicates that the given
921    constructor is an initializer.  */
922
923 static gfc_try
924 resolve_structure_cons (gfc_expr *expr, int init)
925 {
926   gfc_constructor *cons;
927   gfc_component *comp;
928   gfc_try t;
929   symbol_attribute a;
930
931   t = SUCCESS;
932
933   if (expr->ts.type == BT_DERIVED)
934     resolve_symbol (expr->ts.u.derived);
935
936   cons = gfc_constructor_first (expr->value.constructor);
937   /* A constructor may have references if it is the result of substituting a
938      parameter variable.  In this case we just pull out the component we
939      want.  */
940   if (expr->ref)
941     comp = expr->ref->u.c.sym->components;
942   else
943     comp = expr->ts.u.derived->components;
944
945   /* See if the user is trying to invoke a structure constructor for one of
946      the iso_c_binding derived types.  */
947   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
948       && expr->ts.u.derived->ts.is_iso_c && cons
949       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
950     {
951       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
952                  expr->ts.u.derived->name, &(expr->where));
953       return FAILURE;
954     }
955
956   /* Return if structure constructor is c_null_(fun)prt.  */
957   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
958       && expr->ts.u.derived->ts.is_iso_c && cons
959       && cons->expr && cons->expr->expr_type == EXPR_NULL)
960     return SUCCESS;
961
962   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
963     {
964       int rank;
965
966       if (!cons->expr)
967         continue;
968
969       if (gfc_resolve_expr (cons->expr) == FAILURE)
970         {
971           t = FAILURE;
972           continue;
973         }
974
975       rank = comp->as ? comp->as->rank : 0;
976       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
977           && (comp->attr.allocatable || cons->expr->rank))
978         {
979           gfc_error ("The rank of the element in the derived type "
980                      "constructor at %L does not match that of the "
981                      "component (%d/%d)", &cons->expr->where,
982                      cons->expr->rank, rank);
983           t = FAILURE;
984         }
985
986       /* If we don't have the right type, try to convert it.  */
987
988       if (!comp->attr.proc_pointer &&
989           !gfc_compare_types (&cons->expr->ts, &comp->ts))
990         {
991           t = FAILURE;
992           if (strcmp (comp->name, "_extends") == 0)
993             {
994               /* Can afford to be brutal with the _extends initializer.
995                  The derived type can get lost because it is PRIVATE
996                  but it is not usage constrained by the standard.  */
997               cons->expr->ts = comp->ts;
998               t = SUCCESS;
999             }
1000           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
1001             gfc_error ("The element in the derived type constructor at %L, "
1002                        "for pointer component '%s', is %s but should be %s",
1003                        &cons->expr->where, comp->name,
1004                        gfc_basic_typename (cons->expr->ts.type),
1005                        gfc_basic_typename (comp->ts.type));
1006           else
1007             t = gfc_convert_type (cons->expr, &comp->ts, 1);
1008         }
1009
1010       /* For strings, the length of the constructor should be the same as
1011          the one of the structure, ensure this if the lengths are known at
1012          compile time and when we are dealing with PARAMETER or structure
1013          constructors.  */
1014       if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1015           && comp->ts.u.cl->length
1016           && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1017           && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1018           && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1019           && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1020                       comp->ts.u.cl->length->value.integer) != 0)
1021         {
1022           if (cons->expr->expr_type == EXPR_VARIABLE
1023               && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1024             {
1025               /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1026                  to make use of the gfc_resolve_character_array_constructor
1027                  machinery.  The expression is later simplified away to
1028                  an array of string literals.  */
1029               gfc_expr *para = cons->expr;
1030               cons->expr = gfc_get_expr ();
1031               cons->expr->ts = para->ts;
1032               cons->expr->where = para->where;
1033               cons->expr->expr_type = EXPR_ARRAY;
1034               cons->expr->rank = para->rank;
1035               cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1036               gfc_constructor_append_expr (&cons->expr->value.constructor,
1037                                            para, &cons->expr->where);
1038             }
1039           if (cons->expr->expr_type == EXPR_ARRAY)
1040             {
1041               gfc_constructor *p;
1042               p = gfc_constructor_first (cons->expr->value.constructor);
1043               if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1044                 {
1045                   gfc_charlen *cl, *cl2;
1046
1047                   cl2 = NULL;
1048                   for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1049                     {
1050                       if (cl == cons->expr->ts.u.cl)
1051                         break;
1052                       cl2 = cl;
1053                     }
1054
1055                   gcc_assert (cl);
1056
1057                   if (cl2)
1058                     cl2->next = cl->next;
1059
1060                   gfc_free_expr (cl->length);
1061                   gfc_free (cl);
1062                 }
1063
1064               cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1065               cons->expr->ts.u.cl->length_from_typespec = true;
1066               cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1067               gfc_resolve_character_array_constructor (cons->expr);
1068             }
1069         }
1070
1071       if (cons->expr->expr_type == EXPR_NULL
1072           && !(comp->attr.pointer || comp->attr.allocatable
1073                || comp->attr.proc_pointer
1074                || (comp->ts.type == BT_CLASS
1075                    && (CLASS_DATA (comp)->attr.class_pointer
1076                        || CLASS_DATA (comp)->attr.allocatable))))
1077         {
1078           t = FAILURE;
1079           gfc_error ("The NULL in the derived type constructor at %L is "
1080                      "being applied to component '%s', which is neither "
1081                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
1082                      comp->name);
1083         }
1084
1085       if (!comp->attr.pointer || comp->attr.proc_pointer
1086           || cons->expr->expr_type == EXPR_NULL)
1087         continue;
1088
1089       a = gfc_expr_attr (cons->expr);
1090
1091       if (!a.pointer && !a.target)
1092         {
1093           t = FAILURE;
1094           gfc_error ("The element in the derived type constructor at %L, "
1095                      "for pointer component '%s' should be a POINTER or "
1096                      "a TARGET", &cons->expr->where, comp->name);
1097         }
1098
1099       if (init)
1100         {
1101           /* F08:C461. Additional checks for pointer initialization.  */
1102           if (a.allocatable)
1103             {
1104               t = FAILURE;
1105               gfc_error ("Pointer initialization target at %L "
1106                          "must not be ALLOCATABLE ", &cons->expr->where);
1107             }
1108           if (!a.save)
1109             {
1110               t = FAILURE;
1111               gfc_error ("Pointer initialization target at %L "
1112                          "must have the SAVE attribute", &cons->expr->where);
1113             }
1114         }
1115
1116       /* F2003, C1272 (3).  */
1117       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
1118           && (gfc_impure_variable (cons->expr->symtree->n.sym)
1119               || gfc_is_coindexed (cons->expr)))
1120         {
1121           t = FAILURE;
1122           gfc_error ("Invalid expression in the derived type constructor for "
1123                      "pointer component '%s' at %L in PURE procedure",
1124                      comp->name, &cons->expr->where);
1125         }
1126
1127     }
1128
1129   return t;
1130 }
1131
1132
1133 /****************** Expression name resolution ******************/
1134
1135 /* Returns 0 if a symbol was not declared with a type or
1136    attribute declaration statement, nonzero otherwise.  */
1137
1138 static int
1139 was_declared (gfc_symbol *sym)
1140 {
1141   symbol_attribute a;
1142
1143   a = sym->attr;
1144
1145   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1146     return 1;
1147
1148   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1149       || a.optional || a.pointer || a.save || a.target || a.volatile_
1150       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1151       || a.asynchronous || a.codimension)
1152     return 1;
1153
1154   return 0;
1155 }
1156
1157
1158 /* Determine if a symbol is generic or not.  */
1159
1160 static int
1161 generic_sym (gfc_symbol *sym)
1162 {
1163   gfc_symbol *s;
1164
1165   if (sym->attr.generic ||
1166       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1167     return 1;
1168
1169   if (was_declared (sym) || sym->ns->parent == NULL)
1170     return 0;
1171
1172   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1173   
1174   if (s != NULL)
1175     {
1176       if (s == sym)
1177         return 0;
1178       else
1179         return generic_sym (s);
1180     }
1181
1182   return 0;
1183 }
1184
1185
1186 /* Determine if a symbol is specific or not.  */
1187
1188 static int
1189 specific_sym (gfc_symbol *sym)
1190 {
1191   gfc_symbol *s;
1192
1193   if (sym->attr.if_source == IFSRC_IFBODY
1194       || sym->attr.proc == PROC_MODULE
1195       || sym->attr.proc == PROC_INTERNAL
1196       || sym->attr.proc == PROC_ST_FUNCTION
1197       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1198       || sym->attr.external)
1199     return 1;
1200
1201   if (was_declared (sym) || sym->ns->parent == NULL)
1202     return 0;
1203
1204   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1205
1206   return (s == NULL) ? 0 : specific_sym (s);
1207 }
1208
1209
1210 /* Figure out if the procedure is specific, generic or unknown.  */
1211
1212 typedef enum
1213 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1214 proc_type;
1215
1216 static proc_type
1217 procedure_kind (gfc_symbol *sym)
1218 {
1219   if (generic_sym (sym))
1220     return PTYPE_GENERIC;
1221
1222   if (specific_sym (sym))
1223     return PTYPE_SPECIFIC;
1224
1225   return PTYPE_UNKNOWN;
1226 }
1227
1228 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1229    is nonzero when matching actual arguments.  */
1230
1231 static int need_full_assumed_size = 0;
1232
1233 static bool
1234 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1235 {
1236   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1237       return false;
1238
1239   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1240      What should it be?  */
1241   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1242           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1243                && (e->ref->u.ar.type == AR_FULL))
1244     {
1245       gfc_error ("The upper bound in the last dimension must "
1246                  "appear in the reference to the assumed size "
1247                  "array '%s' at %L", sym->name, &e->where);
1248       return true;
1249     }
1250   return false;
1251 }
1252
1253
1254 /* Look for bad assumed size array references in argument expressions
1255   of elemental and array valued intrinsic procedures.  Since this is
1256   called from procedure resolution functions, it only recurses at
1257   operators.  */
1258
1259 static bool
1260 resolve_assumed_size_actual (gfc_expr *e)
1261 {
1262   if (e == NULL)
1263    return false;
1264
1265   switch (e->expr_type)
1266     {
1267     case EXPR_VARIABLE:
1268       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1269         return true;
1270       break;
1271
1272     case EXPR_OP:
1273       if (resolve_assumed_size_actual (e->value.op.op1)
1274           || resolve_assumed_size_actual (e->value.op.op2))
1275         return true;
1276       break;
1277
1278     default:
1279       break;
1280     }
1281   return false;
1282 }
1283
1284
1285 /* Check a generic procedure, passed as an actual argument, to see if
1286    there is a matching specific name.  If none, it is an error, and if
1287    more than one, the reference is ambiguous.  */
1288 static int
1289 count_specific_procs (gfc_expr *e)
1290 {
1291   int n;
1292   gfc_interface *p;
1293   gfc_symbol *sym;
1294         
1295   n = 0;
1296   sym = e->symtree->n.sym;
1297
1298   for (p = sym->generic; p; p = p->next)
1299     if (strcmp (sym->name, p->sym->name) == 0)
1300       {
1301         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1302                                        sym->name);
1303         n++;
1304       }
1305
1306   if (n > 1)
1307     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1308                &e->where);
1309
1310   if (n == 0)
1311     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1312                "argument at %L", sym->name, &e->where);
1313
1314   return n;
1315 }
1316
1317
1318 /* See if a call to sym could possibly be a not allowed RECURSION because of
1319    a missing RECURIVE declaration.  This means that either sym is the current
1320    context itself, or sym is the parent of a contained procedure calling its
1321    non-RECURSIVE containing procedure.
1322    This also works if sym is an ENTRY.  */
1323
1324 static bool
1325 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1326 {
1327   gfc_symbol* proc_sym;
1328   gfc_symbol* context_proc;
1329   gfc_namespace* real_context;
1330
1331   if (sym->attr.flavor == FL_PROGRAM)
1332     return false;
1333
1334   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1335
1336   /* If we've got an ENTRY, find real procedure.  */
1337   if (sym->attr.entry && sym->ns->entries)
1338     proc_sym = sym->ns->entries->sym;
1339   else
1340     proc_sym = sym;
1341
1342   /* If sym is RECURSIVE, all is well of course.  */
1343   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1344     return false;
1345
1346   /* Find the context procedure's "real" symbol if it has entries.
1347      We look for a procedure symbol, so recurse on the parents if we don't
1348      find one (like in case of a BLOCK construct).  */
1349   for (real_context = context; ; real_context = real_context->parent)
1350     {
1351       /* We should find something, eventually!  */
1352       gcc_assert (real_context);
1353
1354       context_proc = (real_context->entries ? real_context->entries->sym
1355                                             : real_context->proc_name);
1356
1357       /* In some special cases, there may not be a proc_name, like for this
1358          invalid code:
1359          real(bad_kind()) function foo () ...
1360          when checking the call to bad_kind ().
1361          In these cases, we simply return here and assume that the
1362          call is ok.  */
1363       if (!context_proc)
1364         return false;
1365
1366       if (context_proc->attr.flavor != FL_LABEL)
1367         break;
1368     }
1369
1370   /* A call from sym's body to itself is recursion, of course.  */
1371   if (context_proc == proc_sym)
1372     return true;
1373
1374   /* The same is true if context is a contained procedure and sym the
1375      containing one.  */
1376   if (context_proc->attr.contained)
1377     {
1378       gfc_symbol* parent_proc;
1379
1380       gcc_assert (context->parent);
1381       parent_proc = (context->parent->entries ? context->parent->entries->sym
1382                                               : context->parent->proc_name);
1383
1384       if (parent_proc == proc_sym)
1385         return true;
1386     }
1387
1388   return false;
1389 }
1390
1391
1392 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1393    its typespec and formal argument list.  */
1394
1395 static gfc_try
1396 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1397 {
1398   gfc_intrinsic_sym* isym = NULL;
1399   const char* symstd;
1400
1401   if (sym->formal)
1402     return SUCCESS;
1403
1404   /* We already know this one is an intrinsic, so we don't call
1405      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1406      gfc_find_subroutine directly to check whether it is a function or
1407      subroutine.  */
1408
1409   if (sym->intmod_sym_id)
1410     isym = gfc_intrinsic_function_by_id ((gfc_isym_id) sym->intmod_sym_id);
1411   else
1412     isym = gfc_find_function (sym->name);
1413
1414   if (isym)
1415     {
1416       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1417           && !sym->attr.implicit_type)
1418         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1419                       " ignored", sym->name, &sym->declared_at);
1420
1421       if (!sym->attr.function &&
1422           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1423         return FAILURE;
1424
1425       sym->ts = isym->ts;
1426     }
1427   else if ((isym = gfc_find_subroutine (sym->name)))
1428     {
1429       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1430         {
1431           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1432                       " specifier", sym->name, &sym->declared_at);
1433           return FAILURE;
1434         }
1435
1436       if (!sym->attr.subroutine &&
1437           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1438         return FAILURE;
1439     }
1440   else
1441     {
1442       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1443                  &sym->declared_at);
1444       return FAILURE;
1445     }
1446
1447   gfc_copy_formal_args_intr (sym, isym);
1448
1449   /* Check it is actually available in the standard settings.  */
1450   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1451       == FAILURE)
1452     {
1453       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1454                  " available in the current standard settings but %s.  Use"
1455                  " an appropriate -std=* option or enable -fall-intrinsics"
1456                  " in order to use it.",
1457                  sym->name, &sym->declared_at, symstd);
1458       return FAILURE;
1459     }
1460
1461   return SUCCESS;
1462 }
1463
1464
1465 /* Resolve a procedure expression, like passing it to a called procedure or as
1466    RHS for a procedure pointer assignment.  */
1467
1468 static gfc_try
1469 resolve_procedure_expression (gfc_expr* expr)
1470 {
1471   gfc_symbol* sym;
1472
1473   if (expr->expr_type != EXPR_VARIABLE)
1474     return SUCCESS;
1475   gcc_assert (expr->symtree);
1476
1477   sym = expr->symtree->n.sym;
1478
1479   if (sym->attr.intrinsic)
1480     resolve_intrinsic (sym, &expr->where);
1481
1482   if (sym->attr.flavor != FL_PROCEDURE
1483       || (sym->attr.function && sym->result == sym))
1484     return SUCCESS;
1485
1486   /* A non-RECURSIVE procedure that is used as procedure expression within its
1487      own body is in danger of being called recursively.  */
1488   if (is_illegal_recursion (sym, gfc_current_ns))
1489     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1490                  " itself recursively.  Declare it RECURSIVE or use"
1491                  " -frecursive", sym->name, &expr->where);
1492   
1493   return SUCCESS;
1494 }
1495
1496
1497 /* Resolve an actual argument list.  Most of the time, this is just
1498    resolving the expressions in the list.
1499    The exception is that we sometimes have to decide whether arguments
1500    that look like procedure arguments are really simple variable
1501    references.  */
1502
1503 static gfc_try
1504 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1505                         bool no_formal_args)
1506 {
1507   gfc_symbol *sym;
1508   gfc_symtree *parent_st;
1509   gfc_expr *e;
1510   int save_need_full_assumed_size;
1511   gfc_component *comp;
1512
1513   for (; arg; arg = arg->next)
1514     {
1515       e = arg->expr;
1516       if (e == NULL)
1517         {
1518           /* Check the label is a valid branching target.  */
1519           if (arg->label)
1520             {
1521               if (arg->label->defined == ST_LABEL_UNKNOWN)
1522                 {
1523                   gfc_error ("Label %d referenced at %L is never defined",
1524                              arg->label->value, &arg->label->where);
1525                   return FAILURE;
1526                 }
1527             }
1528           continue;
1529         }
1530
1531       if (gfc_is_proc_ptr_comp (e, &comp))
1532         {
1533           e->ts = comp->ts;
1534           if (e->expr_type == EXPR_PPC)
1535             {
1536               if (comp->as != NULL)
1537                 e->rank = comp->as->rank;
1538               e->expr_type = EXPR_FUNCTION;
1539             }
1540           if (gfc_resolve_expr (e) == FAILURE)                          
1541             return FAILURE; 
1542           goto argument_list;
1543         }
1544
1545       if (e->expr_type == EXPR_VARIABLE
1546             && e->symtree->n.sym->attr.generic
1547             && no_formal_args
1548             && count_specific_procs (e) != 1)
1549         return FAILURE;
1550
1551       if (e->ts.type != BT_PROCEDURE)
1552         {
1553           save_need_full_assumed_size = need_full_assumed_size;
1554           if (e->expr_type != EXPR_VARIABLE)
1555             need_full_assumed_size = 0;
1556           if (gfc_resolve_expr (e) != SUCCESS)
1557             return FAILURE;
1558           need_full_assumed_size = save_need_full_assumed_size;
1559           goto argument_list;
1560         }
1561
1562       /* See if the expression node should really be a variable reference.  */
1563
1564       sym = e->symtree->n.sym;
1565
1566       if (sym->attr.flavor == FL_PROCEDURE
1567           || sym->attr.intrinsic
1568           || sym->attr.external)
1569         {
1570           int actual_ok;
1571
1572           /* If a procedure is not already determined to be something else
1573              check if it is intrinsic.  */
1574           if (!sym->attr.intrinsic
1575               && !(sym->attr.external || sym->attr.use_assoc
1576                    || sym->attr.if_source == IFSRC_IFBODY)
1577               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1578             sym->attr.intrinsic = 1;
1579
1580           if (sym->attr.proc == PROC_ST_FUNCTION)
1581             {
1582               gfc_error ("Statement function '%s' at %L is not allowed as an "
1583                          "actual argument", sym->name, &e->where);
1584             }
1585
1586           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1587                                                sym->attr.subroutine);
1588           if (sym->attr.intrinsic && actual_ok == 0)
1589             {
1590               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1591                          "actual argument", sym->name, &e->where);
1592             }
1593
1594           if (sym->attr.contained && !sym->attr.use_assoc
1595               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1596             {
1597               if (gfc_notify_std (GFC_STD_F2008,
1598                                   "Fortran 2008: Internal procedure '%s' is"
1599                                   " used as actual argument at %L",
1600                                   sym->name, &e->where) == FAILURE)
1601                 return FAILURE;
1602             }
1603
1604           if (sym->attr.elemental && !sym->attr.intrinsic)
1605             {
1606               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1607                          "allowed as an actual argument at %L", sym->name,
1608                          &e->where);
1609             }
1610
1611           /* Check if a generic interface has a specific procedure
1612             with the same name before emitting an error.  */
1613           if (sym->attr.generic && count_specific_procs (e) != 1)
1614             return FAILURE;
1615           
1616           /* Just in case a specific was found for the expression.  */
1617           sym = e->symtree->n.sym;
1618
1619           /* If the symbol is the function that names the current (or
1620              parent) scope, then we really have a variable reference.  */
1621
1622           if (gfc_is_function_return_value (sym, sym->ns))
1623             goto got_variable;
1624
1625           /* If all else fails, see if we have a specific intrinsic.  */
1626           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1627             {
1628               gfc_intrinsic_sym *isym;
1629
1630               isym = gfc_find_function (sym->name);
1631               if (isym == NULL || !isym->specific)
1632                 {
1633                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1634                              "for the reference '%s' at %L", sym->name,
1635                              &e->where);
1636                   return FAILURE;
1637                 }
1638               sym->ts = isym->ts;
1639               sym->attr.intrinsic = 1;
1640               sym->attr.function = 1;
1641             }
1642
1643           if (gfc_resolve_expr (e) == FAILURE)
1644             return FAILURE;
1645           goto argument_list;
1646         }
1647
1648       /* See if the name is a module procedure in a parent unit.  */
1649
1650       if (was_declared (sym) || sym->ns->parent == NULL)
1651         goto got_variable;
1652
1653       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1654         {
1655           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1656           return FAILURE;
1657         }
1658
1659       if (parent_st == NULL)
1660         goto got_variable;
1661
1662       sym = parent_st->n.sym;
1663       e->symtree = parent_st;           /* Point to the right thing.  */
1664
1665       if (sym->attr.flavor == FL_PROCEDURE
1666           || sym->attr.intrinsic
1667           || sym->attr.external)
1668         {
1669           if (gfc_resolve_expr (e) == FAILURE)
1670             return FAILURE;
1671           goto argument_list;
1672         }
1673
1674     got_variable:
1675       e->expr_type = EXPR_VARIABLE;
1676       e->ts = sym->ts;
1677       if (sym->as != NULL)
1678         {
1679           e->rank = sym->as->rank;
1680           e->ref = gfc_get_ref ();
1681           e->ref->type = REF_ARRAY;
1682           e->ref->u.ar.type = AR_FULL;
1683           e->ref->u.ar.as = sym->as;
1684         }
1685
1686       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1687          primary.c (match_actual_arg). If above code determines that it
1688          is a  variable instead, it needs to be resolved as it was not
1689          done at the beginning of this function.  */
1690       save_need_full_assumed_size = need_full_assumed_size;
1691       if (e->expr_type != EXPR_VARIABLE)
1692         need_full_assumed_size = 0;
1693       if (gfc_resolve_expr (e) != SUCCESS)
1694         return FAILURE;
1695       need_full_assumed_size = save_need_full_assumed_size;
1696
1697     argument_list:
1698       /* Check argument list functions %VAL, %LOC and %REF.  There is
1699          nothing to do for %REF.  */
1700       if (arg->name && arg->name[0] == '%')
1701         {
1702           if (strncmp ("%VAL", arg->name, 4) == 0)
1703             {
1704               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1705                 {
1706                   gfc_error ("By-value argument at %L is not of numeric "
1707                              "type", &e->where);
1708                   return FAILURE;
1709                 }
1710
1711               if (e->rank)
1712                 {
1713                   gfc_error ("By-value argument at %L cannot be an array or "
1714                              "an array section", &e->where);
1715                 return FAILURE;
1716                 }
1717
1718               /* Intrinsics are still PROC_UNKNOWN here.  However,
1719                  since same file external procedures are not resolvable
1720                  in gfortran, it is a good deal easier to leave them to
1721                  intrinsic.c.  */
1722               if (ptype != PROC_UNKNOWN
1723                   && ptype != PROC_DUMMY
1724                   && ptype != PROC_EXTERNAL
1725                   && ptype != PROC_MODULE)
1726                 {
1727                   gfc_error ("By-value argument at %L is not allowed "
1728                              "in this context", &e->where);
1729                   return FAILURE;
1730                 }
1731             }
1732
1733           /* Statement functions have already been excluded above.  */
1734           else if (strncmp ("%LOC", arg->name, 4) == 0
1735                    && e->ts.type == BT_PROCEDURE)
1736             {
1737               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1738                 {
1739                   gfc_error ("Passing internal procedure at %L by location "
1740                              "not allowed", &e->where);
1741                   return FAILURE;
1742                 }
1743             }
1744         }
1745
1746       /* Fortran 2008, C1237.  */
1747       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1748           && gfc_has_ultimate_pointer (e))
1749         {
1750           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1751                      "component", &e->where);
1752           return FAILURE;
1753         }
1754     }
1755
1756   return SUCCESS;
1757 }
1758
1759
1760 /* Do the checks of the actual argument list that are specific to elemental
1761    procedures.  If called with c == NULL, we have a function, otherwise if
1762    expr == NULL, we have a subroutine.  */
1763
1764 static gfc_try
1765 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1766 {
1767   gfc_actual_arglist *arg0;
1768   gfc_actual_arglist *arg;
1769   gfc_symbol *esym = NULL;
1770   gfc_intrinsic_sym *isym = NULL;
1771   gfc_expr *e = NULL;
1772   gfc_intrinsic_arg *iformal = NULL;
1773   gfc_formal_arglist *eformal = NULL;
1774   bool formal_optional = false;
1775   bool set_by_optional = false;
1776   int i;
1777   int rank = 0;
1778
1779   /* Is this an elemental procedure?  */
1780   if (expr && expr->value.function.actual != NULL)
1781     {
1782       if (expr->value.function.esym != NULL
1783           && expr->value.function.esym->attr.elemental)
1784         {
1785           arg0 = expr->value.function.actual;
1786           esym = expr->value.function.esym;
1787         }
1788       else if (expr->value.function.isym != NULL
1789                && expr->value.function.isym->elemental)
1790         {
1791           arg0 = expr->value.function.actual;
1792           isym = expr->value.function.isym;
1793         }
1794       else
1795         return SUCCESS;
1796     }
1797   else if (c && c->ext.actual != NULL)
1798     {
1799       arg0 = c->ext.actual;
1800       
1801       if (c->resolved_sym)
1802         esym = c->resolved_sym;
1803       else
1804         esym = c->symtree->n.sym;
1805       gcc_assert (esym);
1806
1807       if (!esym->attr.elemental)
1808         return SUCCESS;
1809     }
1810   else
1811     return SUCCESS;
1812
1813   /* The rank of an elemental is the rank of its array argument(s).  */
1814   for (arg = arg0; arg; arg = arg->next)
1815     {
1816       if (arg->expr != NULL && arg->expr->rank > 0)
1817         {
1818           rank = arg->expr->rank;
1819           if (arg->expr->expr_type == EXPR_VARIABLE
1820               && arg->expr->symtree->n.sym->attr.optional)
1821             set_by_optional = true;
1822
1823           /* Function specific; set the result rank and shape.  */
1824           if (expr)
1825             {
1826               expr->rank = rank;
1827               if (!expr->shape && arg->expr->shape)
1828                 {
1829                   expr->shape = gfc_get_shape (rank);
1830                   for (i = 0; i < rank; i++)
1831                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1832                 }
1833             }
1834           break;
1835         }
1836     }
1837
1838   /* If it is an array, it shall not be supplied as an actual argument
1839      to an elemental procedure unless an array of the same rank is supplied
1840      as an actual argument corresponding to a nonoptional dummy argument of
1841      that elemental procedure(12.4.1.5).  */
1842   formal_optional = false;
1843   if (isym)
1844     iformal = isym->formal;
1845   else
1846     eformal = esym->formal;
1847
1848   for (arg = arg0; arg; arg = arg->next)
1849     {
1850       if (eformal)
1851         {
1852           if (eformal->sym && eformal->sym->attr.optional)
1853             formal_optional = true;
1854           eformal = eformal->next;
1855         }
1856       else if (isym && iformal)
1857         {
1858           if (iformal->optional)
1859             formal_optional = true;
1860           iformal = iformal->next;
1861         }
1862       else if (isym)
1863         formal_optional = true;
1864
1865       if (pedantic && arg->expr != NULL
1866           && arg->expr->expr_type == EXPR_VARIABLE
1867           && arg->expr->symtree->n.sym->attr.optional
1868           && formal_optional
1869           && arg->expr->rank
1870           && (set_by_optional || arg->expr->rank != rank)
1871           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1872         {
1873           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1874                        "MISSING, it cannot be the actual argument of an "
1875                        "ELEMENTAL procedure unless there is a non-optional "
1876                        "argument with the same rank (12.4.1.5)",
1877                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1878           return FAILURE;
1879         }
1880     }
1881
1882   for (arg = arg0; arg; arg = arg->next)
1883     {
1884       if (arg->expr == NULL || arg->expr->rank == 0)
1885         continue;
1886
1887       /* Being elemental, the last upper bound of an assumed size array
1888          argument must be present.  */
1889       if (resolve_assumed_size_actual (arg->expr))
1890         return FAILURE;
1891
1892       /* Elemental procedure's array actual arguments must conform.  */
1893       if (e != NULL)
1894         {
1895           if (gfc_check_conformance (arg->expr, e,
1896                                      "elemental procedure") == FAILURE)
1897             return FAILURE;
1898         }
1899       else
1900         e = arg->expr;
1901     }
1902
1903   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1904      is an array, the intent inout/out variable needs to be also an array.  */
1905   if (rank > 0 && esym && expr == NULL)
1906     for (eformal = esym->formal, arg = arg0; arg && eformal;
1907          arg = arg->next, eformal = eformal->next)
1908       if ((eformal->sym->attr.intent == INTENT_OUT
1909            || eformal->sym->attr.intent == INTENT_INOUT)
1910           && arg->expr && arg->expr->rank == 0)
1911         {
1912           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1913                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1914                      "actual argument is an array", &arg->expr->where,
1915                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1916                      : "INOUT", eformal->sym->name, esym->name);
1917           return FAILURE;
1918         }
1919   return SUCCESS;
1920 }
1921
1922
1923 /* This function does the checking of references to global procedures
1924    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1925    77 and 95 standards.  It checks for a gsymbol for the name, making
1926    one if it does not already exist.  If it already exists, then the
1927    reference being resolved must correspond to the type of gsymbol.
1928    Otherwise, the new symbol is equipped with the attributes of the
1929    reference.  The corresponding code that is called in creating
1930    global entities is parse.c.
1931
1932    In addition, for all but -std=legacy, the gsymbols are used to
1933    check the interfaces of external procedures from the same file.
1934    The namespace of the gsymbol is resolved and then, once this is
1935    done the interface is checked.  */
1936
1937
1938 static bool
1939 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1940 {
1941   if (!gsym_ns->proc_name->attr.recursive)
1942     return true;
1943
1944   if (sym->ns == gsym_ns)
1945     return false;
1946
1947   if (sym->ns->parent && sym->ns->parent == gsym_ns)
1948     return false;
1949
1950   return true;
1951 }
1952
1953 static bool
1954 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
1955 {
1956   if (gsym_ns->entries)
1957     {
1958       gfc_entry_list *entry = gsym_ns->entries;
1959
1960       for (; entry; entry = entry->next)
1961         {
1962           if (strcmp (sym->name, entry->sym->name) == 0)
1963             {
1964               if (strcmp (gsym_ns->proc_name->name,
1965                           sym->ns->proc_name->name) == 0)
1966                 return false;
1967
1968               if (sym->ns->parent
1969                   && strcmp (gsym_ns->proc_name->name,
1970                              sym->ns->parent->proc_name->name) == 0)
1971                 return false;
1972             }
1973         }
1974     }
1975   return true;
1976 }
1977
1978 static void
1979 resolve_global_procedure (gfc_symbol *sym, locus *where,
1980                           gfc_actual_arglist **actual, int sub)
1981 {
1982   gfc_gsymbol * gsym;
1983   gfc_namespace *ns;
1984   enum gfc_symbol_type type;
1985
1986   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1987
1988   gsym = gfc_get_gsymbol (sym->name);
1989
1990   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1991     gfc_global_used (gsym, where);
1992
1993   if (gfc_option.flag_whole_file
1994         && (sym->attr.if_source == IFSRC_UNKNOWN
1995             || sym->attr.if_source == IFSRC_IFBODY)
1996         && gsym->type != GSYM_UNKNOWN
1997         && gsym->ns
1998         && gsym->ns->resolved != -1
1999         && gsym->ns->proc_name
2000         && not_in_recursive (sym, gsym->ns)
2001         && not_entry_self_reference (sym, gsym->ns))
2002     {
2003       gfc_symbol *def_sym;
2004
2005       /* Resolve the gsymbol namespace if needed.  */
2006       if (!gsym->ns->resolved)
2007         {
2008           gfc_dt_list *old_dt_list;
2009
2010           /* Stash away derived types so that the backend_decls do not
2011              get mixed up.  */
2012           old_dt_list = gfc_derived_types;
2013           gfc_derived_types = NULL;
2014
2015           gfc_resolve (gsym->ns);
2016
2017           /* Store the new derived types with the global namespace.  */
2018           if (gfc_derived_types)
2019             gsym->ns->derived_types = gfc_derived_types;
2020
2021           /* Restore the derived types of this namespace.  */
2022           gfc_derived_types = old_dt_list;
2023         }
2024
2025       /* Make sure that translation for the gsymbol occurs before
2026          the procedure currently being resolved.  */
2027       ns = gfc_global_ns_list;
2028       for (; ns && ns != gsym->ns; ns = ns->sibling)
2029         {
2030           if (ns->sibling == gsym->ns)
2031             {
2032               ns->sibling = gsym->ns->sibling;
2033               gsym->ns->sibling = gfc_global_ns_list;
2034               gfc_global_ns_list = gsym->ns;
2035               break;
2036             }
2037         }
2038
2039       def_sym = gsym->ns->proc_name;
2040       if (def_sym->attr.entry_master)
2041         {
2042           gfc_entry_list *entry;
2043           for (entry = gsym->ns->entries; entry; entry = entry->next)
2044             if (strcmp (entry->sym->name, sym->name) == 0)
2045               {
2046                 def_sym = entry->sym;
2047                 break;
2048               }
2049         }
2050
2051       /* Differences in constant character lengths.  */
2052       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
2053         {
2054           long int l1 = 0, l2 = 0;
2055           gfc_charlen *cl1 = sym->ts.u.cl;
2056           gfc_charlen *cl2 = def_sym->ts.u.cl;
2057
2058           if (cl1 != NULL
2059               && cl1->length != NULL
2060               && cl1->length->expr_type == EXPR_CONSTANT)
2061             l1 = mpz_get_si (cl1->length->value.integer);
2062
2063           if (cl2 != NULL
2064               && cl2->length != NULL
2065               && cl2->length->expr_type == EXPR_CONSTANT)
2066             l2 = mpz_get_si (cl2->length->value.integer);
2067
2068           if (l1 && l2 && l1 != l2)
2069             gfc_error ("Character length mismatch in return type of "
2070                        "function '%s' at %L (%ld/%ld)", sym->name,
2071                        &sym->declared_at, l1, l2);
2072         }
2073
2074      /* Type mismatch of function return type and expected type.  */
2075      if (sym->attr.function
2076          && !gfc_compare_types (&sym->ts, &def_sym->ts))
2077         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
2078                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2079                    gfc_typename (&def_sym->ts));
2080
2081       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
2082         {
2083           gfc_formal_arglist *arg = def_sym->formal;
2084           for ( ; arg; arg = arg->next)
2085             if (!arg->sym)
2086               continue;
2087             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
2088             else if (arg->sym->attr.allocatable
2089                      || arg->sym->attr.asynchronous
2090                      || arg->sym->attr.optional
2091                      || arg->sym->attr.pointer
2092                      || arg->sym->attr.target
2093                      || arg->sym->attr.value
2094                      || arg->sym->attr.volatile_)
2095               {
2096                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
2097                            "has an attribute that requires an explicit "
2098                            "interface for this procedure", arg->sym->name,
2099                            sym->name, &sym->declared_at);
2100                 break;
2101               }
2102             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
2103             else if (arg->sym && arg->sym->as
2104                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
2105               {
2106                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
2107                            "argument '%s' must have an explicit interface",
2108                            sym->name, &sym->declared_at, arg->sym->name);
2109                 break;
2110               }
2111             /* F2008, 12.4.2.2 (2c)  */
2112             else if (arg->sym->attr.codimension)
2113               {
2114                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
2115                            "'%s' must have an explicit interface",
2116                            sym->name, &sym->declared_at, arg->sym->name);
2117                 break;
2118               }
2119             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
2120             else if (false) /* TODO: is a parametrized derived type  */
2121               {
2122                 gfc_error ("Procedure '%s' at %L with parametrized derived "
2123                            "type argument '%s' must have an explicit "
2124                            "interface", sym->name, &sym->declared_at,
2125                            arg->sym->name);
2126                 break;
2127               }
2128             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
2129             else if (arg->sym->ts.type == BT_CLASS)
2130               {
2131                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
2132                            "argument '%s' must have an explicit interface",
2133                            sym->name, &sym->declared_at, arg->sym->name);
2134                 break;
2135               }
2136         }
2137
2138       if (def_sym->attr.function)
2139         {
2140           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
2141           if (def_sym->as && def_sym->as->rank
2142               && (!sym->as || sym->as->rank != def_sym->as->rank))
2143             gfc_error ("The reference to function '%s' at %L either needs an "
2144                        "explicit INTERFACE or the rank is incorrect", sym->name,
2145                        where);
2146
2147           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
2148           if ((def_sym->result->attr.pointer
2149                || def_sym->result->attr.allocatable)
2150                && (sym->attr.if_source != IFSRC_IFBODY
2151                    || def_sym->result->attr.pointer
2152                         != sym->result->attr.pointer
2153                    || def_sym->result->attr.allocatable
2154                         != sym->result->attr.allocatable))
2155             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
2156                        "result must have an explicit interface", sym->name,
2157                        where);
2158
2159           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
2160           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
2161               && def_sym->ts.u.cl->length != NULL)
2162             {
2163               gfc_charlen *cl = sym->ts.u.cl;
2164
2165               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
2166                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
2167                 {
2168                   gfc_error ("Nonconstant character-length function '%s' at %L "
2169                              "must have an explicit interface", sym->name,
2170                              &sym->declared_at);
2171                 }
2172             }
2173         }
2174
2175       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2176       if (def_sym->attr.elemental && !sym->attr.elemental)
2177         {
2178           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2179                      "interface", sym->name, &sym->declared_at);
2180         }
2181
2182       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2183       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2184         {
2185           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2186                      "an explicit interface", sym->name, &sym->declared_at);
2187         }
2188
2189       if (gfc_option.flag_whole_file == 1
2190           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2191               && !(gfc_option.warn_std & GFC_STD_GNU)))
2192         gfc_errors_to_warnings (1);
2193
2194       if (sym->attr.if_source != IFSRC_IFBODY)  
2195         gfc_procedure_use (def_sym, actual, where);
2196
2197       gfc_errors_to_warnings (0);
2198     }
2199
2200   if (gsym->type == GSYM_UNKNOWN)
2201     {
2202       gsym->type = type;
2203       gsym->where = *where;
2204     }
2205
2206   gsym->used = 1;
2207 }
2208
2209
2210 /************* Function resolution *************/
2211
2212 /* Resolve a function call known to be generic.
2213    Section 14.1.2.4.1.  */
2214
2215 static match
2216 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2217 {
2218   gfc_symbol *s;
2219
2220   if (sym->attr.generic)
2221     {
2222       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2223       if (s != NULL)
2224         {
2225           expr->value.function.name = s->name;
2226           expr->value.function.esym = s;
2227
2228           if (s->ts.type != BT_UNKNOWN)
2229             expr->ts = s->ts;
2230           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2231             expr->ts = s->result->ts;
2232
2233           if (s->as != NULL)
2234             expr->rank = s->as->rank;
2235           else if (s->result != NULL && s->result->as != NULL)
2236             expr->rank = s->result->as->rank;
2237
2238           gfc_set_sym_referenced (expr->value.function.esym);
2239
2240           return MATCH_YES;
2241         }
2242
2243       /* TODO: Need to search for elemental references in generic
2244          interface.  */
2245     }
2246
2247   if (sym->attr.intrinsic)
2248     return gfc_intrinsic_func_interface (expr, 0);
2249
2250   return MATCH_NO;
2251 }
2252
2253
2254 static gfc_try
2255 resolve_generic_f (gfc_expr *expr)
2256 {
2257   gfc_symbol *sym;
2258   match m;
2259
2260   sym = expr->symtree->n.sym;
2261
2262   for (;;)
2263     {
2264       m = resolve_generic_f0 (expr, sym);
2265       if (m == MATCH_YES)
2266         return SUCCESS;
2267       else if (m == MATCH_ERROR)
2268         return FAILURE;
2269
2270 generic:
2271       if (sym->ns->parent == NULL)
2272         break;
2273       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2274
2275       if (sym == NULL)
2276         break;
2277       if (!generic_sym (sym))
2278         goto generic;
2279     }
2280
2281   /* Last ditch attempt.  See if the reference is to an intrinsic
2282      that possesses a matching interface.  14.1.2.4  */
2283   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
2284     {
2285       gfc_error ("There is no specific function for the generic '%s' at %L",
2286                  expr->symtree->n.sym->name, &expr->where);
2287       return FAILURE;
2288     }
2289
2290   m = gfc_intrinsic_func_interface (expr, 0);
2291   if (m == MATCH_YES)
2292     return SUCCESS;
2293   if (m == MATCH_NO)
2294     gfc_error ("Generic function '%s' at %L is not consistent with a "
2295                "specific intrinsic interface", expr->symtree->n.sym->name,
2296                &expr->where);
2297
2298   return FAILURE;
2299 }
2300
2301
2302 /* Resolve a function call known to be specific.  */
2303
2304 static match
2305 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2306 {
2307   match m;
2308
2309   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2310     {
2311       if (sym->attr.dummy)
2312         {
2313           sym->attr.proc = PROC_DUMMY;
2314           goto found;
2315         }
2316
2317       sym->attr.proc = PROC_EXTERNAL;
2318       goto found;
2319     }
2320
2321   if (sym->attr.proc == PROC_MODULE
2322       || sym->attr.proc == PROC_ST_FUNCTION
2323       || sym->attr.proc == PROC_INTERNAL)
2324     goto found;
2325
2326   if (sym->attr.intrinsic)
2327     {
2328       m = gfc_intrinsic_func_interface (expr, 1);
2329       if (m == MATCH_YES)
2330         return MATCH_YES;
2331       if (m == MATCH_NO)
2332         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2333                    "with an intrinsic", sym->name, &expr->where);
2334
2335       return MATCH_ERROR;
2336     }
2337
2338   return MATCH_NO;
2339
2340 found:
2341   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2342
2343   if (sym->result)
2344     expr->ts = sym->result->ts;
2345   else
2346     expr->ts = sym->ts;
2347   expr->value.function.name = sym->name;
2348   expr->value.function.esym = sym;
2349   if (sym->as != NULL)
2350     expr->rank = sym->as->rank;
2351
2352   return MATCH_YES;
2353 }
2354
2355
2356 static gfc_try
2357 resolve_specific_f (gfc_expr *expr)
2358 {
2359   gfc_symbol *sym;
2360   match m;
2361
2362   sym = expr->symtree->n.sym;
2363
2364   for (;;)
2365     {
2366       m = resolve_specific_f0 (sym, expr);
2367       if (m == MATCH_YES)
2368         return SUCCESS;
2369       if (m == MATCH_ERROR)
2370         return FAILURE;
2371
2372       if (sym->ns->parent == NULL)
2373         break;
2374
2375       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2376
2377       if (sym == NULL)
2378         break;
2379     }
2380
2381   gfc_error ("Unable to resolve the specific function '%s' at %L",
2382              expr->symtree->n.sym->name, &expr->where);
2383
2384   return SUCCESS;
2385 }
2386
2387
2388 /* Resolve a procedure call not known to be generic nor specific.  */
2389
2390 static gfc_try
2391 resolve_unknown_f (gfc_expr *expr)
2392 {
2393   gfc_symbol *sym;
2394   gfc_typespec *ts;
2395
2396   sym = expr->symtree->n.sym;
2397
2398   if (sym->attr.dummy)
2399     {
2400       sym->attr.proc = PROC_DUMMY;
2401       expr->value.function.name = sym->name;
2402       goto set_type;
2403     }
2404
2405   /* See if we have an intrinsic function reference.  */
2406
2407   if (gfc_is_intrinsic (sym, 0, expr->where))
2408     {
2409       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2410         return SUCCESS;
2411       return FAILURE;
2412     }
2413
2414   /* The reference is to an external name.  */
2415
2416   sym->attr.proc = PROC_EXTERNAL;
2417   expr->value.function.name = sym->name;
2418   expr->value.function.esym = expr->symtree->n.sym;
2419
2420   if (sym->as != NULL)
2421     expr->rank = sym->as->rank;
2422
2423   /* Type of the expression is either the type of the symbol or the
2424      default type of the symbol.  */
2425
2426 set_type:
2427   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2428
2429   if (sym->ts.type != BT_UNKNOWN)
2430     expr->ts = sym->ts;
2431   else
2432     {
2433       ts = gfc_get_default_type (sym->name, sym->ns);
2434
2435       if (ts->type == BT_UNKNOWN)
2436         {
2437           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2438                      sym->name, &expr->where);
2439           return FAILURE;
2440         }
2441       else
2442         expr->ts = *ts;
2443     }
2444
2445   return SUCCESS;
2446 }
2447
2448
2449 /* Return true, if the symbol is an external procedure.  */
2450 static bool
2451 is_external_proc (gfc_symbol *sym)
2452 {
2453   if (!sym->attr.dummy && !sym->attr.contained
2454         && !(sym->attr.intrinsic
2455               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2456         && sym->attr.proc != PROC_ST_FUNCTION
2457         && !sym->attr.proc_pointer
2458         && !sym->attr.use_assoc
2459         && sym->name)
2460     return true;
2461
2462   return false;
2463 }
2464
2465
2466 /* Figure out if a function reference is pure or not.  Also set the name
2467    of the function for a potential error message.  Return nonzero if the
2468    function is PURE, zero if not.  */
2469 static int
2470 pure_stmt_function (gfc_expr *, gfc_symbol *);
2471
2472 static int
2473 pure_function (gfc_expr *e, const char **name)
2474 {
2475   int pure;
2476
2477   *name = NULL;
2478
2479   if (e->symtree != NULL
2480         && e->symtree->n.sym != NULL
2481         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2482     return pure_stmt_function (e, e->symtree->n.sym);
2483
2484   if (e->value.function.esym)
2485     {
2486       pure = gfc_pure (e->value.function.esym);
2487       *name = e->value.function.esym->name;
2488     }
2489   else if (e->value.function.isym)
2490     {
2491       pure = e->value.function.isym->pure
2492              || e->value.function.isym->elemental;
2493       *name = e->value.function.isym->name;
2494     }
2495   else
2496     {
2497       /* Implicit functions are not pure.  */
2498       pure = 0;
2499       *name = e->value.function.name;
2500     }
2501
2502   return pure;
2503 }
2504
2505
2506 static bool
2507 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2508                  int *f ATTRIBUTE_UNUSED)
2509 {
2510   const char *name;
2511
2512   /* Don't bother recursing into other statement functions
2513      since they will be checked individually for purity.  */
2514   if (e->expr_type != EXPR_FUNCTION
2515         || !e->symtree
2516         || e->symtree->n.sym == sym
2517         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2518     return false;
2519
2520   return pure_function (e, &name) ? false : true;
2521 }
2522
2523
2524 static int
2525 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2526 {
2527   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2528 }
2529
2530
2531 static gfc_try
2532 is_scalar_expr_ptr (gfc_expr *expr)
2533 {
2534   gfc_try retval = SUCCESS;
2535   gfc_ref *ref;
2536   int start;
2537   int end;
2538
2539   /* See if we have a gfc_ref, which means we have a substring, array
2540      reference, or a component.  */
2541   if (expr->ref != NULL)
2542     {
2543       ref = expr->ref;
2544       while (ref->next != NULL)
2545         ref = ref->next;
2546
2547       switch (ref->type)
2548         {
2549         case REF_SUBSTRING:
2550           if (ref->u.ss.length != NULL 
2551               && ref->u.ss.length->length != NULL
2552               && ref->u.ss.start
2553               && ref->u.ss.start->expr_type == EXPR_CONSTANT 
2554               && ref->u.ss.end
2555               && ref->u.ss.end->expr_type == EXPR_CONSTANT)
2556             {
2557               start = (int) mpz_get_si (ref->u.ss.start->value.integer);
2558               end = (int) mpz_get_si (ref->u.ss.end->value.integer);
2559               if (end - start + 1 != 1)
2560                 retval = FAILURE;
2561             }
2562           else
2563             retval = FAILURE;
2564           break;
2565         case REF_ARRAY:
2566           if (ref->u.ar.type == AR_ELEMENT)
2567             retval = SUCCESS;
2568           else if (ref->u.ar.type == AR_FULL)
2569             {
2570               /* The user can give a full array if the array is of size 1.  */
2571               if (ref->u.ar.as != NULL
2572                   && ref->u.ar.as->rank == 1
2573                   && ref->u.ar.as->type == AS_EXPLICIT
2574                   && ref->u.ar.as->lower[0] != NULL
2575                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2576                   && ref->u.ar.as->upper[0] != NULL
2577                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2578                 {
2579                   /* If we have a character string, we need to check if
2580                      its length is one.  */
2581                   if (expr->ts.type == BT_CHARACTER)
2582                     {
2583                       if (expr->ts.u.cl == NULL
2584                           || expr->ts.u.cl->length == NULL
2585                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2586                           != 0)
2587                         retval = FAILURE;
2588                     }
2589                   else
2590                     {
2591                       /* We have constant lower and upper bounds.  If the
2592                          difference between is 1, it can be considered a
2593                          scalar.  */
2594                       start = (int) mpz_get_si
2595                                 (ref->u.ar.as->lower[0]->value.integer);
2596                       end = (int) mpz_get_si
2597                                 (ref->u.ar.as->upper[0]->value.integer);
2598                       if (end - start + 1 != 1)
2599                         retval = FAILURE;
2600                    }
2601                 }
2602               else
2603                 retval = FAILURE;
2604             }
2605           else
2606             retval = FAILURE;
2607           break;
2608         default:
2609           retval = SUCCESS;
2610           break;
2611         }
2612     }
2613   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2614     {
2615       /* Character string.  Make sure it's of length 1.  */
2616       if (expr->ts.u.cl == NULL
2617           || expr->ts.u.cl->length == NULL
2618           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2619         retval = FAILURE;
2620     }
2621   else if (expr->rank != 0)
2622     retval = FAILURE;
2623
2624   return retval;
2625 }
2626
2627
2628 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2629    and, in the case of c_associated, set the binding label based on
2630    the arguments.  */
2631
2632 static gfc_try
2633 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2634                           gfc_symbol **new_sym)
2635 {
2636   char name[GFC_MAX_SYMBOL_LEN + 1];
2637   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2638   int optional_arg = 0;
2639   gfc_try retval = SUCCESS;
2640   gfc_symbol *args_sym;
2641   gfc_typespec *arg_ts;
2642   symbol_attribute arg_attr;
2643
2644   if (args->expr->expr_type == EXPR_CONSTANT
2645       || args->expr->expr_type == EXPR_OP
2646       || args->expr->expr_type == EXPR_NULL)
2647     {
2648       gfc_error ("Argument to '%s' at %L is not a variable",
2649                  sym->name, &(args->expr->where));
2650       return FAILURE;
2651     }
2652
2653   args_sym = args->expr->symtree->n.sym;
2654
2655   /* The typespec for the actual arg should be that stored in the expr
2656      and not necessarily that of the expr symbol (args_sym), because
2657      the actual expression could be a part-ref of the expr symbol.  */
2658   arg_ts = &(args->expr->ts);
2659   arg_attr = gfc_expr_attr (args->expr);
2660     
2661   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2662     {
2663       /* If the user gave two args then they are providing something for
2664          the optional arg (the second cptr).  Therefore, set the name and
2665          binding label to the c_associated for two cptrs.  Otherwise,
2666          set c_associated to expect one cptr.  */
2667       if (args->next)
2668         {
2669           /* two args.  */
2670           sprintf (name, "%s_2", sym->name);
2671           sprintf (binding_label, "%s_2", sym->binding_label);
2672           optional_arg = 1;
2673         }
2674       else
2675         {
2676           /* one arg.  */
2677           sprintf (name, "%s_1", sym->name);
2678           sprintf (binding_label, "%s_1", sym->binding_label);
2679           optional_arg = 0;
2680         }
2681
2682       /* Get a new symbol for the version of c_associated that
2683          will get called.  */
2684       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2685     }
2686   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2687            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2688     {
2689       sprintf (name, "%s", sym->name);
2690       sprintf (binding_label, "%s", sym->binding_label);
2691
2692       /* Error check the call.  */
2693       if (args->next != NULL)
2694         {
2695           gfc_error_now ("More actual than formal arguments in '%s' "
2696                          "call at %L", name, &(args->expr->where));
2697           retval = FAILURE;
2698         }
2699       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2700         {
2701           /* Make sure we have either the target or pointer attribute.  */
2702           if (!arg_attr.target && !arg_attr.pointer)
2703             {
2704               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2705                              "a TARGET or an associated pointer",
2706                              args_sym->name,
2707                              sym->name, &(args->expr->where));
2708               retval = FAILURE;
2709             }
2710
2711           /* See if we have interoperable type and type param.  */
2712           if (verify_c_interop (arg_ts) == SUCCESS
2713               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2714             {
2715               if (args_sym->attr.target == 1)
2716                 {
2717                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2718                      has the target attribute and is interoperable.  */
2719                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2720                      allocatable variable that has the TARGET attribute and
2721                      is not an array of zero size.  */
2722                   if (args_sym->attr.allocatable == 1)
2723                     {
2724                       if (args_sym->attr.dimension != 0 
2725                           && (args_sym->as && args_sym->as->rank == 0))
2726                         {
2727                           gfc_error_now ("Allocatable variable '%s' used as a "
2728                                          "parameter to '%s' at %L must not be "
2729                                          "an array of zero size",
2730                                          args_sym->name, sym->name,
2731                                          &(args->expr->where));
2732                           retval = FAILURE;
2733                         }
2734                     }
2735                   else
2736                     {
2737                       /* A non-allocatable target variable with C
2738                          interoperable type and type parameters must be
2739                          interoperable.  */
2740                       if (args_sym && args_sym->attr.dimension)
2741                         {
2742                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2743                             {
2744                               gfc_error ("Assumed-shape array '%s' at %L "
2745                                          "cannot be an argument to the "
2746                                          "procedure '%s' because "
2747                                          "it is not C interoperable",
2748                                          args_sym->name,
2749                                          &(args->expr->where), sym->name);
2750                               retval = FAILURE;
2751                             }
2752                           else if (args_sym->as->type == AS_DEFERRED)
2753                             {
2754                               gfc_error ("Deferred-shape array '%s' at %L "
2755                                          "cannot be an argument to the "
2756                                          "procedure '%s' because "
2757                                          "it is not C interoperable",
2758                                          args_sym->name,
2759                                          &(args->expr->where), sym->name);
2760                               retval = FAILURE;
2761                             }
2762                         }
2763                               
2764                       /* Make sure it's not a character string.  Arrays of
2765                          any type should be ok if the variable is of a C
2766                          interoperable type.  */
2767                       if (arg_ts->type == BT_CHARACTER)
2768                         if (arg_ts->u.cl != NULL
2769                             && (arg_ts->u.cl->length == NULL
2770                                 || arg_ts->u.cl->length->expr_type
2771                                    != EXPR_CONSTANT
2772                                 || mpz_cmp_si
2773                                     (arg_ts->u.cl->length->value.integer, 1)
2774                                    != 0)
2775                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2776                           {
2777                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2778                                            "at %L must have a length of 1",
2779                                            args_sym->name, sym->name,
2780                                            &(args->expr->where));
2781                             retval = FAILURE;
2782                           }
2783                     }
2784                 }
2785               else if (arg_attr.pointer
2786                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2787                 {
2788                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2789                      scalar pointer.  */
2790                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2791                                  "associated scalar POINTER", args_sym->name,
2792                                  sym->name, &(args->expr->where));
2793                   retval = FAILURE;
2794                 }
2795             }
2796           else
2797             {
2798               /* The parameter is not required to be C interoperable.  If it
2799                  is not C interoperable, it must be a nonpolymorphic scalar
2800                  with no length type parameters.  It still must have either
2801                  the pointer or target attribute, and it can be
2802                  allocatable (but must be allocated when c_loc is called).  */
2803               if (args->expr->rank != 0 
2804                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2805                 {
2806                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2807                                  "scalar", args_sym->name, sym->name,
2808                                  &(args->expr->where));
2809                   retval = FAILURE;
2810                 }
2811               else if (arg_ts->type == BT_CHARACTER 
2812                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2813                 {
2814                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2815                                  "%L must have a length of 1",
2816                                  args_sym->name, sym->name,
2817                                  &(args->expr->where));
2818                   retval = FAILURE;
2819                 }
2820               else if (arg_ts->type == BT_CLASS)
2821                 {
2822                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
2823                                  "polymorphic", args_sym->name, sym->name,
2824                                  &(args->expr->where));
2825                   retval = FAILURE;
2826                 }
2827             }
2828         }
2829       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2830         {
2831           if (args_sym->attr.flavor != FL_PROCEDURE)
2832             {
2833               /* TODO: Update this error message to allow for procedure
2834                  pointers once they are implemented.  */
2835               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2836                              "procedure",
2837                              args_sym->name, sym->name,
2838                              &(args->expr->where));
2839               retval = FAILURE;
2840             }
2841           else if (args_sym->attr.is_bind_c != 1)
2842             {
2843               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2844                              "BIND(C)",
2845                              args_sym->name, sym->name,
2846                              &(args->expr->where));
2847               retval = FAILURE;
2848             }
2849         }
2850       
2851       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2852       *new_sym = sym;
2853     }
2854   else
2855     {
2856       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2857                           "iso_c_binding function: '%s'!\n", sym->name);
2858     }
2859
2860   return retval;
2861 }
2862
2863
2864 /* Resolve a function call, which means resolving the arguments, then figuring
2865    out which entity the name refers to.  */
2866
2867 static gfc_try
2868 resolve_function (gfc_expr *expr)
2869 {
2870   gfc_actual_arglist *arg;
2871   gfc_symbol *sym;
2872   const char *name;
2873   gfc_try t;
2874   int temp;
2875   procedure_type p = PROC_INTRINSIC;
2876   bool no_formal_args;
2877
2878   sym = NULL;
2879   if (expr->symtree)
2880     sym = expr->symtree->n.sym;
2881
2882   /* If this is a procedure pointer component, it has already been resolved.  */
2883   if (gfc_is_proc_ptr_comp (expr, NULL))
2884     return SUCCESS;
2885   
2886   if (sym && sym->attr.intrinsic
2887       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2888     return FAILURE;
2889
2890   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2891     {
2892       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2893       return FAILURE;
2894     }
2895
2896   /* If this ia a deferred TBP with an abstract interface (which may
2897      of course be referenced), expr->value.function.esym will be set.  */
2898   if (sym && sym->attr.abstract && !expr->value.function.esym)
2899     {
2900       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2901                  sym->name, &expr->where);
2902       return FAILURE;
2903     }
2904
2905   /* Switch off assumed size checking and do this again for certain kinds
2906      of procedure, once the procedure itself is resolved.  */
2907   need_full_assumed_size++;
2908
2909   if (expr->symtree && expr->symtree->n.sym)
2910     p = expr->symtree->n.sym->attr.proc;
2911
2912   if (expr->value.function.isym && expr->value.function.isym->inquiry)
2913     inquiry_argument = true;
2914   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2915
2916   if (resolve_actual_arglist (expr->value.function.actual,
2917                               p, no_formal_args) == FAILURE)
2918     {
2919       inquiry_argument = false;
2920       return FAILURE;
2921     }
2922
2923   inquiry_argument = false;
2924  
2925   /* Need to setup the call to the correct c_associated, depending on
2926      the number of cptrs to user gives to compare.  */
2927   if (sym && sym->attr.is_iso_c == 1)
2928     {
2929       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2930           == FAILURE)
2931         return FAILURE;
2932       
2933       /* Get the symtree for the new symbol (resolved func).
2934          the old one will be freed later, when it's no longer used.  */
2935       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2936     }
2937   
2938   /* Resume assumed_size checking.  */
2939   need_full_assumed_size--;
2940
2941   /* If the procedure is external, check for usage.  */
2942   if (sym && is_external_proc (sym))
2943     resolve_global_procedure (sym, &expr->where,
2944                               &expr->value.function.actual, 0);
2945
2946   if (sym && sym->ts.type == BT_CHARACTER
2947       && sym->ts.u.cl
2948       && sym->ts.u.cl->length == NULL
2949       && !sym->attr.dummy
2950       && expr->value.function.esym == NULL
2951       && !sym->attr.contained)
2952     {
2953       /* Internal procedures are taken care of in resolve_contained_fntype.  */
2954       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2955                  "be used at %L since it is not a dummy argument",
2956                  sym->name, &expr->where);
2957       return FAILURE;
2958     }
2959
2960   /* See if function is already resolved.  */
2961
2962   if (expr->value.function.name != NULL)
2963     {
2964       if (expr->ts.type == BT_UNKNOWN)
2965         expr->ts = sym->ts;
2966       t = SUCCESS;
2967     }
2968   else
2969     {
2970       /* Apply the rules of section 14.1.2.  */
2971
2972       switch (procedure_kind (sym))
2973         {
2974         case PTYPE_GENERIC:
2975           t = resolve_generic_f (expr);
2976           break;
2977
2978         case PTYPE_SPECIFIC:
2979           t = resolve_specific_f (expr);
2980           break;
2981
2982         case PTYPE_UNKNOWN:
2983           t = resolve_unknown_f (expr);
2984           break;
2985
2986         default:
2987           gfc_internal_error ("resolve_function(): bad function type");
2988         }
2989     }
2990
2991   /* If the expression is still a function (it might have simplified),
2992      then we check to see if we are calling an elemental function.  */
2993
2994   if (expr->expr_type != EXPR_FUNCTION)
2995     return t;
2996
2997   temp = need_full_assumed_size;
2998   need_full_assumed_size = 0;
2999
3000   if (resolve_elemental_actual (expr, NULL) == FAILURE)
3001     return FAILURE;
3002
3003   if (omp_workshare_flag
3004       && expr->value.function.esym
3005       && ! gfc_elemental (expr->value.function.esym))
3006     {
3007       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
3008                  "in WORKSHARE construct", expr->value.function.esym->name,
3009                  &expr->where);
3010       t = FAILURE;
3011     }
3012
3013 #define GENERIC_ID expr->value.function.isym->id
3014   else if (expr->value.function.actual != NULL
3015            && expr->value.function.isym != NULL
3016            && GENERIC_ID != GFC_ISYM_LBOUND
3017            && GENERIC_ID != GFC_ISYM_LEN
3018            && GENERIC_ID != GFC_ISYM_LOC
3019            && GENERIC_ID != GFC_ISYM_PRESENT)
3020     {
3021       /* Array intrinsics must also have the last upper bound of an
3022          assumed size array argument.  UBOUND and SIZE have to be
3023          excluded from the check if the second argument is anything
3024          than a constant.  */
3025
3026       for (arg = expr->value.function.actual; arg; arg = arg->next)
3027         {
3028           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3029               && arg->next != NULL && arg->next->expr)
3030             {
3031               if (arg->next->expr->expr_type != EXPR_CONSTANT)
3032                 break;
3033
3034               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
3035                 break;
3036
3037               if ((int)mpz_get_si (arg->next->expr->value.integer)
3038                         < arg->expr->rank)
3039                 break;
3040             }
3041
3042           if (arg->expr != NULL
3043               && arg->expr->rank > 0
3044               && resolve_assumed_size_actual (arg->expr))
3045             return FAILURE;
3046         }
3047     }
3048 #undef GENERIC_ID
3049
3050   need_full_assumed_size = temp;
3051   name = NULL;
3052
3053   if (!pure_function (expr, &name) && name)
3054     {
3055       if (forall_flag)
3056         {
3057           gfc_error ("reference to non-PURE function '%s' at %L inside a "
3058                      "FORALL %s", name, &expr->where,
3059                      forall_flag == 2 ? "mask" : "block");
3060           t = FAILURE;
3061         }
3062       else if (gfc_pure (NULL))
3063         {
3064           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
3065                      "procedure within a PURE procedure", name, &expr->where);
3066           t = FAILURE;
3067         }
3068     }
3069
3070   /* Functions without the RECURSIVE attribution are not allowed to
3071    * call themselves.  */
3072   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3073     {
3074       gfc_symbol *esym;
3075       esym = expr->value.function.esym;
3076
3077       if (is_illegal_recursion (esym, gfc_current_ns))
3078       {
3079         if (esym->attr.entry && esym->ns->entries)
3080           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3081                      " function '%s' is not RECURSIVE",
3082                      esym->name, &expr->where, esym->ns->entries->sym->name);
3083         else
3084           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
3085                      " is not RECURSIVE", esym->name, &expr->where);
3086
3087         t = FAILURE;
3088       }
3089     }
3090
3091   /* Character lengths of use associated functions may contains references to
3092      symbols not referenced from the current program unit otherwise.  Make sure
3093      those symbols are marked as referenced.  */
3094
3095   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3096       && expr->value.function.esym->attr.use_assoc)
3097     {
3098       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3099     }
3100
3101   /* Make sure that the expression has a typespec that works.  */
3102   if (expr->ts.type == BT_UNKNOWN)
3103     {
3104       if (expr->symtree->n.sym->result
3105             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3106             && !expr->symtree->n.sym->result->attr.proc_pointer)
3107         expr->ts = expr->symtree->n.sym->result->ts;
3108     }
3109
3110   return t;
3111 }
3112
3113
3114 /************* Subroutine resolution *************/
3115
3116 static void
3117 pure_subroutine (gfc_code *c, gfc_symbol *sym)
3118 {
3119   if (gfc_pure (sym))
3120     return;
3121
3122   if (forall_flag)
3123     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
3124                sym->name, &c->loc);
3125   else if (gfc_pure (NULL))
3126     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
3127                &c->loc);
3128 }
3129
3130
3131 static match
3132 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3133 {
3134   gfc_symbol *s;
3135
3136   if (sym->attr.generic)
3137     {
3138       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3139       if (s != NULL)
3140         {
3141           c->resolved_sym = s;
3142           pure_subroutine (c, s);
3143           return MATCH_YES;
3144         }
3145
3146       /* TODO: Need to search for elemental references in generic interface.  */
3147     }
3148
3149   if (sym->attr.intrinsic)
3150     return gfc_intrinsic_sub_interface (c, 0);
3151
3152   return MATCH_NO;
3153 }
3154
3155
3156 static gfc_try
3157 resolve_generic_s (gfc_code *c)
3158 {
3159   gfc_symbol *sym;
3160   match m;
3161
3162   sym = c->symtree->n.sym;
3163
3164   for (;;)
3165     {
3166       m = resolve_generic_s0 (c, sym);
3167       if (m == MATCH_YES)
3168         return SUCCESS;
3169       else if (m == MATCH_ERROR)
3170         return FAILURE;
3171
3172 generic:
3173       if (sym->ns->parent == NULL)
3174         break;
3175       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3176
3177       if (sym == NULL)
3178         break;
3179       if (!generic_sym (sym))
3180         goto generic;
3181     }
3182
3183   /* Last ditch attempt.  See if the reference is to an intrinsic
3184      that possesses a matching interface.  14.1.2.4  */
3185   sym = c->symtree->n.sym;
3186
3187   if (!gfc_is_intrinsic (sym, 1, c->loc))
3188     {
3189       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3190                  sym->name, &c->loc);
3191       return FAILURE;
3192     }
3193
3194   m = gfc_intrinsic_sub_interface (c, 0);
3195   if (m == MATCH_YES)
3196     return SUCCESS;
3197   if (m == MATCH_NO)
3198     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3199                "intrinsic subroutine interface", sym->name, &c->loc);
3200
3201   return FAILURE;
3202 }
3203
3204
3205 /* Set the name and binding label of the subroutine symbol in the call
3206    expression represented by 'c' to include the type and kind of the
3207    second parameter.  This function is for resolving the appropriate
3208    version of c_f_pointer() and c_f_procpointer().  For example, a
3209    call to c_f_pointer() for a default integer pointer could have a
3210    name of c_f_pointer_i4.  If no second arg exists, which is an error
3211    for these two functions, it defaults to the generic symbol's name
3212    and binding label.  */
3213
3214 static void
3215 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3216                     char *name, char *binding_label)
3217 {
3218   gfc_expr *arg = NULL;
3219   char type;
3220   int kind;
3221
3222   /* The second arg of c_f_pointer and c_f_procpointer determines
3223      the type and kind for the procedure name.  */
3224   arg = c->ext.actual->next->expr;
3225
3226   if (arg != NULL)
3227     {
3228       /* Set up the name to have the given symbol's name,
3229          plus the type and kind.  */
3230       /* a derived type is marked with the type letter 'u' */
3231       if (arg->ts.type == BT_DERIVED)
3232         {
3233           type = 'd';
3234           kind = 0; /* set the kind as 0 for now */
3235         }
3236       else
3237         {
3238           type = gfc_type_letter (arg->ts.type);
3239           kind = arg->ts.kind;
3240         }
3241
3242       if (arg->ts.type == BT_CHARACTER)
3243         /* Kind info for character strings not needed.  */
3244         kind = 0;
3245
3246       sprintf (name, "%s_%c%d", sym->name, type, kind);
3247       /* Set up the binding label as the given symbol's label plus
3248          the type and kind.  */
3249       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
3250     }
3251   else
3252     {
3253       /* If the second arg is missing, set the name and label as
3254          was, cause it should at least be found, and the missing
3255          arg error will be caught by compare_parameters().  */
3256       sprintf (name, "%s", sym->name);
3257       sprintf (binding_label, "%s", sym->binding_label);
3258     }
3259    
3260   return;
3261 }
3262
3263
3264 /* Resolve a generic version of the iso_c_binding procedure given
3265    (sym) to the specific one based on the type and kind of the
3266    argument(s).  Currently, this function resolves c_f_pointer() and
3267    c_f_procpointer based on the type and kind of the second argument
3268    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3269    Upon successfully exiting, c->resolved_sym will hold the resolved
3270    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3271    otherwise.  */
3272
3273 match
3274 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3275 {
3276   gfc_symbol *new_sym;
3277   /* this is fine, since we know the names won't use the max */
3278   char name[GFC_MAX_SYMBOL_LEN + 1];
3279   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3280   /* default to success; will override if find error */
3281   match m = MATCH_YES;
3282
3283   /* Make sure the actual arguments are in the necessary order (based on the 
3284      formal args) before resolving.  */
3285   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3286
3287   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3288       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3289     {
3290       set_name_and_label (c, sym, name, binding_label);
3291       
3292       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3293         {
3294           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3295             {
3296               /* Make sure we got a third arg if the second arg has non-zero
3297                  rank.  We must also check that the type and rank are
3298                  correct since we short-circuit this check in
3299                  gfc_procedure_use() (called above to sort actual args).  */
3300               if (c->ext.actual->next->expr->rank != 0)
3301                 {
3302                   if(c->ext.actual->next->next == NULL 
3303                      || c->ext.actual->next->next->expr == NULL)
3304                     {
3305                       m = MATCH_ERROR;
3306                       gfc_error ("Missing SHAPE parameter for call to %s "
3307                                  "at %L", sym->name, &(c->loc));
3308                     }
3309                   else if (c->ext.actual->next->next->expr->ts.type
3310                            != BT_INTEGER
3311                            || c->ext.actual->next->next->expr->rank != 1)
3312                     {
3313                       m = MATCH_ERROR;
3314                       gfc_error ("SHAPE parameter for call to %s at %L must "
3315                                  "be a rank 1 INTEGER array", sym->name,
3316                                  &(c->loc));
3317                     }
3318                 }
3319             }
3320         }
3321       
3322       if (m != MATCH_ERROR)
3323         {
3324           /* the 1 means to add the optional arg to formal list */
3325           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3326          
3327           /* for error reporting, say it's declared where the original was */
3328           new_sym->declared_at = sym->declared_at;
3329         }
3330     }
3331   else
3332     {
3333       /* no differences for c_loc or c_funloc */
3334       new_sym = sym;
3335     }
3336
3337   /* set the resolved symbol */
3338   if (m != MATCH_ERROR)
3339     c->resolved_sym = new_sym;
3340   else
3341     c->resolved_sym = sym;
3342   
3343   return m;
3344 }
3345
3346
3347 /* Resolve a subroutine call known to be specific.  */
3348
3349 static match
3350 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3351 {
3352   match m;
3353
3354   if(sym->attr.is_iso_c)
3355     {
3356       m = gfc_iso_c_sub_interface (c,sym);
3357       return m;
3358     }
3359   
3360   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3361     {
3362       if (sym->attr.dummy)
3363         {
3364           sym->attr.proc = PROC_DUMMY;
3365           goto found;
3366         }
3367
3368       sym->attr.proc = PROC_EXTERNAL;
3369       goto found;
3370     }
3371
3372   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3373     goto found;
3374
3375   if (sym->attr.intrinsic)
3376     {
3377       m = gfc_intrinsic_sub_interface (c, 1);
3378       if (m == MATCH_YES)
3379         return MATCH_YES;
3380       if (m == MATCH_NO)
3381         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3382                    "with an intrinsic", sym->name, &c->loc);
3383
3384       return MATCH_ERROR;
3385     }
3386
3387   return MATCH_NO;
3388
3389 found:
3390   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3391
3392   c->resolved_sym = sym;
3393   pure_subroutine (c, sym);
3394
3395   return MATCH_YES;
3396 }
3397
3398
3399 static gfc_try
3400 resolve_specific_s (gfc_code *c)
3401 {
3402   gfc_symbol *sym;
3403   match m;
3404
3405   sym = c->symtree->n.sym;
3406
3407   for (;;)
3408     {
3409       m = resolve_specific_s0 (c, sym);
3410       if (m == MATCH_YES)
3411         return SUCCESS;
3412       if (m == MATCH_ERROR)
3413         return FAILURE;
3414
3415       if (sym->ns->parent == NULL)
3416         break;
3417
3418       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3419
3420       if (sym == NULL)
3421         break;
3422     }
3423
3424   sym = c->symtree->n.sym;
3425   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3426              sym->name, &c->loc);
3427
3428   return FAILURE;
3429 }
3430
3431
3432 /* Resolve a subroutine call not known to be generic nor specific.  */
3433
3434 static gfc_try
3435 resolve_unknown_s (gfc_code *c)
3436 {
3437   gfc_symbol *sym;
3438
3439   sym = c->symtree->n.sym;
3440
3441   if (sym->attr.dummy)
3442     {
3443       sym->attr.proc = PROC_DUMMY;
3444       goto found;
3445     }
3446
3447   /* See if we have an intrinsic function reference.  */
3448
3449   if (gfc_is_intrinsic (sym, 1, c->loc))
3450     {
3451       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3452         return SUCCESS;
3453       return FAILURE;
3454     }
3455
3456   /* The reference is to an external name.  */
3457
3458 found:
3459   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3460
3461   c->resolved_sym = sym;
3462
3463   pure_subroutine (c, sym);
3464
3465   return SUCCESS;
3466 }
3467
3468
3469 /* Resolve a subroutine call.  Although it was tempting to use the same code
3470    for functions, subroutines and functions are stored differently and this
3471    makes things awkward.  */
3472
3473 static gfc_try
3474 resolve_call (gfc_code *c)
3475 {
3476   gfc_try t;
3477   procedure_type ptype = PROC_INTRINSIC;
3478   gfc_symbol *csym, *sym;
3479   bool no_formal_args;
3480
3481   csym = c->symtree ? c->symtree->n.sym : NULL;
3482
3483   if (csym && csym->ts.type != BT_UNKNOWN)
3484     {
3485       gfc_error ("'%s' at %L has a type, which is not consistent with "
3486                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3487       return FAILURE;
3488     }
3489
3490   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3491     {
3492       gfc_symtree *st;
3493       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3494       sym = st ? st->n.sym : NULL;
3495       if (sym && csym != sym
3496               && sym->ns == gfc_current_ns
3497               && sym->attr.flavor == FL_PROCEDURE
3498               && sym->attr.contained)
3499         {
3500           sym->refs++;
3501           if (csym->attr.generic)
3502             c->symtree->n.sym = sym;
3503           else
3504             c->symtree = st;
3505           csym = c->symtree->n.sym;
3506         }
3507     }
3508
3509   /* If this ia a deferred TBP with an abstract interface
3510      (which may of course be referenced), c->expr1 will be set.  */
3511   if (csym && csym->attr.abstract && !c->expr1)
3512     {
3513       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3514                  csym->name, &c->loc);
3515       return FAILURE;
3516     }
3517
3518   /* Subroutines without the RECURSIVE attribution are not allowed to
3519    * call themselves.  */
3520   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3521     {
3522       if (csym->attr.entry && csym->ns->entries)
3523         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3524                    " subroutine '%s' is not RECURSIVE",
3525                    csym->name, &c->loc, csym->ns->entries->sym->name);
3526       else
3527         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3528                    " is not RECURSIVE", csym->name, &c->loc);
3529
3530       t = FAILURE;
3531     }
3532
3533   /* Switch off assumed size checking and do this again for certain kinds
3534      of procedure, once the procedure itself is resolved.  */
3535   need_full_assumed_size++;
3536
3537   if (csym)
3538     ptype = csym->attr.proc;
3539
3540   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3541   if (resolve_actual_arglist (c->ext.actual, ptype,
3542                               no_formal_args) == FAILURE)
3543     return FAILURE;
3544
3545   /* Resume assumed_size checking.  */
3546   need_full_assumed_size--;
3547
3548   /* If external, check for usage.  */
3549   if (csym && is_external_proc (csym))
3550     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3551
3552   t = SUCCESS;
3553   if (c->resolved_sym == NULL)
3554     {
3555       c->resolved_isym = NULL;
3556       switch (procedure_kind (csym))
3557         {
3558         case PTYPE_GENERIC:
3559           t = resolve_generic_s (c);
3560           break;
3561
3562         case PTYPE_SPECIFIC:
3563           t = resolve_specific_s (c);
3564           break;
3565
3566         case PTYPE_UNKNOWN:
3567           t = resolve_unknown_s (c);
3568           break;
3569
3570         default:
3571           gfc_internal_error ("resolve_subroutine(): bad function type");
3572         }
3573     }
3574
3575   /* Some checks of elemental subroutine actual arguments.  */
3576   if (resolve_elemental_actual (NULL, c) == FAILURE)
3577     return FAILURE;
3578
3579   return t;
3580 }
3581
3582
3583 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3584    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3585    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3586    if their shapes do not match.  If either op1->shape or op2->shape is
3587    NULL, return SUCCESS.  */
3588
3589 static gfc_try
3590 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3591 {
3592   gfc_try t;
3593   int i;
3594
3595   t = SUCCESS;
3596
3597   if (op1->shape != NULL && op2->shape != NULL)
3598     {
3599       for (i = 0; i < op1->rank; i++)
3600         {
3601           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3602            {
3603              gfc_error ("Shapes for operands at %L and %L are not conformable",
3604                          &op1->where, &op2->where);
3605              t = FAILURE;
3606              break;
3607            }
3608         }
3609     }
3610
3611   return t;
3612 }
3613
3614
3615 /* Resolve an operator expression node.  This can involve replacing the
3616    operation with a user defined function call.  */
3617
3618 static gfc_try
3619 resolve_operator (gfc_expr *e)
3620 {
3621   gfc_expr *op1, *op2;
3622   char msg[200];
3623   bool dual_locus_error;
3624   gfc_try t;
3625
3626   /* Resolve all subnodes-- give them types.  */
3627
3628   switch (e->value.op.op)
3629     {
3630     default:
3631       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3632         return FAILURE;
3633
3634     /* Fall through...  */
3635
3636     case INTRINSIC_NOT:
3637     case INTRINSIC_UPLUS:
3638     case INTRINSIC_UMINUS:
3639     case INTRINSIC_PARENTHESES:
3640       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3641         return FAILURE;
3642       break;
3643     }
3644
3645   /* Typecheck the new node.  */
3646
3647   op1 = e->value.op.op1;
3648   op2 = e->value.op.op2;
3649   dual_locus_error = false;
3650
3651   if ((op1 && op1->expr_type == EXPR_NULL)
3652       || (op2 && op2->expr_type == EXPR_NULL))
3653     {
3654       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3655       goto bad_op;
3656     }
3657
3658   switch (e->value.op.op)
3659     {
3660     case INTRINSIC_UPLUS:
3661     case INTRINSIC_UMINUS:
3662       if (op1->ts.type == BT_INTEGER
3663           || op1->ts.type == BT_REAL
3664           || op1->ts.type == BT_COMPLEX)
3665         {
3666           e->ts = op1->ts;
3667           break;
3668         }
3669
3670       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3671                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3672       goto bad_op;
3673
3674     case INTRINSIC_PLUS:
3675     case INTRINSIC_MINUS:
3676     case INTRINSIC_TIMES:
3677     case INTRINSIC_DIVIDE:
3678     case INTRINSIC_POWER:
3679       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3680         {
3681           gfc_type_convert_binary (e, 1);
3682           break;
3683         }
3684
3685       sprintf (msg,
3686                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3687                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3688                gfc_typename (&op2->ts));
3689       goto bad_op;
3690
3691     case INTRINSIC_CONCAT:
3692       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3693           && op1->ts.kind == op2->ts.kind)
3694         {
3695           e->ts.type = BT_CHARACTER;
3696           e->ts.kind = op1->ts.kind;
3697           break;
3698         }
3699
3700       sprintf (msg,
3701                _("Operands of string concatenation operator at %%L are %s/%s"),
3702                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3703       goto bad_op;
3704
3705     case INTRINSIC_AND:
3706     case INTRINSIC_OR:
3707     case INTRINSIC_EQV:
3708     case INTRINSIC_NEQV:
3709       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3710         {
3711           e->ts.type = BT_LOGICAL;
3712           e->ts.kind = gfc_kind_max (op1, op2);
3713           if (op1->ts.kind < e->ts.kind)
3714             gfc_convert_type (op1, &e->ts, 2);
3715           else if (op2->ts.kind < e->ts.kind)
3716             gfc_convert_type (op2, &e->ts, 2);
3717           break;
3718         }
3719
3720       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3721                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3722                gfc_typename (&op2->ts));
3723
3724       goto bad_op;
3725
3726     case INTRINSIC_NOT:
3727       if (op1->ts.type == BT_LOGICAL)
3728         {
3729           e->ts.type = BT_LOGICAL;
3730           e->ts.kind = op1->ts.kind;
3731           break;
3732         }
3733
3734       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3735                gfc_typename (&op1->ts));
3736       goto bad_op;
3737
3738     case INTRINSIC_GT:
3739     case INTRINSIC_GT_OS:
3740     case INTRINSIC_GE:
3741     case INTRINSIC_GE_OS:
3742     case INTRINSIC_LT:
3743     case INTRINSIC_LT_OS:
3744     case INTRINSIC_LE:
3745     case INTRINSIC_LE_OS:
3746       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3747         {
3748           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3749           goto bad_op;
3750         }
3751
3752       /* Fall through...  */
3753
3754     case INTRINSIC_EQ:
3755     case INTRINSIC_EQ_OS:
3756     case INTRINSIC_NE:
3757     case INTRINSIC_NE_OS:
3758       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3759           && op1->ts.kind == op2->ts.kind)
3760         {
3761           e->ts.type = BT_LOGICAL;
3762           e->ts.kind = gfc_default_logical_kind;
3763           break;
3764         }
3765
3766       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3767         {
3768           gfc_type_convert_binary (e, 1);
3769
3770           e->ts.type = BT_LOGICAL;
3771           e->ts.kind = gfc_default_logical_kind;
3772           break;
3773         }
3774
3775       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3776         sprintf (msg,
3777                  _("Logicals at %%L must be compared with %s instead of %s"),
3778                  (e->value.op.op == INTRINSIC_EQ 
3779                   || e->value.op.op == INTRINSIC_EQ_OS)
3780                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3781       else
3782         sprintf (msg,
3783                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3784                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3785                  gfc_typename (&op2->ts));
3786
3787       goto bad_op;
3788
3789     case INTRINSIC_USER:
3790       if (e->value.op.uop->op == NULL)
3791         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3792       else if (op2 == NULL)
3793         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3794                  e->value.op.uop->name, gfc_typename (&op1->ts));
3795       else
3796         sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3797                  e->value.op.uop->name, gfc_typename (&op1->ts),
3798                  gfc_typename (&op2->ts));
3799
3800       goto bad_op;
3801
3802     case INTRINSIC_PARENTHESES:
3803       e->ts = op1->ts;
3804       if (e->ts.type == BT_CHARACTER)
3805         e->ts.u.cl = op1->ts.u.cl;
3806       break;
3807
3808     default:
3809       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3810     }
3811
3812   /* Deal with arrayness of an operand through an operator.  */
3813
3814   t = SUCCESS;
3815
3816   switch (e->value.op.op)
3817     {
3818     case INTRINSIC_PLUS:
3819     case INTRINSIC_MINUS:
3820     case INTRINSIC_TIMES:
3821     case INTRINSIC_DIVIDE:
3822     case INTRINSIC_POWER:
3823     case INTRINSIC_CONCAT:
3824     case INTRINSIC_AND:
3825     case INTRINSIC_OR:
3826     case INTRINSIC_EQV:
3827     case INTRINSIC_NEQV:
3828     case INTRINSIC_EQ:
3829     case INTRINSIC_EQ_OS:
3830     case INTRINSIC_NE:
3831     case INTRINSIC_NE_OS:
3832     case INTRINSIC_GT:
3833     case INTRINSIC_GT_OS:
3834     case INTRINSIC_GE:
3835     case INTRINSIC_GE_OS:
3836     case INTRINSIC_LT:
3837     case INTRINSIC_LT_OS:
3838     case INTRINSIC_LE:
3839     case INTRINSIC_LE_OS:
3840
3841       if (op1->rank == 0 && op2->rank == 0)
3842         e->rank = 0;
3843
3844       if (op1->rank == 0 && op2->rank != 0)
3845         {
3846           e->rank = op2->rank;
3847
3848           if (e->shape == NULL)
3849             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3850         }
3851
3852       if (op1->rank != 0 && op2->rank == 0)
3853         {
3854           e->rank = op1->rank;
3855
3856           if (e->shape == NULL)
3857             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3858         }
3859
3860       if (op1->rank != 0 && op2->rank != 0)
3861         {
3862           if (op1->rank == op2->rank)
3863             {
3864               e->rank = op1->rank;
3865               if (e->shape == NULL)
3866                 {
3867                   t = compare_shapes (op1, op2);
3868                   if (t == FAILURE)
3869                     e->shape = NULL;
3870                   else
3871                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
3872                 }
3873             }
3874           else
3875             {
3876               /* Allow higher level expressions to work.  */
3877               e->rank = 0;
3878
3879               /* Try user-defined operators, and otherwise throw an error.  */
3880               dual_locus_error = true;
3881               sprintf (msg,
3882                        _("Inconsistent ranks for operator at %%L and %%L"));
3883               goto bad_op;
3884             }
3885         }
3886
3887       break;
3888
3889     case INTRINSIC_PARENTHESES:
3890     case INTRINSIC_NOT:
3891     case INTRINSIC_UPLUS:
3892     case INTRINSIC_UMINUS:
3893       /* Simply copy arrayness attribute */
3894       e->rank = op1->rank;
3895
3896       if (e->shape == NULL)
3897         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3898
3899       break;
3900
3901     default:
3902       break;
3903     }
3904
3905   /* Attempt to simplify the expression.  */
3906   if (t == SUCCESS)
3907     {
3908       t = gfc_simplify_expr (e, 0);
3909       /* Some calls do not succeed in simplification and return FAILURE
3910          even though there is no error; e.g. variable references to
3911          PARAMETER arrays.  */
3912       if (!gfc_is_constant_expr (e))
3913         t = SUCCESS;
3914     }
3915   return t;
3916
3917 bad_op:
3918
3919   {
3920     bool real_error;
3921     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3922       return SUCCESS;
3923
3924     if (real_error)
3925       return FAILURE;
3926   }
3927
3928   if (dual_locus_error)
3929     gfc_error (msg, &op1->where, &op2->where);
3930   else
3931     gfc_error (msg, &e->where);
3932
3933   return FAILURE;
3934 }
3935
3936
3937 /************** Array resolution subroutines **************/
3938
3939 typedef enum
3940 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3941 comparison;
3942
3943 /* Compare two integer expressions.  */
3944
3945 static comparison
3946 compare_bound (gfc_expr *a, gfc_expr *b)
3947 {
3948   int i;
3949
3950   if (a == NULL || a->expr_type != EXPR_CONSTANT
3951       || b == NULL || b->expr_type != EXPR_CONSTANT)
3952     return CMP_UNKNOWN;
3953
3954   /* If either of the types isn't INTEGER, we must have
3955      raised an error earlier.  */
3956
3957   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3958     return CMP_UNKNOWN;
3959
3960   i = mpz_cmp (a->value.integer, b->value.integer);
3961
3962   if (i < 0)
3963     return CMP_LT;
3964   if (i > 0)
3965     return CMP_GT;
3966   return CMP_EQ;
3967 }
3968
3969
3970 /* Compare an integer expression with an integer.  */
3971
3972 static comparison
3973 compare_bound_int (gfc_expr *a, int b)
3974 {
3975   int i;
3976
3977   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3978     return CMP_UNKNOWN;
3979
3980   if (a->ts.type != BT_INTEGER)
3981     gfc_internal_error ("compare_bound_int(): Bad expression");
3982
3983   i = mpz_cmp_si (a->value.integer, b);
3984
3985   if (i < 0)
3986     return CMP_LT;
3987   if (i > 0)
3988     return CMP_GT;
3989   return CMP_EQ;
3990 }
3991
3992
3993 /* Compare an integer expression with a mpz_t.  */
3994
3995 static comparison
3996 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3997 {
3998   int i;
3999
4000   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4001     return CMP_UNKNOWN;
4002
4003   if (a->ts.type != BT_INTEGER)
4004     gfc_internal_error ("compare_bound_int(): Bad expression");
4005
4006   i = mpz_cmp (a->value.integer, b);
4007
4008   if (i < 0)
4009     return CMP_LT;
4010   if (i > 0)
4011     return CMP_GT;
4012   return CMP_EQ;
4013 }
4014
4015
4016 /* Compute the last value of a sequence given by a triplet.  
4017    Return 0 if it wasn't able to compute the last value, or if the
4018    sequence if empty, and 1 otherwise.  */
4019
4020 static int
4021 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
4022                                 gfc_expr *stride, mpz_t last)
4023 {
4024   mpz_t rem;
4025
4026   if (start == NULL || start->expr_type != EXPR_CONSTANT
4027       || end == NULL || end->expr_type != EXPR_CONSTANT
4028       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
4029     return 0;
4030
4031   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
4032       || (stride != NULL && stride->ts.type != BT_INTEGER))
4033     return 0;
4034
4035   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
4036     {
4037       if (compare_bound (start, end) == CMP_GT)
4038         return 0;
4039       mpz_set (last, end->value.integer);
4040       return 1;
4041     }
4042
4043   if (compare_bound_int (stride, 0) == CMP_GT)
4044     {
4045       /* Stride is positive */
4046       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
4047         return 0;
4048     }
4049   else
4050     {
4051       /* Stride is negative */
4052       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
4053         return 0;
4054     }
4055
4056   mpz_init (rem);
4057   mpz_sub (rem, end->value.integer, start->value.integer);
4058   mpz_tdiv_r (rem, rem, stride->value.integer);
4059   mpz_sub (last, end->value.integer, rem);
4060   mpz_clear (rem);
4061
4062   return 1;
4063 }
4064
4065
4066 /* Compare a single dimension of an array reference to the array
4067    specification.  */
4068
4069 static gfc_try
4070 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
4071 {
4072   mpz_t last_value;
4073
4074   if (ar->dimen_type[i] == DIMEN_STAR)
4075     {
4076       gcc_assert (ar->stride[i] == NULL);
4077       /* This implies [*] as [*:] and [*:3] are not possible.  */
4078       if (ar->start[i] == NULL)
4079         {
4080           gcc_assert (ar->end[i] == NULL);
4081           return SUCCESS;
4082         }
4083     }
4084
4085 /* Given start, end and stride values, calculate the minimum and
4086    maximum referenced indexes.  */
4087
4088   switch (ar->dimen_type[i])
4089     {
4090     case DIMEN_VECTOR:
4091       break;
4092
4093     case DIMEN_STAR:
4094     case DIMEN_ELEMENT:
4095       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4096         {
4097           if (i < as->rank)
4098             gfc_warning ("Array reference at %L is out of bounds "
4099                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
4100                          mpz_get_si (ar->start[i]->value.integer),
4101                          mpz_get_si (as->lower[i]->value.integer), i+1);
4102           else
4103             gfc_warning ("Array reference at %L is out of bounds "
4104                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
4105                          mpz_get_si (ar->start[i]->value.integer),
4106                          mpz_get_si (as->lower[i]->value.integer),
4107                          i + 1 - as->rank);
4108           return SUCCESS;
4109         }
4110       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4111         {
4112           if (i < as->rank)
4113             gfc_warning ("Array reference at %L is out of bounds "
4114                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
4115                          mpz_get_si (ar->start[i]->value.integer),
4116                          mpz_get_si (as->upper[i]->value.integer), i+1);
4117           else
4118             gfc_warning ("Array reference at %L is out of bounds "
4119                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
4120                          mpz_get_si (ar->start[i]->value.integer),
4121                          mpz_get_si (as->upper[i]->value.integer),
4122                          i + 1 - as->rank);
4123           return SUCCESS;
4124         }
4125
4126       break;
4127
4128     case DIMEN_RANGE:
4129       {
4130 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4131 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4132
4133         comparison comp_start_end = compare_bound (AR_START, AR_END);
4134
4135         /* Check for zero stride, which is not allowed.  */
4136         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4137           {
4138             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4139             return FAILURE;
4140           }
4141
4142         /* if start == len || (stride > 0 && start < len)
4143                            || (stride < 0 && start > len),
4144            then the array section contains at least one element.  In this
4145            case, there is an out-of-bounds access if
4146            (start < lower || start > upper).  */
4147         if (compare_bound (AR_START, AR_END) == CMP_EQ
4148             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4149                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4150             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4151                 && comp_start_end == CMP_GT))
4152           {
4153             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4154               {
4155                 gfc_warning ("Lower array reference at %L is out of bounds "
4156                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4157                        mpz_get_si (AR_START->value.integer),
4158                        mpz_get_si (as->lower[i]->value.integer), i+1);
4159                 return SUCCESS;
4160               }
4161             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4162               {
4163                 gfc_warning ("Lower array reference at %L is out of bounds "
4164                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4165                        mpz_get_si (AR_START->value.integer),
4166                        mpz_get_si (as->upper[i]->value.integer), i+1);
4167                 return SUCCESS;
4168               }
4169           }
4170
4171         /* If we can compute the highest index of the array section,
4172            then it also has to be between lower and upper.  */
4173         mpz_init (last_value);
4174         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4175                                             last_value))
4176           {
4177             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4178               {
4179                 gfc_warning ("Upper array reference at %L is out of bounds "
4180                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4181                        mpz_get_si (last_value),
4182                        mpz_get_si (as->lower[i]->value.integer), i+1);
4183                 mpz_clear (last_value);
4184                 return SUCCESS;
4185               }
4186             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4187               {
4188                 gfc_warning ("Upper array reference at %L is out of bounds "
4189                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4190                        mpz_get_si (last_value),
4191                        mpz_get_si (as->upper[i]->value.integer), i+1);
4192                 mpz_clear (last_value);
4193                 return SUCCESS;
4194               }
4195           }
4196         mpz_clear (last_value);
4197
4198 #undef AR_START
4199 #undef AR_END
4200       }
4201       break;
4202
4203     default:
4204       gfc_internal_error ("check_dimension(): Bad array reference");
4205     }
4206
4207   return SUCCESS;
4208 }
4209
4210
4211 /* Compare an array reference with an array specification.  */
4212
4213 static gfc_try
4214 compare_spec_to_ref (gfc_array_ref *ar)
4215 {
4216   gfc_array_spec *as;
4217   int i;
4218
4219   as = ar->as;
4220   i = as->rank - 1;
4221   /* TODO: Full array sections are only allowed as actual parameters.  */
4222   if (as->type == AS_ASSUMED_SIZE
4223       && (/*ar->type == AR_FULL
4224           ||*/ (ar->type == AR_SECTION
4225               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4226     {
4227       gfc_error ("Rightmost upper bound of assumed size array section "
4228                  "not specified at %L", &ar->where);
4229       return FAILURE;
4230     }
4231
4232   if (ar->type == AR_FULL)
4233     return SUCCESS;
4234
4235   if (as->rank != ar->dimen)
4236     {
4237       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4238                  &ar->where, ar->dimen, as->rank);
4239       return FAILURE;
4240     }
4241
4242   /* ar->codimen == 0 is a local array.  */
4243   if (as->corank != ar->codimen && ar->codimen != 0)
4244     {
4245       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4246                  &ar->where, ar->codimen, as->corank);
4247       return FAILURE;
4248     }
4249
4250   for (i = 0; i < as->rank; i++)
4251     if (check_dimension (i, ar, as) == FAILURE)
4252       return FAILURE;
4253
4254   /* Local access has no coarray spec.  */
4255   if (ar->codimen != 0)
4256     for (i = as->rank; i < as->rank + as->corank; i++)
4257       {
4258         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate)
4259           {
4260             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4261                        i + 1 - as->rank, &ar->where);
4262             return FAILURE;
4263           }
4264         if (check_dimension (i, ar, as) == FAILURE)
4265           return FAILURE;
4266       }
4267
4268   return SUCCESS;
4269 }
4270
4271
4272 /* Resolve one part of an array index.  */
4273
4274 static gfc_try
4275 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4276                      int force_index_integer_kind)
4277 {
4278   gfc_typespec ts;
4279
4280   if (index == NULL)
4281     return SUCCESS;
4282
4283   if (gfc_resolve_expr (index) == FAILURE)
4284     return FAILURE;
4285
4286   if (check_scalar && index->rank != 0)
4287     {
4288       gfc_error ("Array index at %L must be scalar", &index->where);
4289       return FAILURE;
4290     }
4291
4292   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4293     {
4294       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4295                  &index->where, gfc_basic_typename (index->ts.type));
4296       return FAILURE;
4297     }
4298
4299   if (index->ts.type == BT_REAL)
4300     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4301                         &index->where) == FAILURE)
4302       return FAILURE;
4303
4304   if ((index->ts.kind != gfc_index_integer_kind
4305        && force_index_integer_kind)
4306       || index->ts.type != BT_INTEGER)
4307     {
4308       gfc_clear_ts (&ts);
4309       ts.type = BT_INTEGER;
4310       ts.kind = gfc_index_integer_kind;
4311
4312       gfc_convert_type_warn (index, &ts, 2, 0);
4313     }
4314
4315   return SUCCESS;
4316 }
4317
4318 /* Resolve one part of an array index.  */
4319
4320 gfc_try
4321 gfc_resolve_index (gfc_expr *index, int check_scalar)
4322 {
4323   return gfc_resolve_index_1 (index, check_scalar, 1);
4324 }
4325
4326 /* Resolve a dim argument to an intrinsic function.  */
4327
4328 gfc_try
4329 gfc_resolve_dim_arg (gfc_expr *dim)
4330 {
4331   if (dim == NULL)
4332     return SUCCESS;
4333
4334   if (gfc_resolve_expr (dim) == FAILURE)
4335     return FAILURE;
4336
4337   if (dim->rank != 0)
4338     {
4339       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4340       return FAILURE;
4341
4342     }
4343
4344   if (dim->ts.type != BT_INTEGER)
4345     {
4346       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4347       return FAILURE;
4348     }
4349
4350   if (dim->ts.kind != gfc_index_integer_kind)
4351     {
4352       gfc_typespec ts;
4353
4354       gfc_clear_ts (&ts);
4355       ts.type = BT_INTEGER;
4356       ts.kind = gfc_index_integer_kind;
4357
4358       gfc_convert_type_warn (dim, &ts, 2, 0);
4359     }
4360
4361   return SUCCESS;
4362 }
4363
4364 /* Given an expression that contains array references, update those array
4365    references to point to the right array specifications.  While this is
4366    filled in during matching, this information is difficult to save and load
4367    in a module, so we take care of it here.
4368
4369    The idea here is that the original array reference comes from the
4370    base symbol.  We traverse the list of reference structures, setting
4371    the stored reference to references.  Component references can
4372    provide an additional array specification.  */
4373
4374 static void
4375 find_array_spec (gfc_expr *e)
4376 {
4377   gfc_array_spec *as;
4378   gfc_component *c;
4379   gfc_symbol *derived;
4380   gfc_ref *ref;
4381
4382   if (e->symtree->n.sym->ts.type == BT_CLASS)
4383     as = CLASS_DATA (e->symtree->n.sym)->as;
4384   else
4385     as = e->symtree->n.sym->as;
4386   derived = NULL;
4387
4388   for (ref = e->ref; ref; ref = ref->next)
4389     switch (ref->type)
4390       {
4391       case REF_ARRAY:
4392         if (as == NULL)
4393           gfc_internal_error ("find_array_spec(): Missing spec");
4394
4395         ref->u.ar.as = as;
4396         as = NULL;
4397         break;
4398
4399       case REF_COMPONENT:
4400         if (derived == NULL)
4401           derived = e->symtree->n.sym->ts.u.derived;
4402
4403         if (derived->attr.is_class)
4404           derived = derived->components->ts.u.derived;
4405
4406         c = derived->components;
4407
4408         for (; c; c = c->next)
4409           if (c == ref->u.c.component)
4410             {
4411               /* Track the sequence of component references.  */
4412               if (c->ts.type == BT_DERIVED)
4413                 derived = c->ts.u.derived;
4414               break;
4415             }
4416
4417         if (c == NULL)
4418           gfc_internal_error ("find_array_spec(): Component not found");
4419
4420         if (c->attr.dimension)
4421           {
4422             if (as != NULL)
4423               gfc_internal_error ("find_array_spec(): unused as(1)");
4424             as = c->as;
4425           }
4426
4427         break;
4428
4429       case REF_SUBSTRING:
4430         break;
4431       }
4432
4433   if (as != NULL)
4434     gfc_internal_error ("find_array_spec(): unused as(2)");
4435 }
4436
4437
4438 /* Resolve an array reference.  */
4439
4440 static gfc_try
4441 resolve_array_ref (gfc_array_ref *ar)
4442 {
4443   int i, check_scalar;
4444   gfc_expr *e;
4445
4446   for (i = 0; i < ar->dimen + ar->codimen; i++)
4447     {
4448       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4449
4450       /* Do not force gfc_index_integer_kind for the start.  We can
4451          do fine with any integer kind.  This avoids temporary arrays
4452          created for indexing with a vector.  */
4453       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4454         return FAILURE;
4455       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4456         return FAILURE;
4457       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4458         return FAILURE;
4459
4460       e = ar->start[i];
4461
4462       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4463         switch (e->rank)
4464           {
4465           case 0:
4466             ar->dimen_type[i] = DIMEN_ELEMENT;
4467             break;
4468
4469           case 1:
4470             ar->dimen_type[i] = DIMEN_VECTOR;
4471             if (e->expr_type == EXPR_VARIABLE
4472                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4473               ar->start[i] = gfc_get_parentheses (e);
4474             break;
4475
4476           default:
4477             gfc_error ("Array index at %L is an array of rank %d",
4478                        &ar->c_where[i], e->rank);
4479             return FAILURE;
4480           }
4481
4482       /* Fill in the upper bound, which may be lower than the
4483          specified one for something like a(2:10:5), which is
4484          identical to a(2:7:5).  Only relevant for strides not equal
4485          to one.  */
4486       if (ar->dimen_type[i] == DIMEN_RANGE
4487           && ar->stride[i] != NULL && ar->stride[i]->expr_type == EXPR_CONSTANT
4488           && mpz_cmp_si (ar->stride[i]->value.integer, 1L) != 0)
4489         {
4490           mpz_t size, end;
4491
4492           if (gfc_ref_dimen_size (ar, i, &size, &end) == SUCCESS)
4493             {
4494               if (ar->end[i] == NULL)
4495                 {
4496                   ar->end[i] =
4497                     gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
4498                                            &ar->where);
4499                   mpz_set (ar->end[i]->value.integer, end);
4500                 }
4501               else if (ar->end[i]->ts.type == BT_INTEGER
4502                        && ar->end[i]->expr_type == EXPR_CONSTANT)
4503                 {
4504                   mpz_set (ar->end[i]->value.integer, end);
4505                 }
4506               else
4507                 gcc_unreachable ();
4508
4509               mpz_clear (size);
4510               mpz_clear (end);
4511             }
4512         }
4513     }
4514
4515   if (ar->type == AR_FULL && ar->as->rank == 0)
4516     ar->type = AR_ELEMENT;
4517
4518   /* If the reference type is unknown, figure out what kind it is.  */
4519
4520   if (ar->type == AR_UNKNOWN)
4521     {
4522       ar->type = AR_ELEMENT;
4523       for (i = 0; i < ar->dimen; i++)
4524         if (ar->dimen_type[i] == DIMEN_RANGE
4525             || ar->dimen_type[i] == DIMEN_VECTOR)
4526           {
4527             ar->type = AR_SECTION;
4528             break;
4529           }
4530     }
4531
4532   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4533     return FAILURE;
4534
4535   return SUCCESS;
4536 }
4537
4538
4539 static gfc_try
4540 resolve_substring (gfc_ref *ref)
4541 {
4542   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4543
4544   if (ref->u.ss.start != NULL)
4545     {
4546       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4547         return FAILURE;
4548
4549       if (ref->u.ss.start->ts.type != BT_INTEGER)
4550         {
4551           gfc_error ("Substring start index at %L must be of type INTEGER",
4552                      &ref->u.ss.start->where);
4553           return FAILURE;
4554         }
4555
4556       if (ref->u.ss.start->rank != 0)
4557         {
4558           gfc_error ("Substring start index at %L must be scalar",
4559                      &ref->u.ss.start->where);
4560           return FAILURE;
4561         }
4562
4563       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4564           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4565               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4566         {
4567           gfc_error ("Substring start index at %L is less than one",
4568                      &ref->u.ss.start->where);
4569           return FAILURE;
4570         }
4571     }
4572
4573   if (ref->u.ss.end != NULL)
4574     {
4575       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4576         return FAILURE;
4577
4578       if (ref->u.ss.end->ts.type != BT_INTEGER)
4579         {
4580           gfc_error ("Substring end index at %L must be of type INTEGER",
4581                      &ref->u.ss.end->where);
4582           return FAILURE;
4583         }
4584
4585       if (ref->u.ss.end->rank != 0)
4586         {
4587           gfc_error ("Substring end index at %L must be scalar",
4588                      &ref->u.ss.end->where);
4589           return FAILURE;
4590         }
4591
4592       if (ref->u.ss.length != NULL
4593           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4594           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4595               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4596         {
4597           gfc_error ("Substring end index at %L exceeds the string length",
4598                      &ref->u.ss.start->where);
4599           return FAILURE;
4600         }
4601
4602       if (compare_bound_mpz_t (ref->u.ss.end,
4603                                gfc_integer_kinds[k].huge) == CMP_GT
4604           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4605               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4606         {
4607           gfc_error ("Substring end index at %L is too large",
4608                      &ref->u.ss.end->where);
4609           return FAILURE;
4610         }
4611     }
4612
4613   return SUCCESS;
4614 }
4615
4616
4617 /* This function supplies missing substring charlens.  */
4618
4619 void
4620 gfc_resolve_substring_charlen (gfc_expr *e)
4621 {
4622   gfc_ref *char_ref;
4623   gfc_expr *start, *end;
4624
4625   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4626     if (char_ref->type == REF_SUBSTRING)
4627       break;
4628
4629   if (!char_ref)
4630     return;
4631
4632   gcc_assert (char_ref->next == NULL);
4633
4634   if (e->ts.u.cl)
4635     {
4636       if (e->ts.u.cl->length)
4637         gfc_free_expr (e->ts.u.cl->length);
4638       else if (e->expr_type == EXPR_VARIABLE
4639                  && e->symtree->n.sym->attr.dummy)
4640         return;
4641     }
4642
4643   e->ts.type = BT_CHARACTER;
4644   e->ts.kind = gfc_default_character_kind;
4645
4646   if (!e->ts.u.cl)
4647     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4648
4649   if (char_ref->u.ss.start)
4650     start = gfc_copy_expr (char_ref->u.ss.start);
4651   else
4652     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4653
4654   if (char_ref->u.ss.end)
4655     end = gfc_copy_expr (char_ref->u.ss.end);
4656   else if (e->expr_type == EXPR_VARIABLE)
4657     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4658   else
4659     end = NULL;
4660
4661   if (!start || !end)
4662     return;
4663
4664   /* Length = (end - start +1).  */
4665   e->ts.u.cl->length = gfc_subtract (end, start);
4666   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4667                                 gfc_get_int_expr (gfc_default_integer_kind,
4668                                                   NULL, 1));
4669
4670   e->ts.u.cl->length->ts.type = BT_INTEGER;
4671   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4672
4673   /* Make sure that the length is simplified.  */
4674   gfc_simplify_expr (e->ts.u.cl->length, 1);
4675   gfc_resolve_expr (e->ts.u.cl->length);
4676 }
4677
4678
4679 /* Resolve subtype references.  */
4680
4681 static gfc_try
4682 resolve_ref (gfc_expr *expr)
4683 {
4684   int current_part_dimension, n_components, seen_part_dimension;
4685   gfc_ref *ref;
4686
4687   for (ref = expr->ref; ref; ref = ref->next)
4688     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4689       {
4690         find_array_spec (expr);
4691         break;
4692       }
4693
4694   for (ref = expr->ref; ref; ref = ref->next)
4695     switch (ref->type)
4696       {
4697       case REF_ARRAY:
4698         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4699           return FAILURE;
4700         break;
4701
4702       case REF_COMPONENT:
4703         break;
4704
4705       case REF_SUBSTRING:
4706         resolve_substring (ref);
4707         break;
4708       }
4709
4710   /* Check constraints on part references.  */
4711
4712   current_part_dimension = 0;
4713   seen_part_dimension = 0;
4714   n_components = 0;
4715
4716   for (ref = expr->ref; ref; ref = ref->next)
4717     {
4718       switch (ref->type)
4719         {
4720         case REF_ARRAY:
4721           switch (ref->u.ar.type)
4722             {
4723             case AR_FULL:
4724               /* Coarray scalar.  */
4725               if (ref->u.ar.as->rank == 0)
4726                 {
4727                   current_part_dimension = 0;
4728                   break;
4729                 }
4730               /* Fall through.  */
4731             case AR_SECTION:
4732               current_part_dimension = 1;
4733               break;
4734
4735             case AR_ELEMENT:
4736               current_part_dimension = 0;
4737               break;
4738
4739             case AR_UNKNOWN:
4740               gfc_internal_error ("resolve_ref(): Bad array reference");
4741             }
4742
4743           break;
4744
4745         case REF_COMPONENT:
4746           if (current_part_dimension || seen_part_dimension)
4747             {
4748               /* F03:C614.  */
4749               if (ref->u.c.component->attr.pointer
4750                   || ref->u.c.component->attr.proc_pointer)
4751                 {
4752                   gfc_error ("Component to the right of a part reference "
4753                              "with nonzero rank must not have the POINTER "
4754                              "attribute at %L", &expr->where);
4755                   return FAILURE;
4756                 }
4757               else if (ref->u.c.component->attr.allocatable)
4758                 {
4759                   gfc_error ("Component to the right of a part reference "
4760                              "with nonzero rank must not have the ALLOCATABLE "
4761                              "attribute at %L", &expr->where);
4762                   return FAILURE;
4763                 }
4764             }
4765
4766           n_components++;
4767           break;
4768
4769         case REF_SUBSTRING:
4770           break;
4771         }
4772
4773       if (((ref->type == REF_COMPONENT && n_components > 1)
4774            || ref->next == NULL)
4775           && current_part_dimension
4776           && seen_part_dimension)
4777         {
4778           gfc_error ("Two or more part references with nonzero rank must "
4779                      "not be specified at %L", &expr->where);
4780           return FAILURE;
4781         }
4782
4783       if (ref->type == REF_COMPONENT)
4784         {
4785           if (current_part_dimension)
4786             seen_part_dimension = 1;
4787
4788           /* reset to make sure */
4789           current_part_dimension = 0;
4790         }
4791     }
4792
4793   return SUCCESS;
4794 }
4795
4796
4797 /* Given an expression, determine its shape.  This is easier than it sounds.
4798    Leaves the shape array NULL if it is not possible to determine the shape.  */
4799
4800 static void
4801 expression_shape (gfc_expr *e)
4802 {
4803   mpz_t array[GFC_MAX_DIMENSIONS];
4804   int i;
4805
4806   if (e->rank == 0 || e->shape != NULL)
4807     return;
4808
4809   for (i = 0; i < e->rank; i++)
4810     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4811       goto fail;
4812
4813   e->shape = gfc_get_shape (e->rank);
4814
4815   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4816
4817   return;
4818
4819 fail:
4820   for (i--; i >= 0; i--)
4821     mpz_clear (array[i]);
4822 }
4823
4824
4825 /* Given a variable expression node, compute the rank of the expression by
4826    examining the base symbol and any reference structures it may have.  */
4827
4828 static void
4829 expression_rank (gfc_expr *e)
4830 {
4831   gfc_ref *ref;
4832   int i, rank;
4833
4834   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4835      could lead to serious confusion...  */
4836   gcc_assert (e->expr_type != EXPR_COMPCALL);
4837
4838   if (e->ref == NULL)
4839     {
4840       if (e->expr_type == EXPR_ARRAY)
4841         goto done;
4842       /* Constructors can have a rank different from one via RESHAPE().  */
4843
4844       if (e->symtree == NULL)
4845         {
4846           e->rank = 0;
4847           goto done;
4848         }
4849
4850       e->rank = (e->symtree->n.sym->as == NULL)
4851                 ? 0 : e->symtree->n.sym->as->rank;
4852       goto done;
4853     }
4854
4855   rank = 0;
4856
4857   for (ref = e->ref; ref; ref = ref->next)
4858     {
4859       if (ref->type != REF_ARRAY)
4860         continue;
4861
4862       if (ref->u.ar.type == AR_FULL)
4863         {
4864           rank = ref->u.ar.as->rank;
4865           break;
4866         }
4867
4868       if (ref->u.ar.type == AR_SECTION)
4869         {
4870           /* Figure out the rank of the section.  */
4871           if (rank != 0)
4872             gfc_internal_error ("expression_rank(): Two array specs");
4873
4874           for (i = 0; i < ref->u.ar.dimen; i++)
4875             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4876                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4877               rank++;
4878
4879           break;
4880         }
4881     }
4882
4883   e->rank = rank;
4884
4885 done:
4886   expression_shape (e);
4887 }
4888
4889
4890 /* Resolve a variable expression.  */
4891
4892 static gfc_try
4893 resolve_variable (gfc_expr *e)
4894 {
4895   gfc_symbol *sym;
4896   gfc_try t;
4897
4898   t = SUCCESS;
4899
4900   if (e->symtree == NULL)
4901     return FAILURE;
4902   sym = e->symtree->n.sym;
4903
4904   /* If this is an associate-name, it may be parsed with an array reference
4905      in error even though the target is scalar.  Fail directly in this case.  */
4906   if (sym->assoc && !sym->attr.dimension && e->ref && e->ref->type == REF_ARRAY)
4907     return FAILURE;
4908
4909   /* On the other hand, the parser may not have known this is an array;
4910      in this case, we have to add a FULL reference.  */
4911   if (sym->assoc && sym->attr.dimension && !e->ref)
4912     {
4913       e->ref = gfc_get_ref ();
4914       e->ref->type = REF_ARRAY;
4915       e->ref->u.ar.type = AR_FULL;
4916       e->ref->u.ar.dimen = 0;
4917     }
4918
4919   if (e->ref && resolve_ref (e) == FAILURE)
4920     return FAILURE;
4921
4922   if (sym->attr.flavor == FL_PROCEDURE
4923       && (!sym->attr.function
4924           || (sym->attr.function && sym->result
4925               && sym->result->attr.proc_pointer
4926               && !sym->result->attr.function)))
4927     {
4928       e->ts.type = BT_PROCEDURE;
4929       goto resolve_procedure;
4930     }
4931
4932   if (sym->ts.type != BT_UNKNOWN)
4933     gfc_variable_attr (e, &e->ts);
4934   else
4935     {
4936       /* Must be a simple variable reference.  */
4937       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
4938         return FAILURE;
4939       e->ts = sym->ts;
4940     }
4941
4942   if (check_assumed_size_reference (sym, e))
4943     return FAILURE;
4944
4945   /* Deal with forward references to entries during resolve_code, to
4946      satisfy, at least partially, 12.5.2.5.  */
4947   if (gfc_current_ns->entries
4948       && current_entry_id == sym->entry_id
4949       && cs_base
4950       && cs_base->current
4951       && cs_base->current->op != EXEC_ENTRY)
4952     {
4953       gfc_entry_list *entry;
4954       gfc_formal_arglist *formal;
4955       int n;
4956       bool seen;
4957
4958       /* If the symbol is a dummy...  */
4959       if (sym->attr.dummy && sym->ns == gfc_current_ns)
4960         {
4961           entry = gfc_current_ns->entries;
4962           seen = false;
4963
4964           /* ...test if the symbol is a parameter of previous entries.  */
4965           for (; entry && entry->id <= current_entry_id; entry = entry->next)
4966             for (formal = entry->sym->formal; formal; formal = formal->next)
4967               {
4968                 if (formal->sym && sym->name == formal->sym->name)
4969                   seen = true;
4970               }
4971
4972           /*  If it has not been seen as a dummy, this is an error.  */
4973           if (!seen)
4974             {
4975               if (specification_expr)
4976                 gfc_error ("Variable '%s', used in a specification expression"
4977                            ", is referenced at %L before the ENTRY statement "
4978                            "in which it is a parameter",
4979                            sym->name, &cs_base->current->loc);
4980               else
4981                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
4982                            "statement in which it is a parameter",
4983                            sym->name, &cs_base->current->loc);
4984               t = FAILURE;
4985             }
4986         }
4987
4988       /* Now do the same check on the specification expressions.  */
4989       specification_expr = 1;
4990       if (sym->ts.type == BT_CHARACTER
4991           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
4992         t = FAILURE;
4993
4994       if (sym->as)
4995         for (n = 0; n < sym->as->rank; n++)
4996           {
4997              specification_expr = 1;
4998              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
4999                t = FAILURE;
5000              specification_expr = 1;
5001              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
5002                t = FAILURE;
5003           }
5004       specification_expr = 0;
5005
5006       if (t == SUCCESS)
5007         /* Update the symbol's entry level.  */
5008         sym->entry_id = current_entry_id + 1;
5009     }
5010
5011   /* If a symbol has been host_associated mark it.  This is used latter,
5012      to identify if aliasing is possible via host association.  */
5013   if (sym->attr.flavor == FL_VARIABLE
5014         && gfc_current_ns->parent
5015         && (gfc_current_ns->parent == sym->ns
5016               || (gfc_current_ns->parent->parent
5017                     && gfc_current_ns->parent->parent == sym->ns)))
5018     sym->attr.host_assoc = 1;
5019
5020 resolve_procedure:
5021   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
5022     t = FAILURE;
5023
5024   /* F2008, C617 and C1229.  */
5025   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5026       && gfc_is_coindexed (e))
5027     {
5028       gfc_ref *ref, *ref2 = NULL;
5029
5030       if (e->ts.type == BT_CLASS)
5031         {
5032           gfc_error ("Polymorphic subobject of coindexed object at %L",
5033                      &e->where);
5034           t = FAILURE;
5035         }
5036
5037       for (ref = e->ref; ref; ref = ref->next)
5038         {
5039           if (ref->type == REF_COMPONENT)
5040             ref2 = ref;
5041           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5042             break;
5043         }
5044
5045       for ( ; ref; ref = ref->next)
5046         if (ref->type == REF_COMPONENT)
5047           break;
5048
5049       /* Expression itself is coindexed object.  */
5050       if (ref == NULL)
5051         {
5052           gfc_component *c;
5053           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5054           for ( ; c; c = c->next)
5055             if (c->attr.allocatable && c->ts.type == BT_CLASS)
5056               {
5057                 gfc_error ("Coindexed object with polymorphic allocatable "
5058                          "subcomponent at %L", &e->where);
5059                 t = FAILURE;
5060                 break;
5061               }
5062         }
5063     }
5064
5065   return t;
5066 }
5067
5068
5069 /* Checks to see that the correct symbol has been host associated.
5070    The only situation where this arises is that in which a twice
5071    contained function is parsed after the host association is made.
5072    Therefore, on detecting this, change the symbol in the expression
5073    and convert the array reference into an actual arglist if the old
5074    symbol is a variable.  */
5075 static bool
5076 check_host_association (gfc_expr *e)
5077 {
5078   gfc_symbol *sym, *old_sym;
5079   gfc_symtree *st;
5080   int n;
5081   gfc_ref *ref;
5082   gfc_actual_arglist *arg, *tail = NULL;
5083   bool retval = e->expr_type == EXPR_FUNCTION;
5084
5085   /*  If the expression is the result of substitution in
5086       interface.c(gfc_extend_expr) because there is no way in
5087       which the host association can be wrong.  */
5088   if (e->symtree == NULL
5089         || e->symtree->n.sym == NULL
5090         || e->user_operator)
5091     return retval;
5092
5093   old_sym = e->symtree->n.sym;
5094
5095   if (gfc_current_ns->parent
5096         && old_sym->ns != gfc_current_ns)
5097     {
5098       /* Use the 'USE' name so that renamed module symbols are
5099          correctly handled.  */
5100       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5101
5102       if (sym && old_sym != sym
5103               && sym->ts.type == old_sym->ts.type
5104               && sym->attr.flavor == FL_PROCEDURE
5105               && sym->attr.contained)
5106         {
5107           /* Clear the shape, since it might not be valid.  */
5108           if (e->shape != NULL)
5109             {
5110               for (n = 0; n < e->rank; n++)
5111                 mpz_clear (e->shape[n]);
5112
5113               gfc_free (e->shape);
5114             }
5115
5116           /* Give the expression the right symtree!  */
5117           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5118           gcc_assert (st != NULL);
5119
5120           if (old_sym->attr.flavor == FL_PROCEDURE
5121                 || e->expr_type == EXPR_FUNCTION)
5122             {
5123               /* Original was function so point to the new symbol, since
5124                  the actual argument list is already attached to the
5125                  expression. */
5126               e->value.function.esym = NULL;
5127               e->symtree = st;
5128             }
5129           else
5130             {
5131               /* Original was variable so convert array references into
5132                  an actual arglist. This does not need any checking now
5133                  since gfc_resolve_function will take care of it.  */
5134               e->value.function.actual = NULL;
5135               e->expr_type = EXPR_FUNCTION;
5136               e->symtree = st;
5137
5138               /* Ambiguity will not arise if the array reference is not
5139                  the last reference.  */
5140               for (ref = e->ref; ref; ref = ref->next)
5141                 if (ref->type == REF_ARRAY && ref->next == NULL)
5142                   break;
5143
5144               gcc_assert (ref->type == REF_ARRAY);
5145
5146               /* Grab the start expressions from the array ref and
5147                  copy them into actual arguments.  */
5148               for (n = 0; n < ref->u.ar.dimen; n++)
5149                 {
5150                   arg = gfc_get_actual_arglist ();
5151                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5152                   if (e->value.function.actual == NULL)
5153                     tail = e->value.function.actual = arg;
5154                   else
5155                     {
5156                       tail->next = arg;
5157                       tail = arg;
5158                     }
5159                 }
5160
5161               /* Dump the reference list and set the rank.  */
5162               gfc_free_ref_list (e->ref);
5163               e->ref = NULL;
5164               e->rank = sym->as ? sym->as->rank : 0;
5165             }
5166
5167           gfc_resolve_expr (e);
5168           sym->refs++;
5169         }
5170     }
5171   /* This might have changed!  */
5172   return e->expr_type == EXPR_FUNCTION;
5173 }
5174
5175
5176 static void
5177 gfc_resolve_character_operator (gfc_expr *e)
5178 {
5179   gfc_expr *op1 = e->value.op.op1;
5180   gfc_expr *op2 = e->value.op.op2;
5181   gfc_expr *e1 = NULL;
5182   gfc_expr *e2 = NULL;
5183
5184   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5185
5186   if (op1->ts.u.cl && op1->ts.u.cl->length)
5187     e1 = gfc_copy_expr (op1->ts.u.cl->length);
5188   else if (op1->expr_type == EXPR_CONSTANT)
5189     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5190                            op1->value.character.length);
5191
5192   if (op2->ts.u.cl && op2->ts.u.cl->length)
5193     e2 = gfc_copy_expr (op2->ts.u.cl->length);
5194   else if (op2->expr_type == EXPR_CONSTANT)
5195     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5196                            op2->value.character.length);
5197
5198   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5199
5200   if (!e1 || !e2)
5201     return;
5202
5203   e->ts.u.cl->length = gfc_add (e1, e2);
5204   e->ts.u.cl->length->ts.type = BT_INTEGER;
5205   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5206   gfc_simplify_expr (e->ts.u.cl->length, 0);
5207   gfc_resolve_expr (e->ts.u.cl->length);
5208
5209   return;
5210 }
5211
5212
5213 /*  Ensure that an character expression has a charlen and, if possible, a
5214     length expression.  */
5215
5216 static void
5217 fixup_charlen (gfc_expr *e)
5218 {
5219   /* The cases fall through so that changes in expression type and the need
5220      for multiple fixes are picked up.  In all circumstances, a charlen should
5221      be available for the middle end to hang a backend_decl on.  */
5222   switch (e->expr_type)
5223     {
5224     case EXPR_OP:
5225       gfc_resolve_character_operator (e);
5226
5227     case EXPR_ARRAY:
5228       if (e->expr_type == EXPR_ARRAY)
5229         gfc_resolve_character_array_constructor (e);
5230
5231     case EXPR_SUBSTRING:
5232       if (!e->ts.u.cl && e->ref)
5233         gfc_resolve_substring_charlen (e);
5234
5235     default:
5236       if (!e->ts.u.cl)
5237         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5238
5239       break;
5240     }
5241 }
5242
5243
5244 /* Update an actual argument to include the passed-object for type-bound
5245    procedures at the right position.  */
5246
5247 static gfc_actual_arglist*
5248 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5249                      const char *name)
5250 {
5251   gcc_assert (argpos > 0);
5252
5253   if (argpos == 1)
5254     {
5255       gfc_actual_arglist* result;
5256
5257       result = gfc_get_actual_arglist ();
5258       result->expr = po;
5259       result->next = lst;
5260       if (name)
5261         result->name = name;
5262
5263       return result;
5264     }
5265
5266   if (lst)
5267     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5268   else
5269     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5270   return lst;
5271 }
5272
5273
5274 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5275
5276 static gfc_expr*
5277 extract_compcall_passed_object (gfc_expr* e)
5278 {
5279   gfc_expr* po;
5280
5281   gcc_assert (e->expr_type == EXPR_COMPCALL);
5282
5283   if (e->value.compcall.base_object)
5284     po = gfc_copy_expr (e->value.compcall.base_object);
5285   else
5286     {
5287       po = gfc_get_expr ();
5288       po->expr_type = EXPR_VARIABLE;
5289       po->symtree = e->symtree;
5290       po->ref = gfc_copy_ref (e->ref);
5291       po->where = e->where;
5292     }
5293
5294   if (gfc_resolve_expr (po) == FAILURE)
5295     return NULL;
5296
5297   return po;
5298 }
5299
5300
5301 /* Update the arglist of an EXPR_COMPCALL expression to include the
5302    passed-object.  */
5303
5304 static gfc_try
5305 update_compcall_arglist (gfc_expr* e)
5306 {
5307   gfc_expr* po;
5308   gfc_typebound_proc* tbp;
5309
5310   tbp = e->value.compcall.tbp;
5311
5312   if (tbp->error)
5313     return FAILURE;
5314
5315   po = extract_compcall_passed_object (e);
5316   if (!po)
5317     return FAILURE;
5318
5319   if (tbp->nopass || e->value.compcall.ignore_pass)
5320     {
5321       gfc_free_expr (po);
5322       return SUCCESS;
5323     }
5324
5325   gcc_assert (tbp->pass_arg_num > 0);
5326   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5327                                                   tbp->pass_arg_num,
5328                                                   tbp->pass_arg);
5329
5330   return SUCCESS;
5331 }
5332
5333
5334 /* Extract the passed object from a PPC call (a copy of it).  */
5335
5336 static gfc_expr*
5337 extract_ppc_passed_object (gfc_expr *e)
5338 {
5339   gfc_expr *po;
5340   gfc_ref **ref;
5341
5342   po = gfc_get_expr ();
5343   po->expr_type = EXPR_VARIABLE;
5344   po->symtree = e->symtree;
5345   po->ref = gfc_copy_ref (e->ref);
5346   po->where = e->where;
5347
5348   /* Remove PPC reference.  */
5349   ref = &po->ref;
5350   while ((*ref)->next)
5351     ref = &(*ref)->next;
5352   gfc_free_ref_list (*ref);
5353   *ref = NULL;
5354
5355   if (gfc_resolve_expr (po) == FAILURE)
5356     return NULL;
5357
5358   return po;
5359 }
5360
5361
5362 /* Update the actual arglist of a procedure pointer component to include the
5363    passed-object.  */
5364
5365 static gfc_try
5366 update_ppc_arglist (gfc_expr* e)
5367 {
5368   gfc_expr* po;
5369   gfc_component *ppc;
5370   gfc_typebound_proc* tb;
5371
5372   if (!gfc_is_proc_ptr_comp (e, &ppc))
5373     return FAILURE;
5374
5375   tb = ppc->tb;
5376
5377   if (tb->error)
5378     return FAILURE;
5379   else if (tb->nopass)
5380     return SUCCESS;
5381
5382   po = extract_ppc_passed_object (e);
5383   if (!po)
5384     return FAILURE;
5385
5386   if (po->rank > 0)
5387     {
5388       gfc_error ("Passed-object at %L must be scalar", &e->where);
5389       return FAILURE;
5390     }
5391
5392   gcc_assert (tb->pass_arg_num > 0);
5393   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5394                                                   tb->pass_arg_num,
5395                                                   tb->pass_arg);
5396
5397   return SUCCESS;
5398 }
5399
5400
5401 /* Check that the object a TBP is called on is valid, i.e. it must not be
5402    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5403
5404 static gfc_try
5405 check_typebound_baseobject (gfc_expr* e)
5406 {
5407   gfc_expr* base;
5408   gfc_try return_value = FAILURE;
5409
5410   base = extract_compcall_passed_object (e);
5411   if (!base)
5412     return FAILURE;
5413
5414   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5415
5416   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5417     {
5418       gfc_error ("Base object for type-bound procedure call at %L is of"
5419                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5420       goto cleanup;
5421     }
5422
5423   /* If the procedure called is NOPASS, the base object must be scalar.  */
5424   if (e->value.compcall.tbp->nopass && base->rank > 0)
5425     {
5426       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5427                  " be scalar", &e->where);
5428       goto cleanup;
5429     }
5430
5431   /* FIXME: Remove once PR 41177 (this problem) is fixed completely.  */
5432   if (base->rank > 0)
5433     {
5434       gfc_error ("Non-scalar base object at %L currently not implemented",
5435                  &e->where);
5436       goto cleanup;
5437     }
5438
5439   return_value = SUCCESS;
5440
5441 cleanup:
5442   gfc_free_expr (base);
5443   return return_value;
5444 }
5445
5446
5447 /* Resolve a call to a type-bound procedure, either function or subroutine,
5448    statically from the data in an EXPR_COMPCALL expression.  The adapted
5449    arglist and the target-procedure symtree are returned.  */
5450
5451 static gfc_try
5452 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5453                           gfc_actual_arglist** actual)
5454 {
5455   gcc_assert (e->expr_type == EXPR_COMPCALL);
5456   gcc_assert (!e->value.compcall.tbp->is_generic);
5457
5458   /* Update the actual arglist for PASS.  */
5459   if (update_compcall_arglist (e) == FAILURE)
5460     return FAILURE;
5461
5462   *actual = e->value.compcall.actual;
5463   *target = e->value.compcall.tbp->u.specific;
5464
5465   gfc_free_ref_list (e->ref);
5466   e->ref = NULL;
5467   e->value.compcall.actual = NULL;
5468
5469   return SUCCESS;
5470 }
5471
5472
5473 /* Get the ultimate declared type from an expression.  In addition,
5474    return the last class/derived type reference and the copy of the
5475    reference list.  */
5476 static gfc_symbol*
5477 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5478                         gfc_expr *e)
5479 {
5480   gfc_symbol *declared;
5481   gfc_ref *ref;
5482
5483   declared = NULL;
5484   if (class_ref)
5485     *class_ref = NULL;
5486   if (new_ref)
5487     *new_ref = gfc_copy_ref (e->ref);
5488
5489   for (ref = e->ref; ref; ref = ref->next)
5490     {
5491       if (ref->type != REF_COMPONENT)
5492         continue;
5493
5494       if (ref->u.c.component->ts.type == BT_CLASS
5495             || ref->u.c.component->ts.type == BT_DERIVED)
5496         {
5497           declared = ref->u.c.component->ts.u.derived;
5498           if (class_ref)
5499             *class_ref = ref;
5500         }
5501     }
5502
5503   if (declared == NULL)
5504     declared = e->symtree->n.sym->ts.u.derived;
5505
5506   return declared;
5507 }
5508
5509
5510 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5511    which of the specific bindings (if any) matches the arglist and transform
5512    the expression into a call of that binding.  */
5513
5514 static gfc_try
5515 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5516 {
5517   gfc_typebound_proc* genproc;
5518   const char* genname;
5519   gfc_symtree *st;
5520   gfc_symbol *derived;
5521
5522   gcc_assert (e->expr_type == EXPR_COMPCALL);
5523   genname = e->value.compcall.name;
5524   genproc = e->value.compcall.tbp;
5525
5526   if (!genproc->is_generic)
5527     return SUCCESS;
5528
5529   /* Try the bindings on this type and in the inheritance hierarchy.  */
5530   for (; genproc; genproc = genproc->overridden)
5531     {
5532       gfc_tbp_generic* g;
5533
5534       gcc_assert (genproc->is_generic);
5535       for (g = genproc->u.generic; g; g = g->next)
5536         {
5537           gfc_symbol* target;
5538           gfc_actual_arglist* args;
5539           bool matches;
5540
5541           gcc_assert (g->specific);
5542
5543           if (g->specific->error)
5544             continue;
5545
5546           target = g->specific->u.specific->n.sym;
5547
5548           /* Get the right arglist by handling PASS/NOPASS.  */
5549           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5550           if (!g->specific->nopass)
5551             {
5552               gfc_expr* po;
5553               po = extract_compcall_passed_object (e);
5554               if (!po)
5555                 return FAILURE;
5556
5557               gcc_assert (g->specific->pass_arg_num > 0);
5558               gcc_assert (!g->specific->error);
5559               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5560                                           g->specific->pass_arg);
5561             }
5562           resolve_actual_arglist (args, target->attr.proc,
5563                                   is_external_proc (target) && !target->formal);
5564
5565           /* Check if this arglist matches the formal.  */
5566           matches = gfc_arglist_matches_symbol (&args, target);
5567
5568           /* Clean up and break out of the loop if we've found it.  */
5569           gfc_free_actual_arglist (args);
5570           if (matches)
5571             {
5572               e->value.compcall.tbp = g->specific;
5573               genname = g->specific_st->name;
5574               /* Pass along the name for CLASS methods, where the vtab
5575                  procedure pointer component has to be referenced.  */
5576               if (name)
5577                 *name = genname;
5578               goto success;
5579             }
5580         }
5581     }
5582
5583   /* Nothing matching found!  */
5584   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5585              " '%s' at %L", genname, &e->where);
5586   return FAILURE;
5587
5588 success:
5589   /* Make sure that we have the right specific instance for the name.  */
5590   derived = get_declared_from_expr (NULL, NULL, e);
5591
5592   st = gfc_find_typebound_proc (derived, NULL, genname, false, &e->where);
5593   if (st)
5594     e->value.compcall.tbp = st->n.tb;
5595
5596   return SUCCESS;
5597 }
5598
5599
5600 /* Resolve a call to a type-bound subroutine.  */
5601
5602 static gfc_try
5603 resolve_typebound_call (gfc_code* c, const char **name)
5604 {
5605   gfc_actual_arglist* newactual;
5606   gfc_symtree* target;
5607
5608   /* Check that's really a SUBROUTINE.  */
5609   if (!c->expr1->value.compcall.tbp->subroutine)
5610     {
5611       gfc_error ("'%s' at %L should be a SUBROUTINE",
5612                  c->expr1->value.compcall.name, &c->loc);
5613       return FAILURE;
5614     }
5615
5616   if (check_typebound_baseobject (c->expr1) == FAILURE)
5617     return FAILURE;
5618
5619   /* Pass along the name for CLASS methods, where the vtab
5620      procedure pointer component has to be referenced.  */
5621   if (name)
5622     *name = c->expr1->value.compcall.name;
5623
5624   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5625     return FAILURE;
5626
5627   /* Transform into an ordinary EXEC_CALL for now.  */
5628
5629   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5630     return FAILURE;
5631
5632   c->ext.actual = newactual;
5633   c->symtree = target;
5634   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5635
5636   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5637
5638   gfc_free_expr (c->expr1);
5639   c->expr1 = gfc_get_expr ();
5640   c->expr1->expr_type = EXPR_FUNCTION;
5641   c->expr1->symtree = target;
5642   c->expr1->where = c->loc;
5643
5644   return resolve_call (c);
5645 }
5646
5647
5648 /* Resolve a component-call expression.  */
5649 static gfc_try
5650 resolve_compcall (gfc_expr* e, const char **name)
5651 {
5652   gfc_actual_arglist* newactual;
5653   gfc_symtree* target;
5654
5655   /* Check that's really a FUNCTION.  */
5656   if (!e->value.compcall.tbp->function)
5657     {
5658       gfc_error ("'%s' at %L should be a FUNCTION",
5659                  e->value.compcall.name, &e->where);
5660       return FAILURE;
5661     }
5662
5663   /* These must not be assign-calls!  */
5664   gcc_assert (!e->value.compcall.assign);
5665
5666   if (check_typebound_baseobject (e) == FAILURE)
5667     return FAILURE;
5668
5669   /* Pass along the name for CLASS methods, where the vtab
5670      procedure pointer component has to be referenced.  */
5671   if (name)
5672     *name = e->value.compcall.name;
5673
5674   if (resolve_typebound_generic_call (e, name) == FAILURE)
5675     return FAILURE;
5676   gcc_assert (!e->value.compcall.tbp->is_generic);
5677
5678   /* Take the rank from the function's symbol.  */
5679   if (e->value.compcall.tbp->u.specific->n.sym->as)
5680     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5681
5682   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5683      arglist to the TBP's binding target.  */
5684
5685   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5686     return FAILURE;
5687
5688   e->value.function.actual = newactual;
5689   e->value.function.name = NULL;
5690   e->value.function.esym = target->n.sym;
5691   e->value.function.isym = NULL;
5692   e->symtree = target;
5693   e->ts = target->n.sym->ts;
5694   e->expr_type = EXPR_FUNCTION;
5695
5696   /* Resolution is not necessary if this is a class subroutine; this
5697      function only has to identify the specific proc. Resolution of
5698      the call will be done next in resolve_typebound_call.  */
5699   return gfc_resolve_expr (e);
5700 }
5701
5702
5703
5704 /* Resolve a typebound function, or 'method'. First separate all
5705    the non-CLASS references by calling resolve_compcall directly.  */
5706
5707 static gfc_try
5708 resolve_typebound_function (gfc_expr* e)
5709 {
5710   gfc_symbol *declared;
5711   gfc_component *c;
5712   gfc_ref *new_ref;
5713   gfc_ref *class_ref;
5714   gfc_symtree *st;
5715   const char *name;
5716   gfc_typespec ts;
5717   gfc_expr *expr;
5718
5719   st = e->symtree;
5720
5721   /* Deal with typebound operators for CLASS objects.  */
5722   expr = e->value.compcall.base_object;
5723   if (expr && expr->ts.type == BT_CLASS && e->value.compcall.name)
5724     {
5725       /* Since the typebound operators are generic, we have to ensure
5726          that any delays in resolution are corrected and that the vtab
5727          is present.  */
5728       ts = expr->ts;
5729       declared = ts.u.derived;
5730       c = gfc_find_component (declared, "_vptr", true, true);
5731       if (c->ts.u.derived == NULL)
5732         c->ts.u.derived = gfc_find_derived_vtab (declared);
5733
5734       if (resolve_compcall (e, &name) == FAILURE)
5735         return FAILURE;
5736
5737       /* Use the generic name if it is there.  */
5738       name = name ? name : e->value.function.esym->name;
5739       e->symtree = expr->symtree;
5740       e->ref = gfc_copy_ref (expr->ref);
5741       gfc_add_vptr_component (e);
5742       gfc_add_component_ref (e, name);
5743       e->value.function.esym = NULL;
5744       return SUCCESS;
5745     }
5746
5747   if (st == NULL)
5748     return resolve_compcall (e, NULL);
5749
5750   if (resolve_ref (e) == FAILURE)
5751     return FAILURE;
5752
5753   /* Get the CLASS declared type.  */
5754   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5755
5756   /* Weed out cases of the ultimate component being a derived type.  */
5757   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5758          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5759     {
5760       gfc_free_ref_list (new_ref);
5761       return resolve_compcall (e, NULL);
5762     }
5763
5764   c = gfc_find_component (declared, "_data", true, true);
5765   declared = c->ts.u.derived;
5766
5767   /* Treat the call as if it is a typebound procedure, in order to roll
5768      out the correct name for the specific function.  */
5769   if (resolve_compcall (e, &name) == FAILURE)
5770     return FAILURE;
5771   ts = e->ts;
5772
5773   /* Then convert the expression to a procedure pointer component call.  */
5774   e->value.function.esym = NULL;
5775   e->symtree = st;
5776
5777   if (new_ref)  
5778     e->ref = new_ref;
5779
5780   /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5781   gfc_add_vptr_component (e);
5782   gfc_add_component_ref (e, name);
5783
5784   /* Recover the typespec for the expression.  This is really only
5785      necessary for generic procedures, where the additional call
5786      to gfc_add_component_ref seems to throw the collection of the
5787      correct typespec.  */
5788   e->ts = ts;
5789   return SUCCESS;
5790 }
5791
5792 /* Resolve a typebound subroutine, or 'method'. First separate all
5793    the non-CLASS references by calling resolve_typebound_call
5794    directly.  */
5795
5796 static gfc_try
5797 resolve_typebound_subroutine (gfc_code *code)
5798 {
5799   gfc_symbol *declared;
5800   gfc_component *c;
5801   gfc_ref *new_ref;
5802   gfc_ref *class_ref;
5803   gfc_symtree *st;
5804   const char *name;
5805   gfc_typespec ts;
5806   gfc_expr *expr;
5807
5808   st = code->expr1->symtree;
5809
5810   /* Deal with typebound operators for CLASS objects.  */
5811   expr = code->expr1->value.compcall.base_object;
5812   if (expr && expr->symtree->n.sym->ts.type == BT_CLASS
5813         && code->expr1->value.compcall.name)
5814     {
5815       /* Since the typebound operators are generic, we have to ensure
5816          that any delays in resolution are corrected and that the vtab
5817          is present.  */
5818       ts = expr->symtree->n.sym->ts;
5819       declared = ts.u.derived;
5820       c = gfc_find_component (declared, "_vptr", true, true);
5821       if (c->ts.u.derived == NULL)
5822         c->ts.u.derived = gfc_find_derived_vtab (declared);
5823
5824       if (resolve_typebound_call (code, &name) == FAILURE)
5825         return FAILURE;
5826
5827       /* Use the generic name if it is there.  */
5828       name = name ? name : code->expr1->value.function.esym->name;
5829       code->expr1->symtree = expr->symtree;
5830       expr->symtree->n.sym->ts.u.derived = declared;
5831       gfc_add_vptr_component (code->expr1);
5832       gfc_add_component_ref (code->expr1, name);
5833       code->expr1->value.function.esym = NULL;
5834       return SUCCESS;
5835     }
5836
5837   if (st == NULL)
5838     return resolve_typebound_call (code, NULL);
5839
5840   if (resolve_ref (code->expr1) == FAILURE)
5841     return FAILURE;
5842
5843   /* Get the CLASS declared type.  */
5844   get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5845
5846   /* Weed out cases of the ultimate component being a derived type.  */
5847   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5848          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5849     {
5850       gfc_free_ref_list (new_ref);
5851       return resolve_typebound_call (code, NULL);
5852     }
5853
5854   if (resolve_typebound_call (code, &name) == FAILURE)
5855     return FAILURE;
5856   ts = code->expr1->ts;
5857
5858   /* Then convert the expression to a procedure pointer component call.  */
5859   code->expr1->value.function.esym = NULL;
5860   code->expr1->symtree = st;
5861
5862   if (new_ref)
5863     code->expr1->ref = new_ref;
5864
5865   /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5866   gfc_add_vptr_component (code->expr1);
5867   gfc_add_component_ref (code->expr1, name);
5868
5869   /* Recover the typespec for the expression.  This is really only
5870      necessary for generic procedures, where the additional call
5871      to gfc_add_component_ref seems to throw the collection of the
5872      correct typespec.  */
5873   code->expr1->ts = ts;
5874   return SUCCESS;
5875 }
5876
5877
5878 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5879
5880 static gfc_try
5881 resolve_ppc_call (gfc_code* c)
5882 {
5883   gfc_component *comp;
5884   bool b;
5885
5886   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5887   gcc_assert (b);
5888
5889   c->resolved_sym = c->expr1->symtree->n.sym;
5890   c->expr1->expr_type = EXPR_VARIABLE;
5891
5892   if (!comp->attr.subroutine)
5893     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5894
5895   if (resolve_ref (c->expr1) == FAILURE)
5896     return FAILURE;
5897
5898   if (update_ppc_arglist (c->expr1) == FAILURE)
5899     return FAILURE;
5900
5901   c->ext.actual = c->expr1->value.compcall.actual;
5902
5903   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5904                               comp->formal == NULL) == FAILURE)
5905     return FAILURE;
5906
5907   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
5908
5909   return SUCCESS;
5910 }
5911
5912
5913 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
5914
5915 static gfc_try
5916 resolve_expr_ppc (gfc_expr* e)
5917 {
5918   gfc_component *comp;
5919   bool b;
5920
5921   b = gfc_is_proc_ptr_comp (e, &comp);
5922   gcc_assert (b);
5923
5924   /* Convert to EXPR_FUNCTION.  */
5925   e->expr_type = EXPR_FUNCTION;
5926   e->value.function.isym = NULL;
5927   e->value.function.actual = e->value.compcall.actual;
5928   e->ts = comp->ts;
5929   if (comp->as != NULL)
5930     e->rank = comp->as->rank;
5931
5932   if (!comp->attr.function)
5933     gfc_add_function (&comp->attr, comp->name, &e->where);
5934
5935   if (resolve_ref (e) == FAILURE)
5936     return FAILURE;
5937
5938   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
5939                               comp->formal == NULL) == FAILURE)
5940     return FAILURE;
5941
5942   if (update_ppc_arglist (e) == FAILURE)
5943     return FAILURE;
5944
5945   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
5946
5947   return SUCCESS;
5948 }
5949
5950
5951 static bool
5952 gfc_is_expandable_expr (gfc_expr *e)
5953 {
5954   gfc_constructor *con;
5955
5956   if (e->expr_type == EXPR_ARRAY)
5957     {
5958       /* Traverse the constructor looking for variables that are flavor
5959          parameter.  Parameters must be expanded since they are fully used at
5960          compile time.  */
5961       con = gfc_constructor_first (e->value.constructor);
5962       for (; con; con = gfc_constructor_next (con))
5963         {
5964           if (con->expr->expr_type == EXPR_VARIABLE
5965               && con->expr->symtree
5966               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
5967               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
5968             return true;
5969           if (con->expr->expr_type == EXPR_ARRAY
5970               && gfc_is_expandable_expr (con->expr))
5971             return true;
5972         }
5973     }
5974
5975   return false;
5976 }
5977
5978 /* Resolve an expression.  That is, make sure that types of operands agree
5979    with their operators, intrinsic operators are converted to function calls
5980    for overloaded types and unresolved function references are resolved.  */
5981
5982 gfc_try
5983 gfc_resolve_expr (gfc_expr *e)
5984 {
5985   gfc_try t;
5986   bool inquiry_save;
5987
5988   if (e == NULL)
5989     return SUCCESS;
5990
5991   /* inquiry_argument only applies to variables.  */
5992   inquiry_save = inquiry_argument;
5993   if (e->expr_type != EXPR_VARIABLE)
5994     inquiry_argument = false;
5995
5996   switch (e->expr_type)
5997     {
5998     case EXPR_OP:
5999       t = resolve_operator (e);
6000       break;
6001
6002     case EXPR_FUNCTION:
6003     case EXPR_VARIABLE:
6004
6005       if (check_host_association (e))
6006         t = resolve_function (e);
6007       else
6008         {
6009           t = resolve_variable (e);
6010           if (t == SUCCESS)
6011             expression_rank (e);
6012         }
6013
6014       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6015           && e->ref->type != REF_SUBSTRING)
6016         gfc_resolve_substring_charlen (e);
6017
6018       break;
6019
6020     case EXPR_COMPCALL:
6021       t = resolve_typebound_function (e);
6022       break;
6023
6024     case EXPR_SUBSTRING:
6025       t = resolve_ref (e);
6026       break;
6027
6028     case EXPR_CONSTANT:
6029     case EXPR_NULL:
6030       t = SUCCESS;
6031       break;
6032
6033     case EXPR_PPC:
6034       t = resolve_expr_ppc (e);
6035       break;
6036
6037     case EXPR_ARRAY:
6038       t = FAILURE;
6039       if (resolve_ref (e) == FAILURE)
6040         break;
6041
6042       t = gfc_resolve_array_constructor (e);
6043       /* Also try to expand a constructor.  */
6044       if (t == SUCCESS)
6045         {
6046           expression_rank (e);
6047           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6048             gfc_expand_constructor (e, false);
6049         }
6050
6051       /* This provides the opportunity for the length of constructors with
6052          character valued function elements to propagate the string length
6053          to the expression.  */
6054       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
6055         {
6056           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6057              here rather then add a duplicate test for it above.  */ 
6058           gfc_expand_constructor (e, false);
6059           t = gfc_resolve_character_array_constructor (e);
6060         }
6061
6062       break;
6063
6064     case EXPR_STRUCTURE:
6065       t = resolve_ref (e);
6066       if (t == FAILURE)
6067         break;
6068
6069       t = resolve_structure_cons (e, 0);
6070       if (t == FAILURE)
6071         break;
6072
6073       t = gfc_simplify_expr (e, 0);
6074       break;
6075
6076     default:
6077       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6078     }
6079
6080   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
6081     fixup_charlen (e);
6082
6083   inquiry_argument = inquiry_save;
6084
6085   return t;
6086 }
6087
6088
6089 /* Resolve an expression from an iterator.  They must be scalar and have
6090    INTEGER or (optionally) REAL type.  */
6091
6092 static gfc_try
6093 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6094                            const char *name_msgid)
6095 {
6096   if (gfc_resolve_expr (expr) == FAILURE)
6097     return FAILURE;
6098
6099   if (expr->rank != 0)
6100     {
6101       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6102       return FAILURE;
6103     }
6104
6105   if (expr->ts.type != BT_INTEGER)
6106     {
6107       if (expr->ts.type == BT_REAL)
6108         {
6109           if (real_ok)
6110             return gfc_notify_std (GFC_STD_F95_DEL,
6111                                    "Deleted feature: %s at %L must be integer",
6112                                    _(name_msgid), &expr->where);
6113           else
6114             {
6115               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6116                          &expr->where);
6117               return FAILURE;
6118             }
6119         }
6120       else
6121         {
6122           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6123           return FAILURE;
6124         }
6125     }
6126   return SUCCESS;
6127 }
6128
6129
6130 /* Resolve the expressions in an iterator structure.  If REAL_OK is
6131    false allow only INTEGER type iterators, otherwise allow REAL types.  */
6132
6133 gfc_try
6134 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
6135 {
6136   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
6137       == FAILURE)
6138     return FAILURE;
6139
6140   if (gfc_check_vardef_context (iter->var, false, _("iterator variable"))
6141       == FAILURE)
6142     return FAILURE;
6143
6144   if (gfc_resolve_iterator_expr (iter->start, real_ok,
6145                                  "Start expression in DO loop") == FAILURE)
6146     return FAILURE;
6147
6148   if (gfc_resolve_iterator_expr (iter->end, real_ok,
6149                                  "End expression in DO loop") == FAILURE)
6150     return FAILURE;
6151
6152   if (gfc_resolve_iterator_expr (iter->step, real_ok,
6153                                  "Step expression in DO loop") == FAILURE)
6154     return FAILURE;
6155
6156   if (iter->step->expr_type == EXPR_CONSTANT)
6157     {
6158       if ((iter->step->ts.type == BT_INTEGER
6159            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6160           || (iter->step->ts.type == BT_REAL
6161               && mpfr_sgn (iter->step->value.real) == 0))
6162         {
6163           gfc_error ("Step expression in DO loop at %L cannot be zero",
6164                      &iter->step->where);
6165           return FAILURE;
6166         }
6167     }
6168
6169   /* Convert start, end, and step to the same type as var.  */
6170   if (iter->start->ts.kind != iter->var->ts.kind
6171       || iter->start->ts.type != iter->var->ts.type)
6172     gfc_convert_type (iter->start, &iter->var->ts, 2);
6173
6174   if (iter->end->ts.kind != iter->var->ts.kind
6175       || iter->end->ts.type != iter->var->ts.type)
6176     gfc_convert_type (iter->end, &iter->var->ts, 2);
6177
6178   if (iter->step->ts.kind != iter->var->ts.kind
6179       || iter->step->ts.type != iter->var->ts.type)
6180     gfc_convert_type (iter->step, &iter->var->ts, 2);
6181
6182   if (iter->start->expr_type == EXPR_CONSTANT
6183       && iter->end->expr_type == EXPR_CONSTANT
6184       && iter->step->expr_type == EXPR_CONSTANT)
6185     {
6186       int sgn, cmp;
6187       if (iter->start->ts.type == BT_INTEGER)
6188         {
6189           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6190           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6191         }
6192       else
6193         {
6194           sgn = mpfr_sgn (iter->step->value.real);
6195           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6196         }
6197       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
6198         gfc_warning ("DO loop at %L will be executed zero times",
6199                      &iter->step->where);
6200     }
6201
6202   return SUCCESS;
6203 }
6204
6205
6206 /* Traversal function for find_forall_index.  f == 2 signals that
6207    that variable itself is not to be checked - only the references.  */
6208
6209 static bool
6210 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6211 {
6212   if (expr->expr_type != EXPR_VARIABLE)
6213     return false;
6214   
6215   /* A scalar assignment  */
6216   if (!expr->ref || *f == 1)
6217     {
6218       if (expr->symtree->n.sym == sym)
6219         return true;
6220       else
6221         return false;
6222     }
6223
6224   if (*f == 2)
6225     *f = 1;
6226   return false;
6227 }
6228
6229
6230 /* Check whether the FORALL index appears in the expression or not.
6231    Returns SUCCESS if SYM is found in EXPR.  */
6232
6233 gfc_try
6234 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6235 {
6236   if (gfc_traverse_expr (expr, sym, forall_index, f))
6237     return SUCCESS;
6238   else
6239     return FAILURE;
6240 }
6241
6242
6243 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6244    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6245    INTEGERs, and if stride is a constant it must be nonzero.
6246    Furthermore "A subscript or stride in a forall-triplet-spec shall
6247    not contain a reference to any index-name in the
6248    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6249
6250 static void
6251 resolve_forall_iterators (gfc_forall_iterator *it)
6252 {
6253   gfc_forall_iterator *iter, *iter2;
6254
6255   for (iter = it; iter; iter = iter->next)
6256     {
6257       if (gfc_resolve_expr (iter->var) == SUCCESS
6258           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6259         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6260                    &iter->var->where);
6261
6262       if (gfc_resolve_expr (iter->start) == SUCCESS
6263           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6264         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6265                    &iter->start->where);
6266       if (iter->var->ts.kind != iter->start->ts.kind)
6267         gfc_convert_type (iter->start, &iter->var->ts, 2);
6268
6269       if (gfc_resolve_expr (iter->end) == SUCCESS
6270           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6271         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6272                    &iter->end->where);
6273       if (iter->var->ts.kind != iter->end->ts.kind)
6274         gfc_convert_type (iter->end, &iter->var->ts, 2);
6275
6276       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6277         {
6278           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6279             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6280                        &iter->stride->where, "INTEGER");
6281
6282           if (iter->stride->expr_type == EXPR_CONSTANT
6283               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6284             gfc_error ("FORALL stride expression at %L cannot be zero",
6285                        &iter->stride->where);
6286         }
6287       if (iter->var->ts.kind != iter->stride->ts.kind)
6288         gfc_convert_type (iter->stride, &iter->var->ts, 2);
6289     }
6290
6291   for (iter = it; iter; iter = iter->next)
6292     for (iter2 = iter; iter2; iter2 = iter2->next)
6293       {
6294         if (find_forall_index (iter2->start,
6295                                iter->var->symtree->n.sym, 0) == SUCCESS
6296             || find_forall_index (iter2->end,
6297                                   iter->var->symtree->n.sym, 0) == SUCCESS
6298             || find_forall_index (iter2->stride,
6299                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6300           gfc_error ("FORALL index '%s' may not appear in triplet "
6301                      "specification at %L", iter->var->symtree->name,
6302                      &iter2->start->where);
6303       }
6304 }
6305
6306
6307 /* Given a pointer to a symbol that is a derived type, see if it's
6308    inaccessible, i.e. if it's defined in another module and the components are
6309    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6310    inaccessible components are found, nonzero otherwise.  */
6311
6312 static int
6313 derived_inaccessible (gfc_symbol *sym)
6314 {
6315   gfc_component *c;
6316
6317   if (sym->attr.use_assoc && sym->attr.private_comp)
6318     return 1;
6319
6320   for (c = sym->components; c; c = c->next)
6321     {
6322         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6323           return 1;
6324     }
6325
6326   return 0;
6327 }
6328
6329
6330 /* Resolve the argument of a deallocate expression.  The expression must be
6331    a pointer or a full array.  */
6332
6333 static gfc_try
6334 resolve_deallocate_expr (gfc_expr *e)
6335 {
6336   symbol_attribute attr;
6337   int allocatable, pointer;
6338   gfc_ref *ref;
6339   gfc_symbol *sym;
6340   gfc_component *c;
6341
6342   if (gfc_resolve_expr (e) == FAILURE)
6343     return FAILURE;
6344
6345   if (e->expr_type != EXPR_VARIABLE)
6346     goto bad;
6347
6348   sym = e->symtree->n.sym;
6349
6350   if (sym->ts.type == BT_CLASS)
6351     {
6352       allocatable = CLASS_DATA (sym)->attr.allocatable;
6353       pointer = CLASS_DATA (sym)->attr.class_pointer;
6354     }
6355   else
6356     {
6357       allocatable = sym->attr.allocatable;
6358       pointer = sym->attr.pointer;
6359     }
6360   for (ref = e->ref; ref; ref = ref->next)
6361     {
6362       switch (ref->type)
6363         {
6364         case REF_ARRAY:
6365           if (ref->u.ar.type != AR_FULL)
6366             allocatable = 0;
6367           break;
6368
6369         case REF_COMPONENT:
6370           c = ref->u.c.component;
6371           if (c->ts.type == BT_CLASS)
6372             {
6373               allocatable = CLASS_DATA (c)->attr.allocatable;
6374               pointer = CLASS_DATA (c)->attr.class_pointer;
6375             }
6376           else
6377             {
6378               allocatable = c->attr.allocatable;
6379               pointer = c->attr.pointer;
6380             }
6381           break;
6382
6383         case REF_SUBSTRING:
6384           allocatable = 0;
6385           break;
6386         }
6387     }
6388
6389   attr = gfc_expr_attr (e);
6390
6391   if (allocatable == 0 && attr.pointer == 0)
6392     {
6393     bad:
6394       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6395                  &e->where);
6396       return FAILURE;
6397     }
6398
6399   if (pointer
6400       && gfc_check_vardef_context (e, true, _("DEALLOCATE object")) == FAILURE)
6401     return FAILURE;
6402   if (gfc_check_vardef_context (e, false, _("DEALLOCATE object")) == FAILURE)
6403     return FAILURE;
6404
6405   if (e->ts.type == BT_CLASS)
6406     {
6407       /* Only deallocate the DATA component.  */
6408       gfc_add_data_component (e);
6409     }
6410
6411   return SUCCESS;
6412 }
6413
6414
6415 /* Returns true if the expression e contains a reference to the symbol sym.  */
6416 static bool
6417 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6418 {
6419   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6420     return true;
6421
6422   return false;
6423 }
6424
6425 bool
6426 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6427 {
6428   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6429 }
6430
6431
6432 /* Given the expression node e for an allocatable/pointer of derived type to be
6433    allocated, get the expression node to be initialized afterwards (needed for
6434    derived types with default initializers, and derived types with allocatable
6435    components that need nullification.)  */
6436
6437 gfc_expr *
6438 gfc_expr_to_initialize (gfc_expr *e)
6439 {
6440   gfc_expr *result;
6441   gfc_ref *ref;
6442   int i;
6443
6444   result = gfc_copy_expr (e);
6445
6446   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6447   for (ref = result->ref; ref; ref = ref->next)
6448     if (ref->type == REF_ARRAY && ref->next == NULL)
6449       {
6450         ref->u.ar.type = AR_FULL;
6451
6452         for (i = 0; i < ref->u.ar.dimen; i++)
6453           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6454
6455         result->rank = ref->u.ar.dimen;
6456         break;
6457       }
6458
6459   return result;
6460 }
6461
6462
6463 /* If the last ref of an expression is an array ref, return a copy of the
6464    expression with that one removed.  Otherwise, a copy of the original
6465    expression.  This is used for allocate-expressions and pointer assignment
6466    LHS, where there may be an array specification that needs to be stripped
6467    off when using gfc_check_vardef_context.  */
6468
6469 static gfc_expr*
6470 remove_last_array_ref (gfc_expr* e)
6471 {
6472   gfc_expr* e2;
6473   gfc_ref** r;
6474
6475   e2 = gfc_copy_expr (e);
6476   for (r = &e2->ref; *r; r = &(*r)->next)
6477     if ((*r)->type == REF_ARRAY && !(*r)->next)
6478       {
6479         gfc_free_ref_list (*r);
6480         *r = NULL;
6481         break;
6482       }
6483
6484   return e2;
6485 }
6486
6487
6488 /* Used in resolve_allocate_expr to check that a allocation-object and
6489    a source-expr are conformable.  This does not catch all possible 
6490    cases; in particular a runtime checking is needed.  */
6491
6492 static gfc_try
6493 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6494 {
6495   gfc_ref *tail;
6496   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6497   
6498   /* First compare rank.  */
6499   if (tail && e1->rank != tail->u.ar.as->rank)
6500     {
6501       gfc_error ("Source-expr at %L must be scalar or have the "
6502                  "same rank as the allocate-object at %L",
6503                  &e1->where, &e2->where);
6504       return FAILURE;
6505     }
6506
6507   if (e1->shape)
6508     {
6509       int i;
6510       mpz_t s;
6511
6512       mpz_init (s);
6513
6514       for (i = 0; i < e1->rank; i++)
6515         {
6516           if (tail->u.ar.end[i])
6517             {
6518               mpz_set (s, tail->u.ar.end[i]->value.integer);
6519               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6520               mpz_add_ui (s, s, 1);
6521             }
6522           else
6523             {
6524               mpz_set (s, tail->u.ar.start[i]->value.integer);
6525             }
6526
6527           if (mpz_cmp (e1->shape[i], s) != 0)
6528             {
6529               gfc_error ("Source-expr at %L and allocate-object at %L must "
6530                          "have the same shape", &e1->where, &e2->where);
6531               mpz_clear (s);
6532               return FAILURE;
6533             }
6534         }
6535
6536       mpz_clear (s);
6537     }
6538
6539   return SUCCESS;
6540 }
6541
6542
6543 /* Resolve the expression in an ALLOCATE statement, doing the additional
6544    checks to see whether the expression is OK or not.  The expression must
6545    have a trailing array reference that gives the size of the array.  */
6546
6547 static gfc_try
6548 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6549 {
6550   int i, pointer, allocatable, dimension, is_abstract;
6551   int codimension;
6552   symbol_attribute attr;
6553   gfc_ref *ref, *ref2;
6554   gfc_expr *e2;
6555   gfc_array_ref *ar;
6556   gfc_symbol *sym = NULL;
6557   gfc_alloc *a;
6558   gfc_component *c;
6559   gfc_try t;
6560
6561   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6562      checking of coarrays.  */
6563   for (ref = e->ref; ref; ref = ref->next)
6564     if (ref->next == NULL)
6565       break;
6566
6567   if (ref && ref->type == REF_ARRAY)
6568     ref->u.ar.in_allocate = true;
6569
6570   if (gfc_resolve_expr (e) == FAILURE)
6571     goto failure;
6572
6573   /* Make sure the expression is allocatable or a pointer.  If it is
6574      pointer, the next-to-last reference must be a pointer.  */
6575
6576   ref2 = NULL;
6577   if (e->symtree)
6578     sym = e->symtree->n.sym;
6579
6580   /* Check whether ultimate component is abstract and CLASS.  */
6581   is_abstract = 0;
6582
6583   if (e->expr_type != EXPR_VARIABLE)
6584     {
6585       allocatable = 0;
6586       attr = gfc_expr_attr (e);
6587       pointer = attr.pointer;
6588       dimension = attr.dimension;
6589       codimension = attr.codimension;
6590     }
6591   else
6592     {
6593       if (sym->ts.type == BT_CLASS)
6594         {
6595           allocatable = CLASS_DATA (sym)->attr.allocatable;
6596           pointer = CLASS_DATA (sym)->attr.class_pointer;
6597           dimension = CLASS_DATA (sym)->attr.dimension;
6598           codimension = CLASS_DATA (sym)->attr.codimension;
6599           is_abstract = CLASS_DATA (sym)->attr.abstract;
6600         }
6601       else
6602         {
6603           allocatable = sym->attr.allocatable;
6604           pointer = sym->attr.pointer;
6605           dimension = sym->attr.dimension;
6606           codimension = sym->attr.codimension;
6607         }
6608
6609       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6610         {
6611           switch (ref->type)
6612             {
6613               case REF_ARRAY:
6614                 if (ref->next != NULL)
6615                   pointer = 0;
6616                 break;
6617
6618               case REF_COMPONENT:
6619                 /* F2008, C644.  */
6620                 if (gfc_is_coindexed (e))
6621                   {
6622                     gfc_error ("Coindexed allocatable object at %L",
6623                                &e->where);
6624                     goto failure;
6625                   }
6626
6627                 c = ref->u.c.component;
6628                 if (c->ts.type == BT_CLASS)
6629                   {
6630                     allocatable = CLASS_DATA (c)->attr.allocatable;
6631                     pointer = CLASS_DATA (c)->attr.class_pointer;
6632                     dimension = CLASS_DATA (c)->attr.dimension;
6633                     codimension = CLASS_DATA (c)->attr.codimension;
6634                     is_abstract = CLASS_DATA (c)->attr.abstract;
6635                   }
6636                 else
6637                   {
6638                     allocatable = c->attr.allocatable;
6639                     pointer = c->attr.pointer;
6640                     dimension = c->attr.dimension;
6641                     codimension = c->attr.codimension;
6642                     is_abstract = c->attr.abstract;
6643                   }
6644                 break;
6645
6646               case REF_SUBSTRING:
6647                 allocatable = 0;
6648                 pointer = 0;
6649                 break;
6650             }
6651         }
6652     }
6653
6654   if (allocatable == 0 && pointer == 0)
6655     {
6656       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6657                  &e->where);
6658       goto failure;
6659     }
6660
6661   /* Some checks for the SOURCE tag.  */
6662   if (code->expr3)
6663     {
6664       /* Check F03:C631.  */
6665       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6666         {
6667           gfc_error ("Type of entity at %L is type incompatible with "
6668                       "source-expr at %L", &e->where, &code->expr3->where);
6669           goto failure;
6670         }
6671
6672       /* Check F03:C632 and restriction following Note 6.18.  */
6673       if (code->expr3->rank > 0
6674           && conformable_arrays (code->expr3, e) == FAILURE)
6675         goto failure;
6676
6677       /* Check F03:C633.  */
6678       if (code->expr3->ts.kind != e->ts.kind)
6679         {
6680           gfc_error ("The allocate-object at %L and the source-expr at %L "
6681                       "shall have the same kind type parameter",
6682                       &e->where, &code->expr3->where);
6683           goto failure;
6684         }
6685     }
6686
6687   /* Check F08:C629.  */
6688   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
6689       && !code->expr3)
6690     {
6691       gcc_assert (e->ts.type == BT_CLASS);
6692       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6693                  "type-spec or source-expr", sym->name, &e->where);
6694       goto failure;
6695     }
6696
6697   /* In the variable definition context checks, gfc_expr_attr is used
6698      on the expression.  This is fooled by the array specification
6699      present in e, thus we have to eliminate that one temporarily.  */
6700   e2 = remove_last_array_ref (e);
6701   t = SUCCESS;
6702   if (t == SUCCESS && pointer)
6703     t = gfc_check_vardef_context (e2, true, _("ALLOCATE object"));
6704   if (t == SUCCESS)
6705     t = gfc_check_vardef_context (e2, false, _("ALLOCATE object"));
6706   gfc_free_expr (e2);
6707   if (t == FAILURE)
6708     goto failure;
6709
6710   if (!code->expr3)
6711     {
6712       /* Set up default initializer if needed.  */
6713       gfc_typespec ts;
6714       gfc_expr *init_e;
6715
6716       if (code->ext.alloc.ts.type == BT_DERIVED)
6717         ts = code->ext.alloc.ts;
6718       else
6719         ts = e->ts;
6720
6721       if (ts.type == BT_CLASS)
6722         ts = ts.u.derived->components->ts;
6723
6724       if (ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&ts)))
6725         {
6726           gfc_code *init_st = gfc_get_code ();
6727           init_st->loc = code->loc;
6728           init_st->op = EXEC_INIT_ASSIGN;
6729           init_st->expr1 = gfc_expr_to_initialize (e);
6730           init_st->expr2 = init_e;
6731           init_st->next = code->next;
6732           code->next = init_st;
6733         }
6734     }
6735   else if (code->expr3->mold && code->expr3->ts.type == BT_DERIVED)
6736     {
6737       /* Default initialization via MOLD (non-polymorphic).  */
6738       gfc_expr *rhs = gfc_default_initializer (&code->expr3->ts);
6739       gfc_resolve_expr (rhs);
6740       gfc_free_expr (code->expr3);
6741       code->expr3 = rhs;
6742     }
6743
6744   if (e->ts.type == BT_CLASS)
6745     {
6746       /* Make sure the vtab symbol is present when
6747          the module variables are generated.  */
6748       gfc_typespec ts = e->ts;
6749       if (code->expr3)
6750         ts = code->expr3->ts;
6751       else if (code->ext.alloc.ts.type == BT_DERIVED)
6752         ts = code->ext.alloc.ts;
6753       gfc_find_derived_vtab (ts.u.derived);
6754     }
6755
6756   if (pointer || (dimension == 0 && codimension == 0))
6757     goto success;
6758
6759   /* Make sure the last reference node is an array specifiction.  */
6760
6761   if (!ref2 || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
6762       || (dimension && ref2->u.ar.dimen == 0))
6763     {
6764       gfc_error ("Array specification required in ALLOCATE statement "
6765                  "at %L", &e->where);
6766       goto failure;
6767     }
6768
6769   /* Make sure that the array section reference makes sense in the
6770     context of an ALLOCATE specification.  */
6771
6772   ar = &ref2->u.ar;
6773
6774   if (codimension && ar->codimen == 0)
6775     {
6776       gfc_error ("Coarray specification required in ALLOCATE statement "
6777                  "at %L", &e->where);
6778       goto failure;
6779     }
6780
6781   for (i = 0; i < ar->dimen; i++)
6782     {
6783       if (ref2->u.ar.type == AR_ELEMENT)
6784         goto check_symbols;
6785
6786       switch (ar->dimen_type[i])
6787         {
6788         case DIMEN_ELEMENT:
6789           break;
6790
6791         case DIMEN_RANGE:
6792           if (ar->start[i] != NULL
6793               && ar->end[i] != NULL
6794               && ar->stride[i] == NULL)
6795             break;
6796
6797           /* Fall Through...  */
6798
6799         case DIMEN_UNKNOWN:
6800         case DIMEN_VECTOR:
6801         case DIMEN_STAR:
6802           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6803                      &e->where);
6804           goto failure;
6805         }
6806
6807 check_symbols:
6808       for (a = code->ext.alloc.list; a; a = a->next)
6809         {
6810           sym = a->expr->symtree->n.sym;
6811
6812           /* TODO - check derived type components.  */
6813           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6814             continue;
6815
6816           if ((ar->start[i] != NULL
6817                && gfc_find_sym_in_expr (sym, ar->start[i]))
6818               || (ar->end[i] != NULL
6819                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6820             {
6821               gfc_error ("'%s' must not appear in the array specification at "
6822                          "%L in the same ALLOCATE statement where it is "
6823                          "itself allocated", sym->name, &ar->where);
6824               goto failure;
6825             }
6826         }
6827     }
6828
6829   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
6830     {
6831       if (ar->dimen_type[i] == DIMEN_ELEMENT
6832           || ar->dimen_type[i] == DIMEN_RANGE)
6833         {
6834           if (i == (ar->dimen + ar->codimen - 1))
6835             {
6836               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
6837                          "statement at %L", &e->where);
6838               goto failure;
6839             }
6840           break;
6841         }
6842
6843       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
6844           && ar->stride[i] == NULL)
6845         break;
6846
6847       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
6848                  &e->where);
6849       goto failure;
6850     }
6851
6852   if (codimension && ar->as->rank == 0)
6853     {
6854       gfc_error ("Sorry, allocatable scalar coarrays are not yet supported "
6855                  "at %L", &e->where);
6856       goto failure;
6857     }
6858
6859 success:
6860   if (e->ts.deferred)
6861     {
6862       gfc_error ("Support for entity at %L with deferred type parameter "
6863                  "not yet implemented", &e->where);
6864       return FAILURE;
6865     }
6866   return SUCCESS;
6867
6868 failure:
6869   return FAILURE;
6870 }
6871
6872 static void
6873 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6874 {
6875   gfc_expr *stat, *errmsg, *pe, *qe;
6876   gfc_alloc *a, *p, *q;
6877
6878   stat = code->expr1;
6879   errmsg = code->expr2;
6880
6881   /* Check the stat variable.  */
6882   if (stat)
6883     {
6884       gfc_check_vardef_context (stat, false, _("STAT variable"));
6885
6886       if ((stat->ts.type != BT_INTEGER
6887            && !(stat->ref && (stat->ref->type == REF_ARRAY
6888                               || stat->ref->type == REF_COMPONENT)))
6889           || stat->rank > 0)
6890         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6891                    "variable", &stat->where);
6892
6893       for (p = code->ext.alloc.list; p; p = p->next)
6894         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6895           {
6896             gfc_ref *ref1, *ref2;
6897             bool found = true;
6898
6899             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
6900                  ref1 = ref1->next, ref2 = ref2->next)
6901               {
6902                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
6903                   continue;
6904                 if (ref1->u.c.component->name != ref2->u.c.component->name)
6905                   {
6906                     found = false;
6907                     break;
6908                   }
6909               }
6910
6911             if (found)
6912               {
6913                 gfc_error ("Stat-variable at %L shall not be %sd within "
6914                            "the same %s statement", &stat->where, fcn, fcn);
6915                 break;
6916               }
6917           }
6918     }
6919
6920   /* Check the errmsg variable.  */
6921   if (errmsg)
6922     {
6923       if (!stat)
6924         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
6925                      &errmsg->where);
6926
6927       gfc_check_vardef_context (errmsg, false, _("ERRMSG variable"));
6928
6929       if ((errmsg->ts.type != BT_CHARACTER
6930            && !(errmsg->ref
6931                 && (errmsg->ref->type == REF_ARRAY
6932                     || errmsg->ref->type == REF_COMPONENT)))
6933           || errmsg->rank > 0 )
6934         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
6935                    "variable", &errmsg->where);
6936
6937       for (p = code->ext.alloc.list; p; p = p->next)
6938         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
6939           {
6940             gfc_ref *ref1, *ref2;
6941             bool found = true;
6942
6943             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
6944                  ref1 = ref1->next, ref2 = ref2->next)
6945               {
6946                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
6947                   continue;
6948                 if (ref1->u.c.component->name != ref2->u.c.component->name)
6949                   {
6950                     found = false;
6951                     break;
6952                   }
6953               }
6954
6955             if (found)
6956               {
6957                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
6958                            "the same %s statement", &errmsg->where, fcn, fcn);
6959                 break;
6960               }
6961           }
6962     }
6963
6964   /* Check that an allocate-object appears only once in the statement.  
6965      FIXME: Checking derived types is disabled.  */
6966   for (p = code->ext.alloc.list; p; p = p->next)
6967     {
6968       pe = p->expr;
6969       if ((pe->ref && pe->ref->type != REF_COMPONENT)
6970            && (pe->symtree->n.sym->ts.type != BT_DERIVED))
6971         {
6972           for (q = p->next; q; q = q->next)
6973             {
6974               qe = q->expr;
6975               if ((qe->ref && qe->ref->type != REF_COMPONENT)
6976                   && (qe->symtree->n.sym->ts.type != BT_DERIVED)
6977                   && (pe->symtree->n.sym->name == qe->symtree->n.sym->name))
6978                 gfc_error ("Allocate-object at %L also appears at %L",
6979                            &pe->where, &qe->where);
6980             }
6981         }
6982     }
6983
6984   if (strcmp (fcn, "ALLOCATE") == 0)
6985     {
6986       for (a = code->ext.alloc.list; a; a = a->next)
6987         resolve_allocate_expr (a->expr, code);
6988     }
6989   else
6990     {
6991       for (a = code->ext.alloc.list; a; a = a->next)
6992         resolve_deallocate_expr (a->expr);
6993     }
6994 }
6995
6996
6997 /************ SELECT CASE resolution subroutines ************/
6998
6999 /* Callback function for our mergesort variant.  Determines interval
7000    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7001    op1 > op2.  Assumes we're not dealing with the default case.  
7002    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7003    There are nine situations to check.  */
7004
7005 static int
7006 compare_cases (const gfc_case *op1, const gfc_case *op2)
7007 {
7008   int retval;
7009
7010   if (op1->low == NULL) /* op1 = (:L)  */
7011     {
7012       /* op2 = (:N), so overlap.  */
7013       retval = 0;
7014       /* op2 = (M:) or (M:N),  L < M  */
7015       if (op2->low != NULL
7016           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7017         retval = -1;
7018     }
7019   else if (op1->high == NULL) /* op1 = (K:)  */
7020     {
7021       /* op2 = (M:), so overlap.  */
7022       retval = 0;
7023       /* op2 = (:N) or (M:N), K > N  */
7024       if (op2->high != NULL
7025           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7026         retval = 1;
7027     }
7028   else /* op1 = (K:L)  */
7029     {
7030       if (op2->low == NULL)       /* op2 = (:N), K > N  */
7031         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7032                  ? 1 : 0;
7033       else if (op2->high == NULL) /* op2 = (M:), L < M  */
7034         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7035                  ? -1 : 0;
7036       else                      /* op2 = (M:N)  */
7037         {
7038           retval =  0;
7039           /* L < M  */
7040           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7041             retval =  -1;
7042           /* K > N  */
7043           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7044             retval =  1;
7045         }
7046     }
7047
7048   return retval;
7049 }
7050
7051
7052 /* Merge-sort a double linked case list, detecting overlap in the
7053    process.  LIST is the head of the double linked case list before it
7054    is sorted.  Returns the head of the sorted list if we don't see any
7055    overlap, or NULL otherwise.  */
7056
7057 static gfc_case *
7058 check_case_overlap (gfc_case *list)
7059 {
7060   gfc_case *p, *q, *e, *tail;
7061   int insize, nmerges, psize, qsize, cmp, overlap_seen;
7062
7063   /* If the passed list was empty, return immediately.  */
7064   if (!list)
7065     return NULL;
7066
7067   overlap_seen = 0;
7068   insize = 1;
7069
7070   /* Loop unconditionally.  The only exit from this loop is a return
7071      statement, when we've finished sorting the case list.  */
7072   for (;;)
7073     {
7074       p = list;
7075       list = NULL;
7076       tail = NULL;
7077
7078       /* Count the number of merges we do in this pass.  */
7079       nmerges = 0;
7080
7081       /* Loop while there exists a merge to be done.  */
7082       while (p)
7083         {
7084           int i;
7085
7086           /* Count this merge.  */
7087           nmerges++;
7088
7089           /* Cut the list in two pieces by stepping INSIZE places
7090              forward in the list, starting from P.  */
7091           psize = 0;
7092           q = p;
7093           for (i = 0; i < insize; i++)
7094             {
7095               psize++;
7096               q = q->right;
7097               if (!q)
7098                 break;
7099             }
7100           qsize = insize;
7101
7102           /* Now we have two lists.  Merge them!  */
7103           while (psize > 0 || (qsize > 0 && q != NULL))
7104             {
7105               /* See from which the next case to merge comes from.  */
7106               if (psize == 0)
7107                 {
7108                   /* P is empty so the next case must come from Q.  */
7109                   e = q;
7110                   q = q->right;
7111                   qsize--;
7112                 }
7113               else if (qsize == 0 || q == NULL)
7114                 {
7115                   /* Q is empty.  */
7116                   e = p;
7117                   p = p->right;
7118                   psize--;
7119                 }
7120               else
7121                 {
7122                   cmp = compare_cases (p, q);
7123                   if (cmp < 0)
7124                     {
7125                       /* The whole case range for P is less than the
7126                          one for Q.  */
7127                       e = p;
7128                       p = p->right;
7129                       psize--;
7130                     }
7131                   else if (cmp > 0)
7132                     {
7133                       /* The whole case range for Q is greater than
7134                          the case range for P.  */
7135                       e = q;
7136                       q = q->right;
7137                       qsize--;
7138                     }
7139                   else
7140                     {
7141                       /* The cases overlap, or they are the same
7142                          element in the list.  Either way, we must
7143                          issue an error and get the next case from P.  */
7144                       /* FIXME: Sort P and Q by line number.  */
7145                       gfc_error ("CASE label at %L overlaps with CASE "
7146                                  "label at %L", &p->where, &q->where);
7147                       overlap_seen = 1;
7148                       e = p;
7149                       p = p->right;
7150                       psize--;
7151                     }
7152                 }
7153
7154                 /* Add the next element to the merged list.  */
7155               if (tail)
7156                 tail->right = e;
7157               else
7158                 list = e;
7159               e->left = tail;
7160               tail = e;
7161             }
7162
7163           /* P has now stepped INSIZE places along, and so has Q.  So
7164              they're the same.  */
7165           p = q;
7166         }
7167       tail->right = NULL;
7168
7169       /* If we have done only one merge or none at all, we've
7170          finished sorting the cases.  */
7171       if (nmerges <= 1)
7172         {
7173           if (!overlap_seen)
7174             return list;
7175           else
7176             return NULL;
7177         }
7178
7179       /* Otherwise repeat, merging lists twice the size.  */
7180       insize *= 2;
7181     }
7182 }
7183
7184
7185 /* Check to see if an expression is suitable for use in a CASE statement.
7186    Makes sure that all case expressions are scalar constants of the same
7187    type.  Return FAILURE if anything is wrong.  */
7188
7189 static gfc_try
7190 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7191 {
7192   if (e == NULL) return SUCCESS;
7193
7194   if (e->ts.type != case_expr->ts.type)
7195     {
7196       gfc_error ("Expression in CASE statement at %L must be of type %s",
7197                  &e->where, gfc_basic_typename (case_expr->ts.type));
7198       return FAILURE;
7199     }
7200
7201   /* C805 (R808) For a given case-construct, each case-value shall be of
7202      the same type as case-expr.  For character type, length differences
7203      are allowed, but the kind type parameters shall be the same.  */
7204
7205   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7206     {
7207       gfc_error ("Expression in CASE statement at %L must be of kind %d",
7208                  &e->where, case_expr->ts.kind);
7209       return FAILURE;
7210     }
7211
7212   /* Convert the case value kind to that of case expression kind,
7213      if needed */
7214
7215   if (e->ts.kind != case_expr->ts.kind)
7216     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7217
7218   if (e->rank != 0)
7219     {
7220       gfc_error ("Expression in CASE statement at %L must be scalar",
7221                  &e->where);
7222       return FAILURE;
7223     }
7224
7225   return SUCCESS;
7226 }
7227
7228
7229 /* Given a completely parsed select statement, we:
7230
7231      - Validate all expressions and code within the SELECT.
7232      - Make sure that the selection expression is not of the wrong type.
7233      - Make sure that no case ranges overlap.
7234      - Eliminate unreachable cases and unreachable code resulting from
7235        removing case labels.
7236
7237    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7238    they are a hassle for code generation, and to prevent that, we just
7239    cut them out here.  This is not necessary for overlapping cases
7240    because they are illegal and we never even try to generate code.
7241
7242    We have the additional caveat that a SELECT construct could have
7243    been a computed GOTO in the source code. Fortunately we can fairly
7244    easily work around that here: The case_expr for a "real" SELECT CASE
7245    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7246    we have to do is make sure that the case_expr is a scalar integer
7247    expression.  */
7248
7249 static void
7250 resolve_select (gfc_code *code)
7251 {
7252   gfc_code *body;
7253   gfc_expr *case_expr;
7254   gfc_case *cp, *default_case, *tail, *head;
7255   int seen_unreachable;
7256   int seen_logical;
7257   int ncases;
7258   bt type;
7259   gfc_try t;
7260
7261   if (code->expr1 == NULL)
7262     {
7263       /* This was actually a computed GOTO statement.  */
7264       case_expr = code->expr2;
7265       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7266         gfc_error ("Selection expression in computed GOTO statement "
7267                    "at %L must be a scalar integer expression",
7268                    &case_expr->where);
7269
7270       /* Further checking is not necessary because this SELECT was built
7271          by the compiler, so it should always be OK.  Just move the
7272          case_expr from expr2 to expr so that we can handle computed
7273          GOTOs as normal SELECTs from here on.  */
7274       code->expr1 = code->expr2;
7275       code->expr2 = NULL;
7276       return;
7277     }
7278
7279   case_expr = code->expr1;
7280
7281   type = case_expr->ts.type;
7282   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7283     {
7284       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7285                  &case_expr->where, gfc_typename (&case_expr->ts));
7286
7287       /* Punt. Going on here just produce more garbage error messages.  */
7288       return;
7289     }
7290
7291   if (case_expr->rank != 0)
7292     {
7293       gfc_error ("Argument of SELECT statement at %L must be a scalar "
7294                  "expression", &case_expr->where);
7295
7296       /* Punt.  */
7297       return;
7298     }
7299
7300
7301   /* Raise a warning if an INTEGER case value exceeds the range of
7302      the case-expr. Later, all expressions will be promoted to the
7303      largest kind of all case-labels.  */
7304
7305   if (type == BT_INTEGER)
7306     for (body = code->block; body; body = body->block)
7307       for (cp = body->ext.case_list; cp; cp = cp->next)
7308         {
7309           if (cp->low
7310               && gfc_check_integer_range (cp->low->value.integer,
7311                                           case_expr->ts.kind) != ARITH_OK)
7312             gfc_warning ("Expression in CASE statement at %L is "
7313                          "not in the range of %s", &cp->low->where,
7314                          gfc_typename (&case_expr->ts));
7315
7316           if (cp->high
7317               && cp->low != cp->high
7318               && gfc_check_integer_range (cp->high->value.integer,
7319                                           case_expr->ts.kind) != ARITH_OK)
7320             gfc_warning ("Expression in CASE statement at %L is "
7321                          "not in the range of %s", &cp->high->where,
7322                          gfc_typename (&case_expr->ts));
7323         }
7324
7325   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7326      of the SELECT CASE expression and its CASE values.  Walk the lists
7327      of case values, and if we find a mismatch, promote case_expr to
7328      the appropriate kind.  */
7329
7330   if (type == BT_LOGICAL || type == BT_INTEGER)
7331     {
7332       for (body = code->block; body; body = body->block)
7333         {
7334           /* Walk the case label list.  */
7335           for (cp = body->ext.case_list; cp; cp = cp->next)
7336             {
7337               /* Intercept the DEFAULT case.  It does not have a kind.  */
7338               if (cp->low == NULL && cp->high == NULL)
7339                 continue;
7340
7341               /* Unreachable case ranges are discarded, so ignore.  */
7342               if (cp->low != NULL && cp->high != NULL
7343                   && cp->low != cp->high
7344                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7345                 continue;
7346
7347               if (cp->low != NULL
7348                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7349                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7350
7351               if (cp->high != NULL
7352                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7353                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7354             }
7355          }
7356     }
7357
7358   /* Assume there is no DEFAULT case.  */
7359   default_case = NULL;
7360   head = tail = NULL;
7361   ncases = 0;
7362   seen_logical = 0;
7363
7364   for (body = code->block; body; body = body->block)
7365     {
7366       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7367       t = SUCCESS;
7368       seen_unreachable = 0;
7369
7370       /* Walk the case label list, making sure that all case labels
7371          are legal.  */
7372       for (cp = body->ext.case_list; cp; cp = cp->next)
7373         {
7374           /* Count the number of cases in the whole construct.  */
7375           ncases++;
7376
7377           /* Intercept the DEFAULT case.  */
7378           if (cp->low == NULL && cp->high == NULL)
7379             {
7380               if (default_case != NULL)
7381                 {
7382                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7383                              "by a second DEFAULT CASE at %L",
7384                              &default_case->where, &cp->where);
7385                   t = FAILURE;
7386                   break;
7387                 }
7388               else
7389                 {
7390                   default_case = cp;
7391                   continue;
7392                 }
7393             }
7394
7395           /* Deal with single value cases and case ranges.  Errors are
7396              issued from the validation function.  */
7397           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7398               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7399             {
7400               t = FAILURE;
7401               break;
7402             }
7403
7404           if (type == BT_LOGICAL
7405               && ((cp->low == NULL || cp->high == NULL)
7406                   || cp->low != cp->high))
7407             {
7408               gfc_error ("Logical range in CASE statement at %L is not "
7409                          "allowed", &cp->low->where);
7410               t = FAILURE;
7411               break;
7412             }
7413
7414           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7415             {
7416               int value;
7417               value = cp->low->value.logical == 0 ? 2 : 1;
7418               if (value & seen_logical)
7419                 {
7420                   gfc_error ("Constant logical value in CASE statement "
7421                              "is repeated at %L",
7422                              &cp->low->where);
7423                   t = FAILURE;
7424                   break;
7425                 }
7426               seen_logical |= value;
7427             }
7428
7429           if (cp->low != NULL && cp->high != NULL
7430               && cp->low != cp->high
7431               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7432             {
7433               if (gfc_option.warn_surprising)
7434                 gfc_warning ("Range specification at %L can never "
7435                              "be matched", &cp->where);
7436
7437               cp->unreachable = 1;
7438               seen_unreachable = 1;
7439             }
7440           else
7441             {
7442               /* If the case range can be matched, it can also overlap with
7443                  other cases.  To make sure it does not, we put it in a
7444                  double linked list here.  We sort that with a merge sort
7445                  later on to detect any overlapping cases.  */
7446               if (!head)
7447                 {
7448                   head = tail = cp;
7449                   head->right = head->left = NULL;
7450                 }
7451               else
7452                 {
7453                   tail->right = cp;
7454                   tail->right->left = tail;
7455                   tail = tail->right;
7456                   tail->right = NULL;
7457                 }
7458             }
7459         }
7460
7461       /* It there was a failure in the previous case label, give up
7462          for this case label list.  Continue with the next block.  */
7463       if (t == FAILURE)
7464         continue;
7465
7466       /* See if any case labels that are unreachable have been seen.
7467          If so, we eliminate them.  This is a bit of a kludge because
7468          the case lists for a single case statement (label) is a
7469          single forward linked lists.  */
7470       if (seen_unreachable)
7471       {
7472         /* Advance until the first case in the list is reachable.  */
7473         while (body->ext.case_list != NULL
7474                && body->ext.case_list->unreachable)
7475           {
7476             gfc_case *n = body->ext.case_list;
7477             body->ext.case_list = body->ext.case_list->next;
7478             n->next = NULL;
7479             gfc_free_case_list (n);
7480           }
7481
7482         /* Strip all other unreachable cases.  */
7483         if (body->ext.case_list)
7484           {
7485             for (cp = body->ext.case_list; cp->next; cp = cp->next)
7486               {
7487                 if (cp->next->unreachable)
7488                   {
7489                     gfc_case *n = cp->next;
7490                     cp->next = cp->next->next;
7491                     n->next = NULL;
7492                     gfc_free_case_list (n);
7493                   }
7494               }
7495           }
7496       }
7497     }
7498
7499   /* See if there were overlapping cases.  If the check returns NULL,
7500      there was overlap.  In that case we don't do anything.  If head
7501      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7502      then used during code generation for SELECT CASE constructs with
7503      a case expression of a CHARACTER type.  */
7504   if (head)
7505     {
7506       head = check_case_overlap (head);
7507
7508       /* Prepend the default_case if it is there.  */
7509       if (head != NULL && default_case)
7510         {
7511           default_case->left = NULL;
7512           default_case->right = head;
7513           head->left = default_case;
7514         }
7515     }
7516
7517   /* Eliminate dead blocks that may be the result if we've seen
7518      unreachable case labels for a block.  */
7519   for (body = code; body && body->block; body = body->block)
7520     {
7521       if (body->block->ext.case_list == NULL)
7522         {
7523           /* Cut the unreachable block from the code chain.  */
7524           gfc_code *c = body->block;
7525           body->block = c->block;
7526
7527           /* Kill the dead block, but not the blocks below it.  */
7528           c->block = NULL;
7529           gfc_free_statements (c);
7530         }
7531     }
7532
7533   /* More than two cases is legal but insane for logical selects.
7534      Issue a warning for it.  */
7535   if (gfc_option.warn_surprising && type == BT_LOGICAL
7536       && ncases > 2)
7537     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7538                  &code->loc);
7539 }
7540
7541
7542 /* Check if a derived type is extensible.  */
7543
7544 bool
7545 gfc_type_is_extensible (gfc_symbol *sym)
7546 {
7547   return !(sym->attr.is_bind_c || sym->attr.sequence);
7548 }
7549
7550
7551 /* Resolve an associate name:  Resolve target and ensure the type-spec is
7552    correct as well as possibly the array-spec.  */
7553
7554 static void
7555 resolve_assoc_var (gfc_symbol* sym, bool resolve_target)
7556 {
7557   gfc_expr* target;
7558
7559   gcc_assert (sym->assoc);
7560   gcc_assert (sym->attr.flavor == FL_VARIABLE);
7561
7562   /* If this is for SELECT TYPE, the target may not yet be set.  In that
7563      case, return.  Resolution will be called later manually again when
7564      this is done.  */
7565   target = sym->assoc->target;
7566   if (!target)
7567     return;
7568   gcc_assert (!sym->assoc->dangling);
7569
7570   if (resolve_target && gfc_resolve_expr (target) != SUCCESS)
7571     return;
7572
7573   /* For variable targets, we get some attributes from the target.  */
7574   if (target->expr_type == EXPR_VARIABLE)
7575     {
7576       gfc_symbol* tsym;
7577
7578       gcc_assert (target->symtree);
7579       tsym = target->symtree->n.sym;
7580
7581       sym->attr.asynchronous = tsym->attr.asynchronous;
7582       sym->attr.volatile_ = tsym->attr.volatile_;
7583
7584       sym->attr.target = (tsym->attr.target || tsym->attr.pointer);
7585     }
7586
7587   /* Get type if this was not already set.  Note that it can be
7588      some other type than the target in case this is a SELECT TYPE
7589      selector!  So we must not update when the type is already there.  */
7590   if (sym->ts.type == BT_UNKNOWN)
7591     sym->ts = target->ts;
7592   gcc_assert (sym->ts.type != BT_UNKNOWN);
7593
7594   /* See if this is a valid association-to-variable.  */
7595   sym->assoc->variable = (target->expr_type == EXPR_VARIABLE
7596                           && !gfc_has_vector_subscript (target));
7597
7598   /* Finally resolve if this is an array or not.  */
7599   if (sym->attr.dimension && target->rank == 0)
7600     {
7601       gfc_error ("Associate-name '%s' at %L is used as array",
7602                  sym->name, &sym->declared_at);
7603       sym->attr.dimension = 0;
7604       return;
7605     }
7606   if (target->rank > 0)
7607     sym->attr.dimension = 1;
7608
7609   if (sym->attr.dimension)
7610     {
7611       sym->as = gfc_get_array_spec ();
7612       sym->as->rank = target->rank;
7613       sym->as->type = AS_DEFERRED;
7614
7615       /* Target must not be coindexed, thus the associate-variable
7616          has no corank.  */
7617       sym->as->corank = 0;
7618     }
7619 }
7620
7621
7622 /* Resolve a SELECT TYPE statement.  */
7623
7624 static void
7625 resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
7626 {
7627   gfc_symbol *selector_type;
7628   gfc_code *body, *new_st, *if_st, *tail;
7629   gfc_code *class_is = NULL, *default_case = NULL;
7630   gfc_case *c;
7631   gfc_symtree *st;
7632   char name[GFC_MAX_SYMBOL_LEN];
7633   gfc_namespace *ns;
7634   int error = 0;
7635
7636   ns = code->ext.block.ns;
7637   gfc_resolve (ns);
7638
7639   /* Check for F03:C813.  */
7640   if (code->expr1->ts.type != BT_CLASS
7641       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
7642     {
7643       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
7644                  "at %L", &code->loc);
7645       return;
7646     }
7647
7648   if (code->expr2)
7649     {
7650       if (code->expr1->symtree->n.sym->attr.untyped)
7651         code->expr1->symtree->n.sym->ts = code->expr2->ts;
7652       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
7653     }
7654   else
7655     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
7656
7657   /* Loop over TYPE IS / CLASS IS cases.  */
7658   for (body = code->block; body; body = body->block)
7659     {
7660       c = body->ext.case_list;
7661
7662       /* Check F03:C815.  */
7663       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7664           && !gfc_type_is_extensible (c->ts.u.derived))
7665         {
7666           gfc_error ("Derived type '%s' at %L must be extensible",
7667                      c->ts.u.derived->name, &c->where);
7668           error++;
7669           continue;
7670         }
7671
7672       /* Check F03:C816.  */
7673       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7674           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
7675         {
7676           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
7677                      c->ts.u.derived->name, &c->where, selector_type->name);
7678           error++;
7679           continue;
7680         }
7681
7682       /* Intercept the DEFAULT case.  */
7683       if (c->ts.type == BT_UNKNOWN)
7684         {
7685           /* Check F03:C818.  */
7686           if (default_case)
7687             {
7688               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7689                          "by a second DEFAULT CASE at %L",
7690                          &default_case->ext.case_list->where, &c->where);
7691               error++;
7692               continue;
7693             }
7694
7695           default_case = body;
7696         }
7697     }
7698     
7699   if (error > 0)
7700     return;
7701
7702   /* Transform SELECT TYPE statement to BLOCK and associate selector to
7703      target if present.  If there are any EXIT statements referring to the
7704      SELECT TYPE construct, this is no problem because the gfc_code
7705      reference stays the same and EXIT is equally possible from the BLOCK
7706      it is changed to.  */
7707   code->op = EXEC_BLOCK;
7708   if (code->expr2)
7709     {
7710       gfc_association_list* assoc;
7711
7712       assoc = gfc_get_association_list ();
7713       assoc->st = code->expr1->symtree;
7714       assoc->target = gfc_copy_expr (code->expr2);
7715       /* assoc->variable will be set by resolve_assoc_var.  */
7716       
7717       code->ext.block.assoc = assoc;
7718       code->expr1->symtree->n.sym->assoc = assoc;
7719
7720       resolve_assoc_var (code->expr1->symtree->n.sym, false);
7721     }
7722   else
7723     code->ext.block.assoc = NULL;
7724
7725   /* Add EXEC_SELECT to switch on type.  */
7726   new_st = gfc_get_code ();
7727   new_st->op = code->op;
7728   new_st->expr1 = code->expr1;
7729   new_st->expr2 = code->expr2;
7730   new_st->block = code->block;
7731   code->expr1 = code->expr2 =  NULL;
7732   code->block = NULL;
7733   if (!ns->code)
7734     ns->code = new_st;
7735   else
7736     ns->code->next = new_st;
7737   code = new_st;
7738   code->op = EXEC_SELECT;
7739   gfc_add_vptr_component (code->expr1);
7740   gfc_add_hash_component (code->expr1);
7741
7742   /* Loop over TYPE IS / CLASS IS cases.  */
7743   for (body = code->block; body; body = body->block)
7744     {
7745       c = body->ext.case_list;
7746
7747       if (c->ts.type == BT_DERIVED)
7748         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
7749                                              c->ts.u.derived->hash_value);
7750
7751       else if (c->ts.type == BT_UNKNOWN)
7752         continue;
7753
7754       /* Associate temporary to selector.  This should only be done
7755          when this case is actually true, so build a new ASSOCIATE
7756          that does precisely this here (instead of using the
7757          'global' one).  */
7758
7759       if (c->ts.type == BT_CLASS)
7760         sprintf (name, "__tmp_class_%s", c->ts.u.derived->name);
7761       else
7762         sprintf (name, "__tmp_type_%s", c->ts.u.derived->name);
7763       st = gfc_find_symtree (ns->sym_root, name);
7764       gcc_assert (st->n.sym->assoc);
7765       st->n.sym->assoc->target = gfc_get_variable_expr (code->expr1->symtree);
7766       if (c->ts.type == BT_DERIVED)
7767         gfc_add_data_component (st->n.sym->assoc->target);
7768
7769       new_st = gfc_get_code ();
7770       new_st->op = EXEC_BLOCK;
7771       new_st->ext.block.ns = gfc_build_block_ns (ns);
7772       new_st->ext.block.ns->code = body->next;
7773       body->next = new_st;
7774
7775       /* Chain in the new list only if it is marked as dangling.  Otherwise
7776          there is a CASE label overlap and this is already used.  Just ignore,
7777          the error is diagonsed elsewhere.  */
7778       if (st->n.sym->assoc->dangling)
7779         {
7780           new_st->ext.block.assoc = st->n.sym->assoc;
7781           st->n.sym->assoc->dangling = 0;
7782         }
7783
7784       resolve_assoc_var (st->n.sym, false);
7785     }
7786     
7787   /* Take out CLASS IS cases for separate treatment.  */
7788   body = code;
7789   while (body && body->block)
7790     {
7791       if (body->block->ext.case_list->ts.type == BT_CLASS)
7792         {
7793           /* Add to class_is list.  */
7794           if (class_is == NULL)
7795             { 
7796               class_is = body->block;
7797               tail = class_is;
7798             }
7799           else
7800             {
7801               for (tail = class_is; tail->block; tail = tail->block) ;
7802               tail->block = body->block;
7803               tail = tail->block;
7804             }
7805           /* Remove from EXEC_SELECT list.  */
7806           body->block = body->block->block;
7807           tail->block = NULL;
7808         }
7809       else
7810         body = body->block;
7811     }
7812
7813   if (class_is)
7814     {
7815       gfc_symbol *vtab;
7816       
7817       if (!default_case)
7818         {
7819           /* Add a default case to hold the CLASS IS cases.  */
7820           for (tail = code; tail->block; tail = tail->block) ;
7821           tail->block = gfc_get_code ();
7822           tail = tail->block;
7823           tail->op = EXEC_SELECT_TYPE;
7824           tail->ext.case_list = gfc_get_case ();
7825           tail->ext.case_list->ts.type = BT_UNKNOWN;
7826           tail->next = NULL;
7827           default_case = tail;
7828         }
7829
7830       /* More than one CLASS IS block?  */
7831       if (class_is->block)
7832         {
7833           gfc_code **c1,*c2;
7834           bool swapped;
7835           /* Sort CLASS IS blocks by extension level.  */
7836           do
7837             {
7838               swapped = false;
7839               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
7840                 {
7841                   c2 = (*c1)->block;
7842                   /* F03:C817 (check for doubles).  */
7843                   if ((*c1)->ext.case_list->ts.u.derived->hash_value
7844                       == c2->ext.case_list->ts.u.derived->hash_value)
7845                     {
7846                       gfc_error ("Double CLASS IS block in SELECT TYPE "
7847                                  "statement at %L", &c2->ext.case_list->where);
7848                       return;
7849                     }
7850                   if ((*c1)->ext.case_list->ts.u.derived->attr.extension
7851                       < c2->ext.case_list->ts.u.derived->attr.extension)
7852                     {
7853                       /* Swap.  */
7854                       (*c1)->block = c2->block;
7855                       c2->block = *c1;
7856                       *c1 = c2;
7857                       swapped = true;
7858                     }
7859                 }
7860             }
7861           while (swapped);
7862         }
7863         
7864       /* Generate IF chain.  */
7865       if_st = gfc_get_code ();
7866       if_st->op = EXEC_IF;
7867       new_st = if_st;
7868       for (body = class_is; body; body = body->block)
7869         {
7870           new_st->block = gfc_get_code ();
7871           new_st = new_st->block;
7872           new_st->op = EXEC_IF;
7873           /* Set up IF condition: Call _gfortran_is_extension_of.  */
7874           new_st->expr1 = gfc_get_expr ();
7875           new_st->expr1->expr_type = EXPR_FUNCTION;
7876           new_st->expr1->ts.type = BT_LOGICAL;
7877           new_st->expr1->ts.kind = 4;
7878           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
7879           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
7880           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
7881           /* Set up arguments.  */
7882           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
7883           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
7884           gfc_add_vptr_component (new_st->expr1->value.function.actual->expr);
7885           vtab = gfc_find_derived_vtab (body->ext.case_list->ts.u.derived);
7886           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
7887           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
7888           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
7889           new_st->next = body->next;
7890         }
7891         if (default_case->next)
7892           {
7893             new_st->block = gfc_get_code ();
7894             new_st = new_st->block;
7895             new_st->op = EXEC_IF;
7896             new_st->next = default_case->next;
7897           }
7898           
7899         /* Replace CLASS DEFAULT code by the IF chain.  */
7900         default_case->next = if_st;
7901     }
7902
7903   /* Resolve the internal code.  This can not be done earlier because
7904      it requires that the sym->assoc of selectors is set already.  */
7905   gfc_current_ns = ns;
7906   gfc_resolve_blocks (code->block, gfc_current_ns);
7907   gfc_current_ns = old_ns;
7908
7909   resolve_select (code);
7910 }
7911
7912
7913 /* Resolve a transfer statement. This is making sure that:
7914    -- a derived type being transferred has only non-pointer components
7915    -- a derived type being transferred doesn't have private components, unless 
7916       it's being transferred from the module where the type was defined
7917    -- we're not trying to transfer a whole assumed size array.  */
7918
7919 static void
7920 resolve_transfer (gfc_code *code)
7921 {
7922   gfc_typespec *ts;
7923   gfc_symbol *sym;
7924   gfc_ref *ref;
7925   gfc_expr *exp;
7926
7927   exp = code->expr1;
7928
7929   while (exp != NULL && exp->expr_type == EXPR_OP
7930          && exp->value.op.op == INTRINSIC_PARENTHESES)
7931     exp = exp->value.op.op1;
7932
7933   if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
7934                       && exp->expr_type != EXPR_FUNCTION))
7935     return;
7936
7937   /* If we are reading, the variable will be changed.  Note that
7938      code->ext.dt may be NULL if the TRANSFER is related to
7939      an INQUIRE statement -- but in this case, we are not reading, either.  */
7940   if (code->ext.dt && code->ext.dt->dt_io_kind->value.iokind == M_READ
7941       && gfc_check_vardef_context (exp, false, _("item in READ")) == FAILURE)
7942     return;
7943
7944   sym = exp->symtree->n.sym;
7945   ts = &sym->ts;
7946
7947   /* Go to actual component transferred.  */
7948   for (ref = exp->ref; ref; ref = ref->next)
7949     if (ref->type == REF_COMPONENT)
7950       ts = &ref->u.c.component->ts;
7951
7952   if (ts->type == BT_CLASS)
7953     {
7954       /* FIXME: Test for defined input/output.  */
7955       gfc_error ("Data transfer element at %L cannot be polymorphic unless "
7956                 "it is processed by a defined input/output procedure",
7957                 &code->loc);
7958       return;
7959     }
7960
7961   if (ts->type == BT_DERIVED)
7962     {
7963       /* Check that transferred derived type doesn't contain POINTER
7964          components.  */
7965       if (ts->u.derived->attr.pointer_comp)
7966         {
7967           gfc_error ("Data transfer element at %L cannot have "
7968                      "POINTER components", &code->loc);
7969           return;
7970         }
7971
7972       if (ts->u.derived->attr.alloc_comp)
7973         {
7974           gfc_error ("Data transfer element at %L cannot have "
7975                      "ALLOCATABLE components", &code->loc);
7976           return;
7977         }
7978
7979       if (derived_inaccessible (ts->u.derived))
7980         {
7981           gfc_error ("Data transfer element at %L cannot have "
7982                      "PRIVATE components",&code->loc);
7983           return;
7984         }
7985     }
7986
7987   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
7988       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
7989     {
7990       gfc_error ("Data transfer element at %L cannot be a full reference to "
7991                  "an assumed-size array", &code->loc);
7992       return;
7993     }
7994 }
7995
7996
7997 /*********** Toplevel code resolution subroutines ***********/
7998
7999 /* Find the set of labels that are reachable from this block.  We also
8000    record the last statement in each block.  */
8001      
8002 static void
8003 find_reachable_labels (gfc_code *block)
8004 {
8005   gfc_code *c;
8006
8007   if (!block)
8008     return;
8009
8010   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
8011
8012   /* Collect labels in this block.  We don't keep those corresponding
8013      to END {IF|SELECT}, these are checked in resolve_branch by going
8014      up through the code_stack.  */
8015   for (c = block; c; c = c->next)
8016     {
8017       if (c->here && c->op != EXEC_END_BLOCK)
8018         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
8019     }
8020
8021   /* Merge with labels from parent block.  */
8022   if (cs_base->prev)
8023     {
8024       gcc_assert (cs_base->prev->reachable_labels);
8025       bitmap_ior_into (cs_base->reachable_labels,
8026                        cs_base->prev->reachable_labels);
8027     }
8028 }
8029
8030
8031 static void
8032 resolve_sync (gfc_code *code)
8033 {
8034   /* Check imageset. The * case matches expr1 == NULL.  */
8035   if (code->expr1)
8036     {
8037       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
8038         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
8039                    "INTEGER expression", &code->expr1->where);
8040       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
8041           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
8042         gfc_error ("Imageset argument at %L must between 1 and num_images()",
8043                    &code->expr1->where);
8044       else if (code->expr1->expr_type == EXPR_ARRAY
8045                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
8046         {
8047            gfc_constructor *cons;
8048            cons = gfc_constructor_first (code->expr1->value.constructor);
8049            for (; cons; cons = gfc_constructor_next (cons))
8050              if (cons->expr->expr_type == EXPR_CONSTANT
8051                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
8052                gfc_error ("Imageset argument at %L must between 1 and "
8053                           "num_images()", &cons->expr->where);
8054         }
8055     }
8056
8057   /* Check STAT.  */
8058   if (code->expr2
8059       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8060           || code->expr2->expr_type != EXPR_VARIABLE))
8061     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8062                &code->expr2->where);
8063
8064   /* Check ERRMSG.  */
8065   if (code->expr3
8066       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8067           || code->expr3->expr_type != EXPR_VARIABLE))
8068     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8069                &code->expr3->where);
8070 }
8071
8072
8073 /* Given a branch to a label, see if the branch is conforming.
8074    The code node describes where the branch is located.  */
8075
8076 static void
8077 resolve_branch (gfc_st_label *label, gfc_code *code)
8078 {
8079   code_stack *stack;
8080
8081   if (label == NULL)
8082     return;
8083
8084   /* Step one: is this a valid branching target?  */
8085
8086   if (label->defined == ST_LABEL_UNKNOWN)
8087     {
8088       gfc_error ("Label %d referenced at %L is never defined", label->value,
8089                  &label->where);
8090       return;
8091     }
8092
8093   if (label->defined != ST_LABEL_TARGET)
8094     {
8095       gfc_error ("Statement at %L is not a valid branch target statement "
8096                  "for the branch statement at %L", &label->where, &code->loc);
8097       return;
8098     }
8099
8100   /* Step two: make sure this branch is not a branch to itself ;-)  */
8101
8102   if (code->here == label)
8103     {
8104       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
8105       return;
8106     }
8107
8108   /* Step three:  See if the label is in the same block as the
8109      branching statement.  The hard work has been done by setting up
8110      the bitmap reachable_labels.  */
8111
8112   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8113     {
8114       /* Check now whether there is a CRITICAL construct; if so, check
8115          whether the label is still visible outside of the CRITICAL block,
8116          which is invalid.  */
8117       for (stack = cs_base; stack; stack = stack->prev)
8118         if (stack->current->op == EXEC_CRITICAL
8119             && bitmap_bit_p (stack->reachable_labels, label->value))
8120           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8121                       " at %L", &code->loc, &label->where);
8122
8123       return;
8124     }
8125
8126   /* Step four:  If we haven't found the label in the bitmap, it may
8127     still be the label of the END of the enclosing block, in which
8128     case we find it by going up the code_stack.  */
8129
8130   for (stack = cs_base; stack; stack = stack->prev)
8131     {
8132       if (stack->current->next && stack->current->next->here == label)
8133         break;
8134       if (stack->current->op == EXEC_CRITICAL)
8135         {
8136           /* Note: A label at END CRITICAL does not leave the CRITICAL
8137              construct as END CRITICAL is still part of it.  */
8138           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8139                       " at %L", &code->loc, &label->where);
8140           return;
8141         }
8142     }
8143
8144   if (stack)
8145     {
8146       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
8147       return;
8148     }
8149
8150   /* The label is not in an enclosing block, so illegal.  This was
8151      allowed in Fortran 66, so we allow it as extension.  No
8152      further checks are necessary in this case.  */
8153   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
8154                   "as the GOTO statement at %L", &label->where,
8155                   &code->loc);
8156   return;
8157 }
8158
8159
8160 /* Check whether EXPR1 has the same shape as EXPR2.  */
8161
8162 static gfc_try
8163 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8164 {
8165   mpz_t shape[GFC_MAX_DIMENSIONS];
8166   mpz_t shape2[GFC_MAX_DIMENSIONS];
8167   gfc_try result = FAILURE;
8168   int i;
8169
8170   /* Compare the rank.  */
8171   if (expr1->rank != expr2->rank)
8172     return result;
8173
8174   /* Compare the size of each dimension.  */
8175   for (i=0; i<expr1->rank; i++)
8176     {
8177       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
8178         goto ignore;
8179
8180       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
8181         goto ignore;
8182
8183       if (mpz_cmp (shape[i], shape2[i]))
8184         goto over;
8185     }
8186
8187   /* When either of the two expression is an assumed size array, we
8188      ignore the comparison of dimension sizes.  */
8189 ignore:
8190   result = SUCCESS;
8191
8192 over:
8193   for (i--; i >= 0; i--)
8194     {
8195       mpz_clear (shape[i]);
8196       mpz_clear (shape2[i]);
8197     }
8198   return result;
8199 }
8200
8201
8202 /* Check whether a WHERE assignment target or a WHERE mask expression
8203    has the same shape as the outmost WHERE mask expression.  */
8204
8205 static void
8206 resolve_where (gfc_code *code, gfc_expr *mask)
8207 {
8208   gfc_code *cblock;
8209   gfc_code *cnext;
8210   gfc_expr *e = NULL;
8211
8212   cblock = code->block;
8213
8214   /* Store the first WHERE mask-expr of the WHERE statement or construct.
8215      In case of nested WHERE, only the outmost one is stored.  */
8216   if (mask == NULL) /* outmost WHERE */
8217     e = cblock->expr1;
8218   else /* inner WHERE */
8219     e = mask;
8220
8221   while (cblock)
8222     {
8223       if (cblock->expr1)
8224         {
8225           /* Check if the mask-expr has a consistent shape with the
8226              outmost WHERE mask-expr.  */
8227           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
8228             gfc_error ("WHERE mask at %L has inconsistent shape",
8229                        &cblock->expr1->where);
8230          }
8231
8232       /* the assignment statement of a WHERE statement, or the first
8233          statement in where-body-construct of a WHERE construct */
8234       cnext = cblock->next;
8235       while (cnext)
8236         {
8237           switch (cnext->op)
8238             {
8239             /* WHERE assignment statement */
8240             case EXEC_ASSIGN:
8241
8242               /* Check shape consistent for WHERE assignment target.  */
8243               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
8244                gfc_error ("WHERE assignment target at %L has "
8245                           "inconsistent shape", &cnext->expr1->where);
8246               break;
8247
8248   
8249             case EXEC_ASSIGN_CALL:
8250               resolve_call (cnext);
8251               if (!cnext->resolved_sym->attr.elemental)
8252                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8253                           &cnext->ext.actual->expr->where);
8254               break;
8255
8256             /* WHERE or WHERE construct is part of a where-body-construct */
8257             case EXEC_WHERE:
8258               resolve_where (cnext, e);
8259               break;
8260
8261             default:
8262               gfc_error ("Unsupported statement inside WHERE at %L",
8263                          &cnext->loc);
8264             }
8265          /* the next statement within the same where-body-construct */
8266          cnext = cnext->next;
8267        }
8268     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8269     cblock = cblock->block;
8270   }
8271 }
8272
8273
8274 /* Resolve assignment in FORALL construct.
8275    NVAR is the number of FORALL index variables, and VAR_EXPR records the
8276    FORALL index variables.  */
8277
8278 static void
8279 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8280 {
8281   int n;
8282
8283   for (n = 0; n < nvar; n++)
8284     {
8285       gfc_symbol *forall_index;
8286
8287       forall_index = var_expr[n]->symtree->n.sym;
8288
8289       /* Check whether the assignment target is one of the FORALL index
8290          variable.  */
8291       if ((code->expr1->expr_type == EXPR_VARIABLE)
8292           && (code->expr1->symtree->n.sym == forall_index))
8293         gfc_error ("Assignment to a FORALL index variable at %L",
8294                    &code->expr1->where);
8295       else
8296         {
8297           /* If one of the FORALL index variables doesn't appear in the
8298              assignment variable, then there could be a many-to-one
8299              assignment.  Emit a warning rather than an error because the
8300              mask could be resolving this problem.  */
8301           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
8302             gfc_warning ("The FORALL with index '%s' is not used on the "
8303                          "left side of the assignment at %L and so might "
8304                          "cause multiple assignment to this object",
8305                          var_expr[n]->symtree->name, &code->expr1->where);
8306         }
8307     }
8308 }
8309
8310
8311 /* Resolve WHERE statement in FORALL construct.  */
8312
8313 static void
8314 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
8315                                   gfc_expr **var_expr)
8316 {
8317   gfc_code *cblock;
8318   gfc_code *cnext;
8319
8320   cblock = code->block;
8321   while (cblock)
8322     {
8323       /* the assignment statement of a WHERE statement, or the first
8324          statement in where-body-construct of a WHERE construct */
8325       cnext = cblock->next;
8326       while (cnext)
8327         {
8328           switch (cnext->op)
8329             {
8330             /* WHERE assignment statement */
8331             case EXEC_ASSIGN:
8332               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
8333               break;
8334   
8335             /* WHERE operator assignment statement */
8336             case EXEC_ASSIGN_CALL:
8337               resolve_call (cnext);
8338               if (!cnext->resolved_sym->attr.elemental)
8339                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8340                           &cnext->ext.actual->expr->where);
8341               break;
8342
8343             /* WHERE or WHERE construct is part of a where-body-construct */
8344             case EXEC_WHERE:
8345               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
8346               break;
8347
8348             default:
8349               gfc_error ("Unsupported statement inside WHERE at %L",
8350                          &cnext->loc);
8351             }
8352           /* the next statement within the same where-body-construct */
8353           cnext = cnext->next;
8354         }
8355       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8356       cblock = cblock->block;
8357     }
8358 }
8359
8360
8361 /* Traverse the FORALL body to check whether the following errors exist:
8362    1. For assignment, check if a many-to-one assignment happens.
8363    2. For WHERE statement, check the WHERE body to see if there is any
8364       many-to-one assignment.  */
8365
8366 static void
8367 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
8368 {
8369   gfc_code *c;
8370
8371   c = code->block->next;
8372   while (c)
8373     {
8374       switch (c->op)
8375         {
8376         case EXEC_ASSIGN:
8377         case EXEC_POINTER_ASSIGN:
8378           gfc_resolve_assign_in_forall (c, nvar, var_expr);
8379           break;
8380
8381         case EXEC_ASSIGN_CALL:
8382           resolve_call (c);
8383           break;
8384
8385         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
8386            there is no need to handle it here.  */
8387         case EXEC_FORALL:
8388           break;
8389         case EXEC_WHERE:
8390           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
8391           break;
8392         default:
8393           break;
8394         }
8395       /* The next statement in the FORALL body.  */
8396       c = c->next;
8397     }
8398 }
8399
8400
8401 /* Counts the number of iterators needed inside a forall construct, including
8402    nested forall constructs. This is used to allocate the needed memory 
8403    in gfc_resolve_forall.  */
8404
8405 static int 
8406 gfc_count_forall_iterators (gfc_code *code)
8407 {
8408   int max_iters, sub_iters, current_iters;
8409   gfc_forall_iterator *fa;
8410
8411   gcc_assert(code->op == EXEC_FORALL);
8412   max_iters = 0;
8413   current_iters = 0;
8414
8415   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8416     current_iters ++;
8417   
8418   code = code->block->next;
8419
8420   while (code)
8421     {          
8422       if (code->op == EXEC_FORALL)
8423         {
8424           sub_iters = gfc_count_forall_iterators (code);
8425           if (sub_iters > max_iters)
8426             max_iters = sub_iters;
8427         }
8428       code = code->next;
8429     }
8430
8431   return current_iters + max_iters;
8432 }
8433
8434
8435 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8436    gfc_resolve_forall_body to resolve the FORALL body.  */
8437
8438 static void
8439 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8440 {
8441   static gfc_expr **var_expr;
8442   static int total_var = 0;
8443   static int nvar = 0;
8444   int old_nvar, tmp;
8445   gfc_forall_iterator *fa;
8446   int i;
8447
8448   old_nvar = nvar;
8449
8450   /* Start to resolve a FORALL construct   */
8451   if (forall_save == 0)
8452     {
8453       /* Count the total number of FORALL index in the nested FORALL
8454          construct in order to allocate the VAR_EXPR with proper size.  */
8455       total_var = gfc_count_forall_iterators (code);
8456
8457       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8458       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
8459     }
8460
8461   /* The information about FORALL iterator, including FORALL index start, end
8462      and stride. The FORALL index can not appear in start, end or stride.  */
8463   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8464     {
8465       /* Check if any outer FORALL index name is the same as the current
8466          one.  */
8467       for (i = 0; i < nvar; i++)
8468         {
8469           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8470             {
8471               gfc_error ("An outer FORALL construct already has an index "
8472                          "with this name %L", &fa->var->where);
8473             }
8474         }
8475
8476       /* Record the current FORALL index.  */
8477       var_expr[nvar] = gfc_copy_expr (fa->var);
8478
8479       nvar++;
8480
8481       /* No memory leak.  */
8482       gcc_assert (nvar <= total_var);
8483     }
8484
8485   /* Resolve the FORALL body.  */
8486   gfc_resolve_forall_body (code, nvar, var_expr);
8487
8488   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8489   gfc_resolve_blocks (code->block, ns);
8490
8491   tmp = nvar;
8492   nvar = old_nvar;
8493   /* Free only the VAR_EXPRs allocated in this frame.  */
8494   for (i = nvar; i < tmp; i++)
8495      gfc_free_expr (var_expr[i]);
8496
8497   if (nvar == 0)
8498     {
8499       /* We are in the outermost FORALL construct.  */
8500       gcc_assert (forall_save == 0);
8501
8502       /* VAR_EXPR is not needed any more.  */
8503       gfc_free (var_expr);
8504       total_var = 0;
8505     }
8506 }
8507
8508
8509 /* Resolve a BLOCK construct statement.  */
8510
8511 static void
8512 resolve_block_construct (gfc_code* code)
8513 {
8514   /* Resolve the BLOCK's namespace.  */
8515   gfc_resolve (code->ext.block.ns);
8516
8517   /* For an ASSOCIATE block, the associations (and their targets) are already
8518      resolved during resolve_symbol.  */
8519 }
8520
8521
8522 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
8523    DO code nodes.  */
8524
8525 static void resolve_code (gfc_code *, gfc_namespace *);
8526
8527 void
8528 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8529 {
8530   gfc_try t;
8531
8532   for (; b; b = b->block)
8533     {
8534       t = gfc_resolve_expr (b->expr1);
8535       if (gfc_resolve_expr (b->expr2) == FAILURE)
8536         t = FAILURE;
8537
8538       switch (b->op)
8539         {
8540         case EXEC_IF:
8541           if (t == SUCCESS && b->expr1 != NULL
8542               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8543             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8544                        &b->expr1->where);
8545           break;
8546
8547         case EXEC_WHERE:
8548           if (t == SUCCESS
8549               && b->expr1 != NULL
8550               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8551             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8552                        &b->expr1->where);
8553           break;
8554
8555         case EXEC_GOTO:
8556           resolve_branch (b->label1, b);
8557           break;
8558
8559         case EXEC_BLOCK:
8560           resolve_block_construct (b);
8561           break;
8562
8563         case EXEC_SELECT:
8564         case EXEC_SELECT_TYPE:
8565         case EXEC_FORALL:
8566         case EXEC_DO:
8567         case EXEC_DO_WHILE:
8568         case EXEC_CRITICAL:
8569         case EXEC_READ:
8570         case EXEC_WRITE:
8571         case EXEC_IOLENGTH:
8572         case EXEC_WAIT:
8573           break;
8574
8575         case EXEC_OMP_ATOMIC:
8576         case EXEC_OMP_CRITICAL:
8577         case EXEC_OMP_DO:
8578         case EXEC_OMP_MASTER:
8579         case EXEC_OMP_ORDERED:
8580         case EXEC_OMP_PARALLEL:
8581         case EXEC_OMP_PARALLEL_DO:
8582         case EXEC_OMP_PARALLEL_SECTIONS:
8583         case EXEC_OMP_PARALLEL_WORKSHARE:
8584         case EXEC_OMP_SECTIONS:
8585         case EXEC_OMP_SINGLE:
8586         case EXEC_OMP_TASK:
8587         case EXEC_OMP_TASKWAIT:
8588         case EXEC_OMP_WORKSHARE:
8589           break;
8590
8591         default:
8592           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
8593         }
8594
8595       resolve_code (b->next, ns);
8596     }
8597 }
8598
8599
8600 /* Does everything to resolve an ordinary assignment.  Returns true
8601    if this is an interface assignment.  */
8602 static bool
8603 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
8604 {
8605   bool rval = false;
8606   gfc_expr *lhs;
8607   gfc_expr *rhs;
8608   int llen = 0;
8609   int rlen = 0;
8610   int n;
8611   gfc_ref *ref;
8612
8613   if (gfc_extend_assign (code, ns) == SUCCESS)
8614     {
8615       gfc_expr** rhsptr;
8616
8617       if (code->op == EXEC_ASSIGN_CALL)
8618         {
8619           lhs = code->ext.actual->expr;
8620           rhsptr = &code->ext.actual->next->expr;
8621         }
8622       else
8623         {
8624           gfc_actual_arglist* args;
8625           gfc_typebound_proc* tbp;
8626
8627           gcc_assert (code->op == EXEC_COMPCALL);
8628
8629           args = code->expr1->value.compcall.actual;
8630           lhs = args->expr;
8631           rhsptr = &args->next->expr;
8632
8633           tbp = code->expr1->value.compcall.tbp;
8634           gcc_assert (!tbp->is_generic);
8635         }
8636
8637       /* Make a temporary rhs when there is a default initializer
8638          and rhs is the same symbol as the lhs.  */
8639       if ((*rhsptr)->expr_type == EXPR_VARIABLE
8640             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
8641             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
8642             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
8643         *rhsptr = gfc_get_parentheses (*rhsptr);
8644
8645       return true;
8646     }
8647
8648   lhs = code->expr1;
8649   rhs = code->expr2;
8650
8651   if (rhs->is_boz
8652       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
8653                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
8654                          &code->loc) == FAILURE)
8655     return false;
8656
8657   /* Handle the case of a BOZ literal on the RHS.  */
8658   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
8659     {
8660       int rc;
8661       if (gfc_option.warn_surprising)
8662         gfc_warning ("BOZ literal at %L is bitwise transferred "
8663                      "non-integer symbol '%s'", &code->loc,
8664                      lhs->symtree->n.sym->name);
8665
8666       if (!gfc_convert_boz (rhs, &lhs->ts))
8667         return false;
8668       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
8669         {
8670           if (rc == ARITH_UNDERFLOW)
8671             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
8672                        ". This check can be disabled with the option "
8673                        "-fno-range-check", &rhs->where);
8674           else if (rc == ARITH_OVERFLOW)
8675             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
8676                        ". This check can be disabled with the option "
8677                        "-fno-range-check", &rhs->where);
8678           else if (rc == ARITH_NAN)
8679             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
8680                        ". This check can be disabled with the option "
8681                        "-fno-range-check", &rhs->where);
8682           return false;
8683         }
8684     }
8685
8686   if (lhs->ts.type == BT_CHARACTER
8687         && gfc_option.warn_character_truncation)
8688     {
8689       if (lhs->ts.u.cl != NULL
8690             && lhs->ts.u.cl->length != NULL
8691             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8692         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
8693
8694       if (rhs->expr_type == EXPR_CONSTANT)
8695         rlen = rhs->value.character.length;
8696
8697       else if (rhs->ts.u.cl != NULL
8698                  && rhs->ts.u.cl->length != NULL
8699                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8700         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
8701
8702       if (rlen && llen && rlen > llen)
8703         gfc_warning_now ("CHARACTER expression will be truncated "
8704                          "in assignment (%d/%d) at %L",
8705                          llen, rlen, &code->loc);
8706     }
8707
8708   /* Ensure that a vector index expression for the lvalue is evaluated
8709      to a temporary if the lvalue symbol is referenced in it.  */
8710   if (lhs->rank)
8711     {
8712       for (ref = lhs->ref; ref; ref= ref->next)
8713         if (ref->type == REF_ARRAY)
8714           {
8715             for (n = 0; n < ref->u.ar.dimen; n++)
8716               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
8717                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
8718                                            ref->u.ar.start[n]))
8719                 ref->u.ar.start[n]
8720                         = gfc_get_parentheses (ref->u.ar.start[n]);
8721           }
8722     }
8723
8724   if (gfc_pure (NULL))
8725     {
8726       if (lhs->ts.type == BT_DERIVED
8727             && lhs->expr_type == EXPR_VARIABLE
8728             && lhs->ts.u.derived->attr.pointer_comp
8729             && rhs->expr_type == EXPR_VARIABLE
8730             && (gfc_impure_variable (rhs->symtree->n.sym)
8731                 || gfc_is_coindexed (rhs)))
8732         {
8733           /* F2008, C1283.  */
8734           if (gfc_is_coindexed (rhs))
8735             gfc_error ("Coindexed expression at %L is assigned to "
8736                         "a derived type variable with a POINTER "
8737                         "component in a PURE procedure",
8738                         &rhs->where);
8739           else
8740             gfc_error ("The impure variable at %L is assigned to "
8741                         "a derived type variable with a POINTER "
8742                         "component in a PURE procedure (12.6)",
8743                         &rhs->where);
8744           return rval;
8745         }
8746
8747       /* Fortran 2008, C1283.  */
8748       if (gfc_is_coindexed (lhs))
8749         {
8750           gfc_error ("Assignment to coindexed variable at %L in a PURE "
8751                      "procedure", &rhs->where);
8752           return rval;
8753         }
8754     }
8755
8756   /* F03:7.4.1.2.  */
8757   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
8758      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
8759   if (lhs->ts.type == BT_CLASS)
8760     {
8761       gfc_error ("Variable must not be polymorphic in assignment at %L",
8762                  &lhs->where);
8763       return false;
8764     }
8765
8766   /* F2008, Section 7.2.1.2.  */
8767   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
8768     {
8769       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
8770                  "component in assignment at %L", &lhs->where);
8771       return false;
8772     }
8773
8774   gfc_check_assign (lhs, rhs, 1);
8775   return false;
8776 }
8777
8778
8779 /* Given a block of code, recursively resolve everything pointed to by this
8780    code block.  */
8781
8782 static void
8783 resolve_code (gfc_code *code, gfc_namespace *ns)
8784 {
8785   int omp_workshare_save;
8786   int forall_save;
8787   code_stack frame;
8788   gfc_try t;
8789
8790   frame.prev = cs_base;
8791   frame.head = code;
8792   cs_base = &frame;
8793
8794   find_reachable_labels (code);
8795
8796   for (; code; code = code->next)
8797     {
8798       frame.current = code;
8799       forall_save = forall_flag;
8800
8801       if (code->op == EXEC_FORALL)
8802         {
8803           forall_flag = 1;
8804           gfc_resolve_forall (code, ns, forall_save);
8805           forall_flag = 2;
8806         }
8807       else if (code->block)
8808         {
8809           omp_workshare_save = -1;
8810           switch (code->op)
8811             {
8812             case EXEC_OMP_PARALLEL_WORKSHARE:
8813               omp_workshare_save = omp_workshare_flag;
8814               omp_workshare_flag = 1;
8815               gfc_resolve_omp_parallel_blocks (code, ns);
8816               break;
8817             case EXEC_OMP_PARALLEL:
8818             case EXEC_OMP_PARALLEL_DO:
8819             case EXEC_OMP_PARALLEL_SECTIONS:
8820             case EXEC_OMP_TASK:
8821               omp_workshare_save = omp_workshare_flag;
8822               omp_workshare_flag = 0;
8823               gfc_resolve_omp_parallel_blocks (code, ns);
8824               break;
8825             case EXEC_OMP_DO:
8826               gfc_resolve_omp_do_blocks (code, ns);
8827               break;
8828             case EXEC_SELECT_TYPE:
8829               /* Blocks are handled in resolve_select_type because we have
8830                  to transform the SELECT TYPE into ASSOCIATE first.  */
8831               break;
8832             case EXEC_OMP_WORKSHARE:
8833               omp_workshare_save = omp_workshare_flag;
8834               omp_workshare_flag = 1;
8835               /* FALLTHROUGH */
8836             default:
8837               gfc_resolve_blocks (code->block, ns);
8838               break;
8839             }
8840
8841           if (omp_workshare_save != -1)
8842             omp_workshare_flag = omp_workshare_save;
8843         }
8844
8845       t = SUCCESS;
8846       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
8847         t = gfc_resolve_expr (code->expr1);
8848       forall_flag = forall_save;
8849
8850       if (gfc_resolve_expr (code->expr2) == FAILURE)
8851         t = FAILURE;
8852
8853       if (code->op == EXEC_ALLOCATE
8854           && gfc_resolve_expr (code->expr3) == FAILURE)
8855         t = FAILURE;
8856
8857       switch (code->op)
8858         {
8859         case EXEC_NOP:
8860         case EXEC_END_BLOCK:
8861         case EXEC_CYCLE:
8862         case EXEC_PAUSE:
8863         case EXEC_STOP:
8864         case EXEC_ERROR_STOP:
8865         case EXEC_EXIT:
8866         case EXEC_CONTINUE:
8867         case EXEC_DT_END:
8868         case EXEC_ASSIGN_CALL:
8869         case EXEC_CRITICAL:
8870           break;
8871
8872         case EXEC_SYNC_ALL:
8873         case EXEC_SYNC_IMAGES:
8874         case EXEC_SYNC_MEMORY:
8875           resolve_sync (code);
8876           break;
8877
8878         case EXEC_ENTRY:
8879           /* Keep track of which entry we are up to.  */
8880           current_entry_id = code->ext.entry->id;
8881           break;
8882
8883         case EXEC_WHERE:
8884           resolve_where (code, NULL);
8885           break;
8886
8887         case EXEC_GOTO:
8888           if (code->expr1 != NULL)
8889             {
8890               if (code->expr1->ts.type != BT_INTEGER)
8891                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
8892                            "INTEGER variable", &code->expr1->where);
8893               else if (code->expr1->symtree->n.sym->attr.assign != 1)
8894                 gfc_error ("Variable '%s' has not been assigned a target "
8895                            "label at %L", code->expr1->symtree->n.sym->name,
8896                            &code->expr1->where);
8897             }
8898           else
8899             resolve_branch (code->label1, code);
8900           break;
8901
8902         case EXEC_RETURN:
8903           if (code->expr1 != NULL
8904                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
8905             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
8906                        "INTEGER return specifier", &code->expr1->where);
8907           break;
8908
8909         case EXEC_INIT_ASSIGN:
8910         case EXEC_END_PROCEDURE:
8911           break;
8912
8913         case EXEC_ASSIGN:
8914           if (t == FAILURE)
8915             break;
8916
8917           if (gfc_check_vardef_context (code->expr1, false, _("assignment"))
8918                 == FAILURE)
8919             break;
8920
8921           if (resolve_ordinary_assign (code, ns))
8922             {
8923               if (code->op == EXEC_COMPCALL)
8924                 goto compcall;
8925               else
8926                 goto call;
8927             }
8928           break;
8929
8930         case EXEC_LABEL_ASSIGN:
8931           if (code->label1->defined == ST_LABEL_UNKNOWN)
8932             gfc_error ("Label %d referenced at %L is never defined",
8933                        code->label1->value, &code->label1->where);
8934           if (t == SUCCESS
8935               && (code->expr1->expr_type != EXPR_VARIABLE
8936                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
8937                   || code->expr1->symtree->n.sym->ts.kind
8938                      != gfc_default_integer_kind
8939                   || code->expr1->symtree->n.sym->as != NULL))
8940             gfc_error ("ASSIGN statement at %L requires a scalar "
8941                        "default INTEGER variable", &code->expr1->where);
8942           break;
8943
8944         case EXEC_POINTER_ASSIGN:
8945           {
8946             gfc_expr* e;
8947
8948             if (t == FAILURE)
8949               break;
8950
8951             /* This is both a variable definition and pointer assignment
8952                context, so check both of them.  For rank remapping, a final
8953                array ref may be present on the LHS and fool gfc_expr_attr
8954                used in gfc_check_vardef_context.  Remove it.  */
8955             e = remove_last_array_ref (code->expr1);
8956             t = gfc_check_vardef_context (e, true, _("pointer assignment"));
8957             if (t == SUCCESS)
8958               t = gfc_check_vardef_context (e, false, _("pointer assignment"));
8959             gfc_free_expr (e);
8960             if (t == FAILURE)
8961               break;
8962
8963             gfc_check_pointer_assign (code->expr1, code->expr2);
8964             break;
8965           }
8966
8967         case EXEC_ARITHMETIC_IF:
8968           if (t == SUCCESS
8969               && code->expr1->ts.type != BT_INTEGER
8970               && code->expr1->ts.type != BT_REAL)
8971             gfc_error ("Arithmetic IF statement at %L requires a numeric "
8972                        "expression", &code->expr1->where);
8973
8974           resolve_branch (code->label1, code);
8975           resolve_branch (code->label2, code);
8976           resolve_branch (code->label3, code);
8977           break;
8978
8979         case EXEC_IF:
8980           if (t == SUCCESS && code->expr1 != NULL
8981               && (code->expr1->ts.type != BT_LOGICAL
8982                   || code->expr1->rank != 0))
8983             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8984                        &code->expr1->where);
8985           break;
8986
8987         case EXEC_CALL:
8988         call:
8989           resolve_call (code);
8990           break;
8991
8992         case EXEC_COMPCALL:
8993         compcall:
8994           resolve_typebound_subroutine (code);
8995           break;
8996
8997         case EXEC_CALL_PPC:
8998           resolve_ppc_call (code);
8999           break;
9000
9001         case EXEC_SELECT:
9002           /* Select is complicated. Also, a SELECT construct could be
9003              a transformed computed GOTO.  */
9004           resolve_select (code);
9005           break;
9006
9007         case EXEC_SELECT_TYPE:
9008           resolve_select_type (code, ns);
9009           break;
9010
9011         case EXEC_BLOCK:
9012           resolve_block_construct (code);
9013           break;
9014
9015         case EXEC_DO:
9016           if (code->ext.iterator != NULL)
9017             {
9018               gfc_iterator *iter = code->ext.iterator;
9019               if (gfc_resolve_iterator (iter, true) != FAILURE)
9020                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
9021             }
9022           break;
9023
9024         case EXEC_DO_WHILE:
9025           if (code->expr1 == NULL)
9026             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
9027           if (t == SUCCESS
9028               && (code->expr1->rank != 0
9029                   || code->expr1->ts.type != BT_LOGICAL))
9030             gfc_error ("Exit condition of DO WHILE loop at %L must be "
9031                        "a scalar LOGICAL expression", &code->expr1->where);
9032           break;
9033
9034         case EXEC_ALLOCATE:
9035           if (t == SUCCESS)
9036             resolve_allocate_deallocate (code, "ALLOCATE");
9037
9038           break;
9039
9040         case EXEC_DEALLOCATE:
9041           if (t == SUCCESS)
9042             resolve_allocate_deallocate (code, "DEALLOCATE");
9043
9044           break;
9045
9046         case EXEC_OPEN:
9047           if (gfc_resolve_open (code->ext.open) == FAILURE)
9048             break;
9049
9050           resolve_branch (code->ext.open->err, code);
9051           break;
9052
9053         case EXEC_CLOSE:
9054           if (gfc_resolve_close (code->ext.close) == FAILURE)
9055             break;
9056
9057           resolve_branch (code->ext.close->err, code);
9058           break;
9059
9060         case EXEC_BACKSPACE:
9061         case EXEC_ENDFILE:
9062         case EXEC_REWIND:
9063         case EXEC_FLUSH:
9064           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
9065             break;
9066
9067           resolve_branch (code->ext.filepos->err, code);
9068           break;
9069
9070         case EXEC_INQUIRE:
9071           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9072               break;
9073
9074           resolve_branch (code->ext.inquire->err, code);
9075           break;
9076
9077         case EXEC_IOLENGTH:
9078           gcc_assert (code->ext.inquire != NULL);
9079           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9080             break;
9081
9082           resolve_branch (code->ext.inquire->err, code);
9083           break;
9084
9085         case EXEC_WAIT:
9086           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
9087             break;
9088
9089           resolve_branch (code->ext.wait->err, code);
9090           resolve_branch (code->ext.wait->end, code);
9091           resolve_branch (code->ext.wait->eor, code);
9092           break;
9093
9094         case EXEC_READ:
9095         case EXEC_WRITE:
9096           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
9097             break;
9098
9099           resolve_branch (code->ext.dt->err, code);
9100           resolve_branch (code->ext.dt->end, code);
9101           resolve_branch (code->ext.dt->eor, code);
9102           break;
9103
9104         case EXEC_TRANSFER:
9105           resolve_transfer (code);
9106           break;
9107
9108         case EXEC_FORALL:
9109           resolve_forall_iterators (code->ext.forall_iterator);
9110
9111           if (code->expr1 != NULL
9112               && (code->expr1->ts.type != BT_LOGICAL || code->expr1->rank))
9113             gfc_error ("FORALL mask clause at %L requires a scalar LOGICAL "
9114                        "expression", &code->expr1->where);
9115           break;
9116
9117         case EXEC_OMP_ATOMIC:
9118         case EXEC_OMP_BARRIER:
9119         case EXEC_OMP_CRITICAL:
9120         case EXEC_OMP_FLUSH:
9121         case EXEC_OMP_DO:
9122         case EXEC_OMP_MASTER:
9123         case EXEC_OMP_ORDERED:
9124         case EXEC_OMP_SECTIONS:
9125         case EXEC_OMP_SINGLE:
9126         case EXEC_OMP_TASKWAIT:
9127         case EXEC_OMP_WORKSHARE:
9128           gfc_resolve_omp_directive (code, ns);
9129           break;
9130
9131         case EXEC_OMP_PARALLEL:
9132         case EXEC_OMP_PARALLEL_DO:
9133         case EXEC_OMP_PARALLEL_SECTIONS:
9134         case EXEC_OMP_PARALLEL_WORKSHARE:
9135         case EXEC_OMP_TASK:
9136           omp_workshare_save = omp_workshare_flag;
9137           omp_workshare_flag = 0;
9138           gfc_resolve_omp_directive (code, ns);
9139           omp_workshare_flag = omp_workshare_save;
9140           break;
9141
9142         default:
9143           gfc_internal_error ("resolve_code(): Bad statement code");
9144         }
9145     }
9146
9147   cs_base = frame.prev;
9148 }
9149
9150
9151 /* Resolve initial values and make sure they are compatible with
9152    the variable.  */
9153
9154 static void
9155 resolve_values (gfc_symbol *sym)
9156 {
9157   gfc_try t;
9158
9159   if (sym->value == NULL)
9160     return;
9161
9162   if (sym->value->expr_type == EXPR_STRUCTURE)
9163     t= resolve_structure_cons (sym->value, 1);
9164   else 
9165     t = gfc_resolve_expr (sym->value);
9166
9167   if (t == FAILURE)
9168     return;
9169
9170   gfc_check_assign_symbol (sym, sym->value);
9171 }
9172
9173
9174 /* Verify the binding labels for common blocks that are BIND(C).  The label
9175    for a BIND(C) common block must be identical in all scoping units in which
9176    the common block is declared.  Further, the binding label can not collide
9177    with any other global entity in the program.  */
9178
9179 static void
9180 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
9181 {
9182   if (comm_block_tree->n.common->is_bind_c == 1)
9183     {
9184       gfc_gsymbol *binding_label_gsym;
9185       gfc_gsymbol *comm_name_gsym;
9186
9187       /* See if a global symbol exists by the common block's name.  It may
9188          be NULL if the common block is use-associated.  */
9189       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
9190                                          comm_block_tree->n.common->name);
9191       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
9192         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
9193                    "with the global entity '%s' at %L",
9194                    comm_block_tree->n.common->binding_label,
9195                    comm_block_tree->n.common->name,
9196                    &(comm_block_tree->n.common->where),
9197                    comm_name_gsym->name, &(comm_name_gsym->where));
9198       else if (comm_name_gsym != NULL
9199                && strcmp (comm_name_gsym->name,
9200                           comm_block_tree->n.common->name) == 0)
9201         {
9202           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
9203              as expected.  */
9204           if (comm_name_gsym->binding_label == NULL)
9205             /* No binding label for common block stored yet; save this one.  */
9206             comm_name_gsym->binding_label =
9207               comm_block_tree->n.common->binding_label;
9208           else
9209             if (strcmp (comm_name_gsym->binding_label,
9210                         comm_block_tree->n.common->binding_label) != 0)
9211               {
9212                 /* Common block names match but binding labels do not.  */
9213                 gfc_error ("Binding label '%s' for common block '%s' at %L "
9214                            "does not match the binding label '%s' for common "
9215                            "block '%s' at %L",
9216                            comm_block_tree->n.common->binding_label,
9217                            comm_block_tree->n.common->name,
9218                            &(comm_block_tree->n.common->where),
9219                            comm_name_gsym->binding_label,
9220                            comm_name_gsym->name,
9221                            &(comm_name_gsym->where));
9222                 return;
9223               }
9224         }
9225
9226       /* There is no binding label (NAME="") so we have nothing further to
9227          check and nothing to add as a global symbol for the label.  */
9228       if (comm_block_tree->n.common->binding_label[0] == '\0' )
9229         return;
9230       
9231       binding_label_gsym =
9232         gfc_find_gsymbol (gfc_gsym_root,
9233                           comm_block_tree->n.common->binding_label);
9234       if (binding_label_gsym == NULL)
9235         {
9236           /* Need to make a global symbol for the binding label to prevent
9237              it from colliding with another.  */
9238           binding_label_gsym =
9239             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
9240           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
9241           binding_label_gsym->type = GSYM_COMMON;
9242         }
9243       else
9244         {
9245           /* If comm_name_gsym is NULL, the name common block is use
9246              associated and the name could be colliding.  */
9247           if (binding_label_gsym->type != GSYM_COMMON)
9248             gfc_error ("Binding label '%s' for common block '%s' at %L "
9249                        "collides with the global entity '%s' at %L",
9250                        comm_block_tree->n.common->binding_label,
9251                        comm_block_tree->n.common->name,
9252                        &(comm_block_tree->n.common->where),
9253                        binding_label_gsym->name,
9254                        &(binding_label_gsym->where));
9255           else if (comm_name_gsym != NULL
9256                    && (strcmp (binding_label_gsym->name,
9257                                comm_name_gsym->binding_label) != 0)
9258                    && (strcmp (binding_label_gsym->sym_name,
9259                                comm_name_gsym->name) != 0))
9260             gfc_error ("Binding label '%s' for common block '%s' at %L "
9261                        "collides with global entity '%s' at %L",
9262                        binding_label_gsym->name, binding_label_gsym->sym_name,
9263                        &(comm_block_tree->n.common->where),
9264                        comm_name_gsym->name, &(comm_name_gsym->where));
9265         }
9266     }
9267   
9268   return;
9269 }
9270
9271
9272 /* Verify any BIND(C) derived types in the namespace so we can report errors
9273    for them once, rather than for each variable declared of that type.  */
9274
9275 static void
9276 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
9277 {
9278   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
9279       && derived_sym->attr.is_bind_c == 1)
9280     verify_bind_c_derived_type (derived_sym);
9281   
9282   return;
9283 }
9284
9285
9286 /* Verify that any binding labels used in a given namespace do not collide 
9287    with the names or binding labels of any global symbols.  */
9288
9289 static void
9290 gfc_verify_binding_labels (gfc_symbol *sym)
9291 {
9292   int has_error = 0;
9293   
9294   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
9295       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
9296     {
9297       gfc_gsymbol *bind_c_sym;
9298
9299       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
9300       if (bind_c_sym != NULL 
9301           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
9302         {
9303           if (sym->attr.if_source == IFSRC_DECL 
9304               && (bind_c_sym->type != GSYM_SUBROUTINE 
9305                   && bind_c_sym->type != GSYM_FUNCTION) 
9306               && ((sym->attr.contained == 1 
9307                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
9308                   || (sym->attr.use_assoc == 1 
9309                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
9310             {
9311               /* Make sure global procedures don't collide with anything.  */
9312               gfc_error ("Binding label '%s' at %L collides with the global "
9313                          "entity '%s' at %L", sym->binding_label,
9314                          &(sym->declared_at), bind_c_sym->name,
9315                          &(bind_c_sym->where));
9316               has_error = 1;
9317             }
9318           else if (sym->attr.contained == 0 
9319                    && (sym->attr.if_source == IFSRC_IFBODY 
9320                        && sym->attr.flavor == FL_PROCEDURE) 
9321                    && (bind_c_sym->sym_name != NULL 
9322                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
9323             {
9324               /* Make sure procedures in interface bodies don't collide.  */
9325               gfc_error ("Binding label '%s' in interface body at %L collides "
9326                          "with the global entity '%s' at %L",
9327                          sym->binding_label,
9328                          &(sym->declared_at), bind_c_sym->name,
9329                          &(bind_c_sym->where));
9330               has_error = 1;
9331             }
9332           else if (sym->attr.contained == 0 
9333                    && sym->attr.if_source == IFSRC_UNKNOWN)
9334             if ((sym->attr.use_assoc && bind_c_sym->mod_name
9335                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
9336                 || sym->attr.use_assoc == 0)
9337               {
9338                 gfc_error ("Binding label '%s' at %L collides with global "
9339                            "entity '%s' at %L", sym->binding_label,
9340                            &(sym->declared_at), bind_c_sym->name,
9341                            &(bind_c_sym->where));
9342                 has_error = 1;
9343               }
9344
9345           if (has_error != 0)
9346             /* Clear the binding label to prevent checking multiple times.  */
9347             sym->binding_label[0] = '\0';
9348         }
9349       else if (bind_c_sym == NULL)
9350         {
9351           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
9352           bind_c_sym->where = sym->declared_at;
9353           bind_c_sym->sym_name = sym->name;
9354
9355           if (sym->attr.use_assoc == 1)
9356             bind_c_sym->mod_name = sym->module;
9357           else
9358             if (sym->ns->proc_name != NULL)
9359               bind_c_sym->mod_name = sym->ns->proc_name->name;
9360
9361           if (sym->attr.contained == 0)
9362             {
9363               if (sym->attr.subroutine)
9364                 bind_c_sym->type = GSYM_SUBROUTINE;
9365               else if (sym->attr.function)
9366                 bind_c_sym->type = GSYM_FUNCTION;
9367             }
9368         }
9369     }
9370   return;
9371 }
9372
9373
9374 /* Resolve an index expression.  */
9375
9376 static gfc_try
9377 resolve_index_expr (gfc_expr *e)
9378 {
9379   if (gfc_resolve_expr (e) == FAILURE)
9380     return FAILURE;
9381
9382   if (gfc_simplify_expr (e, 0) == FAILURE)
9383     return FAILURE;
9384
9385   if (gfc_specification_expr (e) == FAILURE)
9386     return FAILURE;
9387
9388   return SUCCESS;
9389 }
9390
9391
9392 /* Resolve a charlen structure.  */
9393
9394 static gfc_try
9395 resolve_charlen (gfc_charlen *cl)
9396 {
9397   int i, k;
9398
9399   if (cl->resolved)
9400     return SUCCESS;
9401
9402   cl->resolved = 1;
9403
9404   specification_expr = 1;
9405
9406   if (resolve_index_expr (cl->length) == FAILURE)
9407     {
9408       specification_expr = 0;
9409       return FAILURE;
9410     }
9411
9412   /* "If the character length parameter value evaluates to a negative
9413      value, the length of character entities declared is zero."  */
9414   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
9415     {
9416       if (gfc_option.warn_surprising)
9417         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
9418                          " the length has been set to zero",
9419                          &cl->length->where, i);
9420       gfc_replace_expr (cl->length,
9421                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
9422     }
9423
9424   /* Check that the character length is not too large.  */
9425   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
9426   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
9427       && cl->length->ts.type == BT_INTEGER
9428       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
9429     {
9430       gfc_error ("String length at %L is too large", &cl->length->where);
9431       return FAILURE;
9432     }
9433
9434   return SUCCESS;
9435 }
9436
9437
9438 /* Test for non-constant shape arrays.  */
9439
9440 static bool
9441 is_non_constant_shape_array (gfc_symbol *sym)
9442 {
9443   gfc_expr *e;
9444   int i;
9445   bool not_constant;
9446
9447   not_constant = false;
9448   if (sym->as != NULL)
9449     {
9450       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
9451          has not been simplified; parameter array references.  Do the
9452          simplification now.  */
9453       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
9454         {
9455           e = sym->as->lower[i];
9456           if (e && (resolve_index_expr (e) == FAILURE
9457                     || !gfc_is_constant_expr (e)))
9458             not_constant = true;
9459           e = sym->as->upper[i];
9460           if (e && (resolve_index_expr (e) == FAILURE
9461                     || !gfc_is_constant_expr (e)))
9462             not_constant = true;
9463         }
9464     }
9465   return not_constant;
9466 }
9467
9468 /* Given a symbol and an initialization expression, add code to initialize
9469    the symbol to the function entry.  */
9470 static void
9471 build_init_assign (gfc_symbol *sym, gfc_expr *init)
9472 {
9473   gfc_expr *lval;
9474   gfc_code *init_st;
9475   gfc_namespace *ns = sym->ns;
9476
9477   /* Search for the function namespace if this is a contained
9478      function without an explicit result.  */
9479   if (sym->attr.function && sym == sym->result
9480       && sym->name != sym->ns->proc_name->name)
9481     {
9482       ns = ns->contained;
9483       for (;ns; ns = ns->sibling)
9484         if (strcmp (ns->proc_name->name, sym->name) == 0)
9485           break;
9486     }
9487
9488   if (ns == NULL)
9489     {
9490       gfc_free_expr (init);
9491       return;
9492     }
9493
9494   /* Build an l-value expression for the result.  */
9495   lval = gfc_lval_expr_from_sym (sym);
9496
9497   /* Add the code at scope entry.  */
9498   init_st = gfc_get_code ();
9499   init_st->next = ns->code;
9500   ns->code = init_st;
9501
9502   /* Assign the default initializer to the l-value.  */
9503   init_st->loc = sym->declared_at;
9504   init_st->op = EXEC_INIT_ASSIGN;
9505   init_st->expr1 = lval;
9506   init_st->expr2 = init;
9507 }
9508
9509 /* Assign the default initializer to a derived type variable or result.  */
9510
9511 static void
9512 apply_default_init (gfc_symbol *sym)
9513 {
9514   gfc_expr *init = NULL;
9515
9516   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9517     return;
9518
9519   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
9520     init = gfc_default_initializer (&sym->ts);
9521
9522   if (init == NULL && sym->ts.type != BT_CLASS)
9523     return;
9524
9525   build_init_assign (sym, init);
9526   sym->attr.referenced = 1;
9527 }
9528
9529 /* Build an initializer for a local integer, real, complex, logical, or
9530    character variable, based on the command line flags finit-local-zero,
9531    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
9532    null if the symbol should not have a default initialization.  */
9533 static gfc_expr *
9534 build_default_init_expr (gfc_symbol *sym)
9535 {
9536   int char_len;
9537   gfc_expr *init_expr;
9538   int i;
9539
9540   /* These symbols should never have a default initialization.  */
9541   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
9542       || sym->attr.external
9543       || sym->attr.dummy
9544       || sym->attr.pointer
9545       || sym->attr.in_equivalence
9546       || sym->attr.in_common
9547       || sym->attr.data
9548       || sym->module
9549       || sym->attr.cray_pointee
9550       || sym->attr.cray_pointer)
9551     return NULL;
9552
9553   /* Now we'll try to build an initializer expression.  */
9554   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
9555                                      &sym->declared_at);
9556
9557   /* We will only initialize integers, reals, complex, logicals, and
9558      characters, and only if the corresponding command-line flags
9559      were set.  Otherwise, we free init_expr and return null.  */
9560   switch (sym->ts.type)
9561     {    
9562     case BT_INTEGER:
9563       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
9564         mpz_set_si (init_expr->value.integer, 
9565                          gfc_option.flag_init_integer_value);
9566       else
9567         {
9568           gfc_free_expr (init_expr);
9569           init_expr = NULL;
9570         }
9571       break;
9572
9573     case BT_REAL:
9574       switch (gfc_option.flag_init_real)
9575         {
9576         case GFC_INIT_REAL_SNAN:
9577           init_expr->is_snan = 1;
9578           /* Fall through.  */
9579         case GFC_INIT_REAL_NAN:
9580           mpfr_set_nan (init_expr->value.real);
9581           break;
9582
9583         case GFC_INIT_REAL_INF:
9584           mpfr_set_inf (init_expr->value.real, 1);
9585           break;
9586
9587         case GFC_INIT_REAL_NEG_INF:
9588           mpfr_set_inf (init_expr->value.real, -1);
9589           break;
9590
9591         case GFC_INIT_REAL_ZERO:
9592           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
9593           break;
9594
9595         default:
9596           gfc_free_expr (init_expr);
9597           init_expr = NULL;
9598           break;
9599         }
9600       break;
9601           
9602     case BT_COMPLEX:
9603       switch (gfc_option.flag_init_real)
9604         {
9605         case GFC_INIT_REAL_SNAN:
9606           init_expr->is_snan = 1;
9607           /* Fall through.  */
9608         case GFC_INIT_REAL_NAN:
9609           mpfr_set_nan (mpc_realref (init_expr->value.complex));
9610           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
9611           break;
9612
9613         case GFC_INIT_REAL_INF:
9614           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
9615           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
9616           break;
9617
9618         case GFC_INIT_REAL_NEG_INF:
9619           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
9620           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
9621           break;
9622
9623         case GFC_INIT_REAL_ZERO:
9624           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
9625           break;
9626
9627         default:
9628           gfc_free_expr (init_expr);
9629           init_expr = NULL;
9630           break;
9631         }
9632       break;
9633           
9634     case BT_LOGICAL:
9635       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
9636         init_expr->value.logical = 0;
9637       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
9638         init_expr->value.logical = 1;
9639       else
9640         {
9641           gfc_free_expr (init_expr);
9642           init_expr = NULL;
9643         }
9644       break;
9645           
9646     case BT_CHARACTER:
9647       /* For characters, the length must be constant in order to 
9648          create a default initializer.  */
9649       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
9650           && sym->ts.u.cl->length
9651           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9652         {
9653           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
9654           init_expr->value.character.length = char_len;
9655           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
9656           for (i = 0; i < char_len; i++)
9657             init_expr->value.character.string[i]
9658               = (unsigned char) gfc_option.flag_init_character_value;
9659         }
9660       else
9661         {
9662           gfc_free_expr (init_expr);
9663           init_expr = NULL;
9664         }
9665       break;
9666           
9667     default:
9668      gfc_free_expr (init_expr);
9669      init_expr = NULL;
9670     }
9671   return init_expr;
9672 }
9673
9674 /* Add an initialization expression to a local variable.  */
9675 static void
9676 apply_default_init_local (gfc_symbol *sym)
9677 {
9678   gfc_expr *init = NULL;
9679
9680   /* The symbol should be a variable or a function return value.  */
9681   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9682       || (sym->attr.function && sym->result != sym))
9683     return;
9684
9685   /* Try to build the initializer expression.  If we can't initialize
9686      this symbol, then init will be NULL.  */
9687   init = build_default_init_expr (sym);
9688   if (init == NULL)
9689     return;
9690
9691   /* For saved variables, we don't want to add an initializer at 
9692      function entry, so we just add a static initializer.  */
9693   if (sym->attr.save || sym->ns->save_all 
9694       || gfc_option.flag_max_stack_var_size == 0)
9695     {
9696       /* Don't clobber an existing initializer!  */
9697       gcc_assert (sym->value == NULL);
9698       sym->value = init;
9699       return;
9700     }
9701
9702   build_init_assign (sym, init);
9703 }
9704
9705
9706 /* Resolution of common features of flavors variable and procedure.  */
9707
9708 static gfc_try
9709 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
9710 {
9711   /* Constraints on deferred shape variable.  */
9712   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
9713     {
9714       if (sym->attr.allocatable)
9715         {
9716           if (sym->attr.dimension)
9717             {
9718               gfc_error ("Allocatable array '%s' at %L must have "
9719                          "a deferred shape", sym->name, &sym->declared_at);
9720               return FAILURE;
9721             }
9722           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
9723                                    "may not be ALLOCATABLE", sym->name,
9724                                    &sym->declared_at) == FAILURE)
9725             return FAILURE;
9726         }
9727
9728       if (sym->attr.pointer && sym->attr.dimension)
9729         {
9730           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
9731                      sym->name, &sym->declared_at);
9732           return FAILURE;
9733         }
9734     }
9735   else
9736     {
9737       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
9738           && !sym->attr.dummy && sym->ts.type != BT_CLASS && !sym->assoc)
9739         {
9740           gfc_error ("Array '%s' at %L cannot have a deferred shape",
9741                      sym->name, &sym->declared_at);
9742           return FAILURE;
9743          }
9744     }
9745
9746   /* Constraints on polymorphic variables.  */
9747   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
9748     {
9749       /* F03:C502.  */
9750       if (sym->attr.class_ok
9751           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
9752         {
9753           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
9754                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
9755                      &sym->declared_at);
9756           return FAILURE;
9757         }
9758
9759       /* F03:C509.  */
9760       /* Assume that use associated symbols were checked in the module ns.
9761          Class-variables that are associate-names are also something special
9762          and excepted from the test.  */
9763       if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
9764         {
9765           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
9766                      "or pointer", sym->name, &sym->declared_at);
9767           return FAILURE;
9768         }
9769     }
9770     
9771   return SUCCESS;
9772 }
9773
9774
9775 /* Additional checks for symbols with flavor variable and derived
9776    type.  To be called from resolve_fl_variable.  */
9777
9778 static gfc_try
9779 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
9780 {
9781   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
9782
9783   /* Check to see if a derived type is blocked from being host
9784      associated by the presence of another class I symbol in the same
9785      namespace.  14.6.1.3 of the standard and the discussion on
9786      comp.lang.fortran.  */
9787   if (sym->ns != sym->ts.u.derived->ns
9788       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
9789     {
9790       gfc_symbol *s;
9791       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
9792       if (s && s->attr.flavor != FL_DERIVED)
9793         {
9794           gfc_error ("The type '%s' cannot be host associated at %L "
9795                      "because it is blocked by an incompatible object "
9796                      "of the same name declared at %L",
9797                      sym->ts.u.derived->name, &sym->declared_at,
9798                      &s->declared_at);
9799           return FAILURE;
9800         }
9801     }
9802
9803   /* 4th constraint in section 11.3: "If an object of a type for which
9804      component-initialization is specified (R429) appears in the
9805      specification-part of a module and does not have the ALLOCATABLE
9806      or POINTER attribute, the object shall have the SAVE attribute."
9807
9808      The check for initializers is performed with
9809      gfc_has_default_initializer because gfc_default_initializer generates
9810      a hidden default for allocatable components.  */
9811   if (!(sym->value || no_init_flag) && sym->ns->proc_name
9812       && sym->ns->proc_name->attr.flavor == FL_MODULE
9813       && !sym->ns->save_all && !sym->attr.save
9814       && !sym->attr.pointer && !sym->attr.allocatable
9815       && gfc_has_default_initializer (sym->ts.u.derived)
9816       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
9817                          "module variable '%s' at %L, needed due to "
9818                          "the default initialization", sym->name,
9819                          &sym->declared_at) == FAILURE)
9820     return FAILURE;
9821
9822   /* Assign default initializer.  */
9823   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
9824       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
9825     {
9826       sym->value = gfc_default_initializer (&sym->ts);
9827     }
9828
9829   return SUCCESS;
9830 }
9831
9832
9833 /* Resolve symbols with flavor variable.  */
9834
9835 static gfc_try
9836 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
9837 {
9838   int no_init_flag, automatic_flag;
9839   gfc_expr *e;
9840   const char *auto_save_msg;
9841
9842   auto_save_msg = "Automatic object '%s' at %L cannot have the "
9843                   "SAVE attribute";
9844
9845   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9846     return FAILURE;
9847
9848   /* Set this flag to check that variables are parameters of all entries.
9849      This check is effected by the call to gfc_resolve_expr through
9850      is_non_constant_shape_array.  */
9851   specification_expr = 1;
9852
9853   if (sym->ns->proc_name
9854       && (sym->ns->proc_name->attr.flavor == FL_MODULE
9855           || sym->ns->proc_name->attr.is_main_program)
9856       && !sym->attr.use_assoc
9857       && !sym->attr.allocatable
9858       && !sym->attr.pointer
9859       && is_non_constant_shape_array (sym))
9860     {
9861       /* The shape of a main program or module array needs to be
9862          constant.  */
9863       gfc_error ("The module or main program array '%s' at %L must "
9864                  "have constant shape", sym->name, &sym->declared_at);
9865       specification_expr = 0;
9866       return FAILURE;
9867     }
9868
9869   /* Constraints on deferred type parameter.  */
9870   if (sym->ts.deferred && !(sym->attr.pointer || sym->attr.allocatable))
9871     {
9872       gfc_error ("Entity '%s' at %L has a deferred type parameter and "
9873                  "requires either the pointer or allocatable attribute",
9874                      sym->name, &sym->declared_at);
9875       return FAILURE;
9876     }
9877
9878   if (sym->ts.type == BT_CHARACTER)
9879     {
9880       /* Make sure that character string variables with assumed length are
9881          dummy arguments.  */
9882       e = sym->ts.u.cl->length;
9883       if (e == NULL && !sym->attr.dummy && !sym->attr.result
9884           && !sym->ts.deferred)
9885         {
9886           gfc_error ("Entity with assumed character length at %L must be a "
9887                      "dummy argument or a PARAMETER", &sym->declared_at);
9888           return FAILURE;
9889         }
9890
9891       if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
9892         {
9893           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9894           return FAILURE;
9895         }
9896
9897       if (!gfc_is_constant_expr (e)
9898           && !(e->expr_type == EXPR_VARIABLE
9899                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
9900           && sym->ns->proc_name
9901           && (sym->ns->proc_name->attr.flavor == FL_MODULE
9902               || sym->ns->proc_name->attr.is_main_program)
9903           && !sym->attr.use_assoc)
9904         {
9905           gfc_error ("'%s' at %L must have constant character length "
9906                      "in this context", sym->name, &sym->declared_at);
9907           return FAILURE;
9908         }
9909     }
9910
9911   if (sym->value == NULL && sym->attr.referenced)
9912     apply_default_init_local (sym); /* Try to apply a default initialization.  */
9913
9914   /* Determine if the symbol may not have an initializer.  */
9915   no_init_flag = automatic_flag = 0;
9916   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
9917       || sym->attr.intrinsic || sym->attr.result)
9918     no_init_flag = 1;
9919   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
9920            && is_non_constant_shape_array (sym))
9921     {
9922       no_init_flag = automatic_flag = 1;
9923
9924       /* Also, they must not have the SAVE attribute.
9925          SAVE_IMPLICIT is checked below.  */
9926       if (sym->attr.save == SAVE_EXPLICIT)
9927         {
9928           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9929           return FAILURE;
9930         }
9931     }
9932
9933   /* Ensure that any initializer is simplified.  */
9934   if (sym->value)
9935     gfc_simplify_expr (sym->value, 1);
9936
9937   /* Reject illegal initializers.  */
9938   if (!sym->mark && sym->value)
9939     {
9940       if (sym->attr.allocatable)
9941         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
9942                    sym->name, &sym->declared_at);
9943       else if (sym->attr.external)
9944         gfc_error ("External '%s' at %L cannot have an initializer",
9945                    sym->name, &sym->declared_at);
9946       else if (sym->attr.dummy
9947         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
9948         gfc_error ("Dummy '%s' at %L cannot have an initializer",
9949                    sym->name, &sym->declared_at);
9950       else if (sym->attr.intrinsic)
9951         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
9952                    sym->name, &sym->declared_at);
9953       else if (sym->attr.result)
9954         gfc_error ("Function result '%s' at %L cannot have an initializer",
9955                    sym->name, &sym->declared_at);
9956       else if (automatic_flag)
9957         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
9958                    sym->name, &sym->declared_at);
9959       else
9960         goto no_init_error;
9961       return FAILURE;
9962     }
9963
9964 no_init_error:
9965   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
9966     return resolve_fl_variable_derived (sym, no_init_flag);
9967
9968   return SUCCESS;
9969 }
9970
9971
9972 /* Resolve a procedure.  */
9973
9974 static gfc_try
9975 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
9976 {
9977   gfc_formal_arglist *arg;
9978
9979   if (sym->attr.function
9980       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9981     return FAILURE;
9982
9983   if (sym->ts.type == BT_CHARACTER)
9984     {
9985       gfc_charlen *cl = sym->ts.u.cl;
9986
9987       if (cl && cl->length && gfc_is_constant_expr (cl->length)
9988              && resolve_charlen (cl) == FAILURE)
9989         return FAILURE;
9990
9991       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
9992           && sym->attr.proc == PROC_ST_FUNCTION)
9993         {
9994           gfc_error ("Character-valued statement function '%s' at %L must "
9995                      "have constant length", sym->name, &sym->declared_at);
9996           return FAILURE;
9997         }
9998     }
9999
10000   /* Ensure that derived type for are not of a private type.  Internal
10001      module procedures are excluded by 2.2.3.3 - i.e., they are not
10002      externally accessible and can access all the objects accessible in
10003      the host.  */
10004   if (!(sym->ns->parent
10005         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
10006       && gfc_check_access(sym->attr.access, sym->ns->default_access))
10007     {
10008       gfc_interface *iface;
10009
10010       for (arg = sym->formal; arg; arg = arg->next)
10011         {
10012           if (arg->sym
10013               && arg->sym->ts.type == BT_DERIVED
10014               && !arg->sym->ts.u.derived->attr.use_assoc
10015               && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
10016                                     arg->sym->ts.u.derived->ns->default_access)
10017               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
10018                                  "PRIVATE type and cannot be a dummy argument"
10019                                  " of '%s', which is PUBLIC at %L",
10020                                  arg->sym->name, sym->name, &sym->declared_at)
10021                  == FAILURE)
10022             {
10023               /* Stop this message from recurring.  */
10024               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10025               return FAILURE;
10026             }
10027         }
10028
10029       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10030          PRIVATE to the containing module.  */
10031       for (iface = sym->generic; iface; iface = iface->next)
10032         {
10033           for (arg = iface->sym->formal; arg; arg = arg->next)
10034             {
10035               if (arg->sym
10036                   && arg->sym->ts.type == BT_DERIVED
10037                   && !arg->sym->ts.u.derived->attr.use_assoc
10038                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
10039                                         arg->sym->ts.u.derived->ns->default_access)
10040                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10041                                      "'%s' in PUBLIC interface '%s' at %L "
10042                                      "takes dummy arguments of '%s' which is "
10043                                      "PRIVATE", iface->sym->name, sym->name,
10044                                      &iface->sym->declared_at,
10045                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10046                 {
10047                   /* Stop this message from recurring.  */
10048                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10049                   return FAILURE;
10050                 }
10051              }
10052         }
10053
10054       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10055          PRIVATE to the containing module.  */
10056       for (iface = sym->generic; iface; iface = iface->next)
10057         {
10058           for (arg = iface->sym->formal; arg; arg = arg->next)
10059             {
10060               if (arg->sym
10061                   && arg->sym->ts.type == BT_DERIVED
10062                   && !arg->sym->ts.u.derived->attr.use_assoc
10063                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
10064                                         arg->sym->ts.u.derived->ns->default_access)
10065                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10066                                      "'%s' in PUBLIC interface '%s' at %L "
10067                                      "takes dummy arguments of '%s' which is "
10068                                      "PRIVATE", iface->sym->name, sym->name,
10069                                      &iface->sym->declared_at,
10070                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10071                 {
10072                   /* Stop this message from recurring.  */
10073                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10074                   return FAILURE;
10075                 }
10076              }
10077         }
10078     }
10079
10080   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
10081       && !sym->attr.proc_pointer)
10082     {
10083       gfc_error ("Function '%s' at %L cannot have an initializer",
10084                  sym->name, &sym->declared_at);
10085       return FAILURE;
10086     }
10087
10088   /* An external symbol may not have an initializer because it is taken to be
10089      a procedure. Exception: Procedure Pointers.  */
10090   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
10091     {
10092       gfc_error ("External object '%s' at %L may not have an initializer",
10093                  sym->name, &sym->declared_at);
10094       return FAILURE;
10095     }
10096
10097   /* An elemental function is required to return a scalar 12.7.1  */
10098   if (sym->attr.elemental && sym->attr.function && sym->as)
10099     {
10100       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
10101                  "result", sym->name, &sym->declared_at);
10102       /* Reset so that the error only occurs once.  */
10103       sym->attr.elemental = 0;
10104       return FAILURE;
10105     }
10106
10107   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
10108      char-len-param shall not be array-valued, pointer-valued, recursive
10109      or pure.  ....snip... A character value of * may only be used in the
10110      following ways: (i) Dummy arg of procedure - dummy associates with
10111      actual length; (ii) To declare a named constant; or (iii) External
10112      function - but length must be declared in calling scoping unit.  */
10113   if (sym->attr.function
10114       && sym->ts.type == BT_CHARACTER
10115       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
10116     {
10117       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
10118           || (sym->attr.recursive) || (sym->attr.pure))
10119         {
10120           if (sym->as && sym->as->rank)
10121             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10122                        "array-valued", sym->name, &sym->declared_at);
10123
10124           if (sym->attr.pointer)
10125             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10126                        "pointer-valued", sym->name, &sym->declared_at);
10127
10128           if (sym->attr.pure)
10129             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10130                        "pure", sym->name, &sym->declared_at);
10131
10132           if (sym->attr.recursive)
10133             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10134                        "recursive", sym->name, &sym->declared_at);
10135
10136           return FAILURE;
10137         }
10138
10139       /* Appendix B.2 of the standard.  Contained functions give an
10140          error anyway.  Fixed-form is likely to be F77/legacy.  */
10141       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
10142         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
10143                         "CHARACTER(*) function '%s' at %L",
10144                         sym->name, &sym->declared_at);
10145     }
10146
10147   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
10148     {
10149       gfc_formal_arglist *curr_arg;
10150       int has_non_interop_arg = 0;
10151
10152       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10153                              sym->common_block) == FAILURE)
10154         {
10155           /* Clear these to prevent looking at them again if there was an
10156              error.  */
10157           sym->attr.is_bind_c = 0;
10158           sym->attr.is_c_interop = 0;
10159           sym->ts.is_c_interop = 0;
10160         }
10161       else
10162         {
10163           /* So far, no errors have been found.  */
10164           sym->attr.is_c_interop = 1;
10165           sym->ts.is_c_interop = 1;
10166         }
10167       
10168       curr_arg = sym->formal;
10169       while (curr_arg != NULL)
10170         {
10171           /* Skip implicitly typed dummy args here.  */
10172           if (curr_arg->sym->attr.implicit_type == 0)
10173             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
10174               /* If something is found to fail, record the fact so we
10175                  can mark the symbol for the procedure as not being
10176                  BIND(C) to try and prevent multiple errors being
10177                  reported.  */
10178               has_non_interop_arg = 1;
10179           
10180           curr_arg = curr_arg->next;
10181         }
10182
10183       /* See if any of the arguments were not interoperable and if so, clear
10184          the procedure symbol to prevent duplicate error messages.  */
10185       if (has_non_interop_arg != 0)
10186         {
10187           sym->attr.is_c_interop = 0;
10188           sym->ts.is_c_interop = 0;
10189           sym->attr.is_bind_c = 0;
10190         }
10191     }
10192   
10193   if (!sym->attr.proc_pointer)
10194     {
10195       if (sym->attr.save == SAVE_EXPLICIT)
10196         {
10197           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
10198                      "in '%s' at %L", sym->name, &sym->declared_at);
10199           return FAILURE;
10200         }
10201       if (sym->attr.intent)
10202         {
10203           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
10204                      "in '%s' at %L", sym->name, &sym->declared_at);
10205           return FAILURE;
10206         }
10207       if (sym->attr.subroutine && sym->attr.result)
10208         {
10209           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
10210                      "in '%s' at %L", sym->name, &sym->declared_at);
10211           return FAILURE;
10212         }
10213       if (sym->attr.external && sym->attr.function
10214           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
10215               || sym->attr.contained))
10216         {
10217           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
10218                      "in '%s' at %L", sym->name, &sym->declared_at);
10219           return FAILURE;
10220         }
10221       if (strcmp ("ppr@", sym->name) == 0)
10222         {
10223           gfc_error ("Procedure pointer result '%s' at %L "
10224                      "is missing the pointer attribute",
10225                      sym->ns->proc_name->name, &sym->declared_at);
10226           return FAILURE;
10227         }
10228     }
10229
10230   return SUCCESS;
10231 }
10232
10233
10234 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
10235    been defined and we now know their defined arguments, check that they fulfill
10236    the requirements of the standard for procedures used as finalizers.  */
10237
10238 static gfc_try
10239 gfc_resolve_finalizers (gfc_symbol* derived)
10240 {
10241   gfc_finalizer* list;
10242   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
10243   gfc_try result = SUCCESS;
10244   bool seen_scalar = false;
10245
10246   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
10247     return SUCCESS;
10248
10249   /* Walk over the list of finalizer-procedures, check them, and if any one
10250      does not fit in with the standard's definition, print an error and remove
10251      it from the list.  */
10252   prev_link = &derived->f2k_derived->finalizers;
10253   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
10254     {
10255       gfc_symbol* arg;
10256       gfc_finalizer* i;
10257       int my_rank;
10258
10259       /* Skip this finalizer if we already resolved it.  */
10260       if (list->proc_tree)
10261         {
10262           prev_link = &(list->next);
10263           continue;
10264         }
10265
10266       /* Check this exists and is a SUBROUTINE.  */
10267       if (!list->proc_sym->attr.subroutine)
10268         {
10269           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
10270                      list->proc_sym->name, &list->where);
10271           goto error;
10272         }
10273
10274       /* We should have exactly one argument.  */
10275       if (!list->proc_sym->formal || list->proc_sym->formal->next)
10276         {
10277           gfc_error ("FINAL procedure at %L must have exactly one argument",
10278                      &list->where);
10279           goto error;
10280         }
10281       arg = list->proc_sym->formal->sym;
10282
10283       /* This argument must be of our type.  */
10284       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
10285         {
10286           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
10287                      &arg->declared_at, derived->name);
10288           goto error;
10289         }
10290
10291       /* It must neither be a pointer nor allocatable nor optional.  */
10292       if (arg->attr.pointer)
10293         {
10294           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
10295                      &arg->declared_at);
10296           goto error;
10297         }
10298       if (arg->attr.allocatable)
10299         {
10300           gfc_error ("Argument of FINAL procedure at %L must not be"
10301                      " ALLOCATABLE", &arg->declared_at);
10302           goto error;
10303         }
10304       if (arg->attr.optional)
10305         {
10306           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
10307                      &arg->declared_at);
10308           goto error;
10309         }
10310
10311       /* It must not be INTENT(OUT).  */
10312       if (arg->attr.intent == INTENT_OUT)
10313         {
10314           gfc_error ("Argument of FINAL procedure at %L must not be"
10315                      " INTENT(OUT)", &arg->declared_at);
10316           goto error;
10317         }
10318
10319       /* Warn if the procedure is non-scalar and not assumed shape.  */
10320       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
10321           && arg->as->type != AS_ASSUMED_SHAPE)
10322         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
10323                      " shape argument", &arg->declared_at);
10324
10325       /* Check that it does not match in kind and rank with a FINAL procedure
10326          defined earlier.  To really loop over the *earlier* declarations,
10327          we need to walk the tail of the list as new ones were pushed at the
10328          front.  */
10329       /* TODO: Handle kind parameters once they are implemented.  */
10330       my_rank = (arg->as ? arg->as->rank : 0);
10331       for (i = list->next; i; i = i->next)
10332         {
10333           /* Argument list might be empty; that is an error signalled earlier,
10334              but we nevertheless continued resolving.  */
10335           if (i->proc_sym->formal)
10336             {
10337               gfc_symbol* i_arg = i->proc_sym->formal->sym;
10338               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
10339               if (i_rank == my_rank)
10340                 {
10341                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
10342                              " rank (%d) as '%s'",
10343                              list->proc_sym->name, &list->where, my_rank, 
10344                              i->proc_sym->name);
10345                   goto error;
10346                 }
10347             }
10348         }
10349
10350         /* Is this the/a scalar finalizer procedure?  */
10351         if (!arg->as || arg->as->rank == 0)
10352           seen_scalar = true;
10353
10354         /* Find the symtree for this procedure.  */
10355         gcc_assert (!list->proc_tree);
10356         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
10357
10358         prev_link = &list->next;
10359         continue;
10360
10361         /* Remove wrong nodes immediately from the list so we don't risk any
10362            troubles in the future when they might fail later expectations.  */
10363 error:
10364         result = FAILURE;
10365         i = list;
10366         *prev_link = list->next;
10367         gfc_free_finalizer (i);
10368     }
10369
10370   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
10371      were nodes in the list, must have been for arrays.  It is surely a good
10372      idea to have a scalar version there if there's something to finalize.  */
10373   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
10374     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
10375                  " defined at %L, suggest also scalar one",
10376                  derived->name, &derived->declared_at);
10377
10378   /* TODO:  Remove this error when finalization is finished.  */
10379   gfc_error ("Finalization at %L is not yet implemented",
10380              &derived->declared_at);
10381
10382   return result;
10383 }
10384
10385
10386 /* Check that it is ok for the typebound procedure proc to override the
10387    procedure old.  */
10388
10389 static gfc_try
10390 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
10391 {
10392   locus where;
10393   const gfc_symbol* proc_target;
10394   const gfc_symbol* old_target;
10395   unsigned proc_pass_arg, old_pass_arg, argpos;
10396   gfc_formal_arglist* proc_formal;
10397   gfc_formal_arglist* old_formal;
10398
10399   /* This procedure should only be called for non-GENERIC proc.  */
10400   gcc_assert (!proc->n.tb->is_generic);
10401
10402   /* If the overwritten procedure is GENERIC, this is an error.  */
10403   if (old->n.tb->is_generic)
10404     {
10405       gfc_error ("Can't overwrite GENERIC '%s' at %L",
10406                  old->name, &proc->n.tb->where);
10407       return FAILURE;
10408     }
10409
10410   where = proc->n.tb->where;
10411   proc_target = proc->n.tb->u.specific->n.sym;
10412   old_target = old->n.tb->u.specific->n.sym;
10413
10414   /* Check that overridden binding is not NON_OVERRIDABLE.  */
10415   if (old->n.tb->non_overridable)
10416     {
10417       gfc_error ("'%s' at %L overrides a procedure binding declared"
10418                  " NON_OVERRIDABLE", proc->name, &where);
10419       return FAILURE;
10420     }
10421
10422   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
10423   if (!old->n.tb->deferred && proc->n.tb->deferred)
10424     {
10425       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
10426                  " non-DEFERRED binding", proc->name, &where);
10427       return FAILURE;
10428     }
10429
10430   /* If the overridden binding is PURE, the overriding must be, too.  */
10431   if (old_target->attr.pure && !proc_target->attr.pure)
10432     {
10433       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
10434                  proc->name, &where);
10435       return FAILURE;
10436     }
10437
10438   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
10439      is not, the overriding must not be either.  */
10440   if (old_target->attr.elemental && !proc_target->attr.elemental)
10441     {
10442       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
10443                  " ELEMENTAL", proc->name, &where);
10444       return FAILURE;
10445     }
10446   if (!old_target->attr.elemental && proc_target->attr.elemental)
10447     {
10448       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
10449                  " be ELEMENTAL, either", proc->name, &where);
10450       return FAILURE;
10451     }
10452
10453   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
10454      SUBROUTINE.  */
10455   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
10456     {
10457       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
10458                  " SUBROUTINE", proc->name, &where);
10459       return FAILURE;
10460     }
10461
10462   /* If the overridden binding is a FUNCTION, the overriding must also be a
10463      FUNCTION and have the same characteristics.  */
10464   if (old_target->attr.function)
10465     {
10466       if (!proc_target->attr.function)
10467         {
10468           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
10469                      " FUNCTION", proc->name, &where);
10470           return FAILURE;
10471         }
10472
10473       /* FIXME:  Do more comprehensive checking (including, for instance, the
10474          rank and array-shape).  */
10475       gcc_assert (proc_target->result && old_target->result);
10476       if (!gfc_compare_types (&proc_target->result->ts,
10477                               &old_target->result->ts))
10478         {
10479           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
10480                      " matching result types", proc->name, &where);
10481           return FAILURE;
10482         }
10483     }
10484
10485   /* If the overridden binding is PUBLIC, the overriding one must not be
10486      PRIVATE.  */
10487   if (old->n.tb->access == ACCESS_PUBLIC
10488       && proc->n.tb->access == ACCESS_PRIVATE)
10489     {
10490       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
10491                  " PRIVATE", proc->name, &where);
10492       return FAILURE;
10493     }
10494
10495   /* Compare the formal argument lists of both procedures.  This is also abused
10496      to find the position of the passed-object dummy arguments of both
10497      bindings as at least the overridden one might not yet be resolved and we
10498      need those positions in the check below.  */
10499   proc_pass_arg = old_pass_arg = 0;
10500   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
10501     proc_pass_arg = 1;
10502   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
10503     old_pass_arg = 1;
10504   argpos = 1;
10505   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
10506        proc_formal && old_formal;
10507        proc_formal = proc_formal->next, old_formal = old_formal->next)
10508     {
10509       if (proc->n.tb->pass_arg
10510           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
10511         proc_pass_arg = argpos;
10512       if (old->n.tb->pass_arg
10513           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
10514         old_pass_arg = argpos;
10515
10516       /* Check that the names correspond.  */
10517       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
10518         {
10519           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
10520                      " to match the corresponding argument of the overridden"
10521                      " procedure", proc_formal->sym->name, proc->name, &where,
10522                      old_formal->sym->name);
10523           return FAILURE;
10524         }
10525
10526       /* Check that the types correspond if neither is the passed-object
10527          argument.  */
10528       /* FIXME:  Do more comprehensive testing here.  */
10529       if (proc_pass_arg != argpos && old_pass_arg != argpos
10530           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
10531         {
10532           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L "
10533                      "in respect to the overridden procedure",
10534                      proc_formal->sym->name, proc->name, &where);
10535           return FAILURE;
10536         }
10537
10538       ++argpos;
10539     }
10540   if (proc_formal || old_formal)
10541     {
10542       gfc_error ("'%s' at %L must have the same number of formal arguments as"
10543                  " the overridden procedure", proc->name, &where);
10544       return FAILURE;
10545     }
10546
10547   /* If the overridden binding is NOPASS, the overriding one must also be
10548      NOPASS.  */
10549   if (old->n.tb->nopass && !proc->n.tb->nopass)
10550     {
10551       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
10552                  " NOPASS", proc->name, &where);
10553       return FAILURE;
10554     }
10555
10556   /* If the overridden binding is PASS(x), the overriding one must also be
10557      PASS and the passed-object dummy arguments must correspond.  */
10558   if (!old->n.tb->nopass)
10559     {
10560       if (proc->n.tb->nopass)
10561         {
10562           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
10563                      " PASS", proc->name, &where);
10564           return FAILURE;
10565         }
10566
10567       if (proc_pass_arg != old_pass_arg)
10568         {
10569           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
10570                      " the same position as the passed-object dummy argument of"
10571                      " the overridden procedure", proc->name, &where);
10572           return FAILURE;
10573         }
10574     }
10575
10576   return SUCCESS;
10577 }
10578
10579
10580 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10581
10582 static gfc_try
10583 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10584                              const char* generic_name, locus where)
10585 {
10586   gfc_symbol* sym1;
10587   gfc_symbol* sym2;
10588
10589   gcc_assert (t1->specific && t2->specific);
10590   gcc_assert (!t1->specific->is_generic);
10591   gcc_assert (!t2->specific->is_generic);
10592
10593   sym1 = t1->specific->u.specific->n.sym;
10594   sym2 = t2->specific->u.specific->n.sym;
10595
10596   if (sym1 == sym2)
10597     return SUCCESS;
10598
10599   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10600   if (sym1->attr.subroutine != sym2->attr.subroutine
10601       || sym1->attr.function != sym2->attr.function)
10602     {
10603       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10604                  " GENERIC '%s' at %L",
10605                  sym1->name, sym2->name, generic_name, &where);
10606       return FAILURE;
10607     }
10608
10609   /* Compare the interfaces.  */
10610   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10611     {
10612       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10613                  sym1->name, sym2->name, generic_name, &where);
10614       return FAILURE;
10615     }
10616
10617   return SUCCESS;
10618 }
10619
10620
10621 /* Worker function for resolving a generic procedure binding; this is used to
10622    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10623
10624    The difference between those cases is finding possible inherited bindings
10625    that are overridden, as one has to look for them in tb_sym_root,
10626    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10627    the super-type and set p->overridden correctly.  */
10628
10629 static gfc_try
10630 resolve_tb_generic_targets (gfc_symbol* super_type,
10631                             gfc_typebound_proc* p, const char* name)
10632 {
10633   gfc_tbp_generic* target;
10634   gfc_symtree* first_target;
10635   gfc_symtree* inherited;
10636
10637   gcc_assert (p && p->is_generic);
10638
10639   /* Try to find the specific bindings for the symtrees in our target-list.  */
10640   gcc_assert (p->u.generic);
10641   for (target = p->u.generic; target; target = target->next)
10642     if (!target->specific)
10643       {
10644         gfc_typebound_proc* overridden_tbp;
10645         gfc_tbp_generic* g;
10646         const char* target_name;
10647
10648         target_name = target->specific_st->name;
10649
10650         /* Defined for this type directly.  */
10651         if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
10652           {
10653             target->specific = target->specific_st->n.tb;
10654             goto specific_found;
10655           }
10656
10657         /* Look for an inherited specific binding.  */
10658         if (super_type)
10659           {
10660             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10661                                                  true, NULL);
10662
10663             if (inherited)
10664               {
10665                 gcc_assert (inherited->n.tb);
10666                 target->specific = inherited->n.tb;
10667                 goto specific_found;
10668               }
10669           }
10670
10671         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10672                    " at %L", target_name, name, &p->where);
10673         return FAILURE;
10674
10675         /* Once we've found the specific binding, check it is not ambiguous with
10676            other specifics already found or inherited for the same GENERIC.  */
10677 specific_found:
10678         gcc_assert (target->specific);
10679
10680         /* This must really be a specific binding!  */
10681         if (target->specific->is_generic)
10682           {
10683             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
10684                        " '%s' is GENERIC, too", name, &p->where, target_name);
10685             return FAILURE;
10686           }
10687
10688         /* Check those already resolved on this type directly.  */
10689         for (g = p->u.generic; g; g = g->next)
10690           if (g != target && g->specific
10691               && check_generic_tbp_ambiguity (target, g, name, p->where)
10692                   == FAILURE)
10693             return FAILURE;
10694
10695         /* Check for ambiguity with inherited specific targets.  */
10696         for (overridden_tbp = p->overridden; overridden_tbp;
10697              overridden_tbp = overridden_tbp->overridden)
10698           if (overridden_tbp->is_generic)
10699             {
10700               for (g = overridden_tbp->u.generic; g; g = g->next)
10701                 {
10702                   gcc_assert (g->specific);
10703                   if (check_generic_tbp_ambiguity (target, g,
10704                                                    name, p->where) == FAILURE)
10705                     return FAILURE;
10706                 }
10707             }
10708       }
10709
10710   /* If we attempt to "overwrite" a specific binding, this is an error.  */
10711   if (p->overridden && !p->overridden->is_generic)
10712     {
10713       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
10714                  " the same name", name, &p->where);
10715       return FAILURE;
10716     }
10717
10718   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
10719      all must have the same attributes here.  */
10720   first_target = p->u.generic->specific->u.specific;
10721   gcc_assert (first_target);
10722   p->subroutine = first_target->n.sym->attr.subroutine;
10723   p->function = first_target->n.sym->attr.function;
10724
10725   return SUCCESS;
10726 }
10727
10728
10729 /* Resolve a GENERIC procedure binding for a derived type.  */
10730
10731 static gfc_try
10732 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
10733 {
10734   gfc_symbol* super_type;
10735
10736   /* Find the overridden binding if any.  */
10737   st->n.tb->overridden = NULL;
10738   super_type = gfc_get_derived_super_type (derived);
10739   if (super_type)
10740     {
10741       gfc_symtree* overridden;
10742       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
10743                                             true, NULL);
10744
10745       if (overridden && overridden->n.tb)
10746         st->n.tb->overridden = overridden->n.tb;
10747     }
10748
10749   /* Resolve using worker function.  */
10750   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
10751 }
10752
10753
10754 /* Retrieve the target-procedure of an operator binding and do some checks in
10755    common for intrinsic and user-defined type-bound operators.  */
10756
10757 static gfc_symbol*
10758 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
10759 {
10760   gfc_symbol* target_proc;
10761
10762   gcc_assert (target->specific && !target->specific->is_generic);
10763   target_proc = target->specific->u.specific->n.sym;
10764   gcc_assert (target_proc);
10765
10766   /* All operator bindings must have a passed-object dummy argument.  */
10767   if (target->specific->nopass)
10768     {
10769       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
10770       return NULL;
10771     }
10772
10773   return target_proc;
10774 }
10775
10776
10777 /* Resolve a type-bound intrinsic operator.  */
10778
10779 static gfc_try
10780 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
10781                                 gfc_typebound_proc* p)
10782 {
10783   gfc_symbol* super_type;
10784   gfc_tbp_generic* target;
10785   
10786   /* If there's already an error here, do nothing (but don't fail again).  */
10787   if (p->error)
10788     return SUCCESS;
10789
10790   /* Operators should always be GENERIC bindings.  */
10791   gcc_assert (p->is_generic);
10792
10793   /* Look for an overridden binding.  */
10794   super_type = gfc_get_derived_super_type (derived);
10795   if (super_type && super_type->f2k_derived)
10796     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
10797                                                      op, true, NULL);
10798   else
10799     p->overridden = NULL;
10800
10801   /* Resolve general GENERIC properties using worker function.  */
10802   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
10803     goto error;
10804
10805   /* Check the targets to be procedures of correct interface.  */
10806   for (target = p->u.generic; target; target = target->next)
10807     {
10808       gfc_symbol* target_proc;
10809
10810       target_proc = get_checked_tb_operator_target (target, p->where);
10811       if (!target_proc)
10812         goto error;
10813
10814       if (!gfc_check_operator_interface (target_proc, op, p->where))
10815         goto error;
10816     }
10817
10818   return SUCCESS;
10819
10820 error:
10821   p->error = 1;
10822   return FAILURE;
10823 }
10824
10825
10826 /* Resolve a type-bound user operator (tree-walker callback).  */
10827
10828 static gfc_symbol* resolve_bindings_derived;
10829 static gfc_try resolve_bindings_result;
10830
10831 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
10832
10833 static void
10834 resolve_typebound_user_op (gfc_symtree* stree)
10835 {
10836   gfc_symbol* super_type;
10837   gfc_tbp_generic* target;
10838
10839   gcc_assert (stree && stree->n.tb);
10840
10841   if (stree->n.tb->error)
10842     return;
10843
10844   /* Operators should always be GENERIC bindings.  */
10845   gcc_assert (stree->n.tb->is_generic);
10846
10847   /* Find overridden procedure, if any.  */
10848   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10849   if (super_type && super_type->f2k_derived)
10850     {
10851       gfc_symtree* overridden;
10852       overridden = gfc_find_typebound_user_op (super_type, NULL,
10853                                                stree->name, true, NULL);
10854
10855       if (overridden && overridden->n.tb)
10856         stree->n.tb->overridden = overridden->n.tb;
10857     }
10858   else
10859     stree->n.tb->overridden = NULL;
10860
10861   /* Resolve basically using worker function.  */
10862   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
10863         == FAILURE)
10864     goto error;
10865
10866   /* Check the targets to be functions of correct interface.  */
10867   for (target = stree->n.tb->u.generic; target; target = target->next)
10868     {
10869       gfc_symbol* target_proc;
10870
10871       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
10872       if (!target_proc)
10873         goto error;
10874
10875       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
10876         goto error;
10877     }
10878
10879   return;
10880
10881 error:
10882   resolve_bindings_result = FAILURE;
10883   stree->n.tb->error = 1;
10884 }
10885
10886
10887 /* Resolve the type-bound procedures for a derived type.  */
10888
10889 static void
10890 resolve_typebound_procedure (gfc_symtree* stree)
10891 {
10892   gfc_symbol* proc;
10893   locus where;
10894   gfc_symbol* me_arg;
10895   gfc_symbol* super_type;
10896   gfc_component* comp;
10897
10898   gcc_assert (stree);
10899
10900   /* Undefined specific symbol from GENERIC target definition.  */
10901   if (!stree->n.tb)
10902     return;
10903
10904   if (stree->n.tb->error)
10905     return;
10906
10907   /* If this is a GENERIC binding, use that routine.  */
10908   if (stree->n.tb->is_generic)
10909     {
10910       if (resolve_typebound_generic (resolve_bindings_derived, stree)
10911             == FAILURE)
10912         goto error;
10913       return;
10914     }
10915
10916   /* Get the target-procedure to check it.  */
10917   gcc_assert (!stree->n.tb->is_generic);
10918   gcc_assert (stree->n.tb->u.specific);
10919   proc = stree->n.tb->u.specific->n.sym;
10920   where = stree->n.tb->where;
10921
10922   /* Default access should already be resolved from the parser.  */
10923   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
10924
10925   /* It should be a module procedure or an external procedure with explicit
10926      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
10927   if ((!proc->attr.subroutine && !proc->attr.function)
10928       || (proc->attr.proc != PROC_MODULE
10929           && proc->attr.if_source != IFSRC_IFBODY)
10930       || (proc->attr.abstract && !stree->n.tb->deferred))
10931     {
10932       gfc_error ("'%s' must be a module procedure or an external procedure with"
10933                  " an explicit interface at %L", proc->name, &where);
10934       goto error;
10935     }
10936   stree->n.tb->subroutine = proc->attr.subroutine;
10937   stree->n.tb->function = proc->attr.function;
10938
10939   /* Find the super-type of the current derived type.  We could do this once and
10940      store in a global if speed is needed, but as long as not I believe this is
10941      more readable and clearer.  */
10942   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10943
10944   /* If PASS, resolve and check arguments if not already resolved / loaded
10945      from a .mod file.  */
10946   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
10947     {
10948       if (stree->n.tb->pass_arg)
10949         {
10950           gfc_formal_arglist* i;
10951
10952           /* If an explicit passing argument name is given, walk the arg-list
10953              and look for it.  */
10954
10955           me_arg = NULL;
10956           stree->n.tb->pass_arg_num = 1;
10957           for (i = proc->formal; i; i = i->next)
10958             {
10959               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
10960                 {
10961                   me_arg = i->sym;
10962                   break;
10963                 }
10964               ++stree->n.tb->pass_arg_num;
10965             }
10966
10967           if (!me_arg)
10968             {
10969               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
10970                          " argument '%s'",
10971                          proc->name, stree->n.tb->pass_arg, &where,
10972                          stree->n.tb->pass_arg);
10973               goto error;
10974             }
10975         }
10976       else
10977         {
10978           /* Otherwise, take the first one; there should in fact be at least
10979              one.  */
10980           stree->n.tb->pass_arg_num = 1;
10981           if (!proc->formal)
10982             {
10983               gfc_error ("Procedure '%s' with PASS at %L must have at"
10984                          " least one argument", proc->name, &where);
10985               goto error;
10986             }
10987           me_arg = proc->formal->sym;
10988         }
10989
10990       /* Now check that the argument-type matches and the passed-object
10991          dummy argument is generally fine.  */
10992
10993       gcc_assert (me_arg);
10994
10995       if (me_arg->ts.type != BT_CLASS)
10996         {
10997           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10998                      " at %L", proc->name, &where);
10999           goto error;
11000         }
11001
11002       if (CLASS_DATA (me_arg)->ts.u.derived
11003           != resolve_bindings_derived)
11004         {
11005           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11006                      " the derived-type '%s'", me_arg->name, proc->name,
11007                      me_arg->name, &where, resolve_bindings_derived->name);
11008           goto error;
11009         }
11010   
11011       gcc_assert (me_arg->ts.type == BT_CLASS);
11012       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
11013         {
11014           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
11015                      " scalar", proc->name, &where);
11016           goto error;
11017         }
11018       if (CLASS_DATA (me_arg)->attr.allocatable)
11019         {
11020           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11021                      " be ALLOCATABLE", proc->name, &where);
11022           goto error;
11023         }
11024       if (CLASS_DATA (me_arg)->attr.class_pointer)
11025         {
11026           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11027                      " be POINTER", proc->name, &where);
11028           goto error;
11029         }
11030     }
11031
11032   /* If we are extending some type, check that we don't override a procedure
11033      flagged NON_OVERRIDABLE.  */
11034   stree->n.tb->overridden = NULL;
11035   if (super_type)
11036     {
11037       gfc_symtree* overridden;
11038       overridden = gfc_find_typebound_proc (super_type, NULL,
11039                                             stree->name, true, NULL);
11040
11041       if (overridden && overridden->n.tb)
11042         stree->n.tb->overridden = overridden->n.tb;
11043
11044       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
11045         goto error;
11046     }
11047
11048   /* See if there's a name collision with a component directly in this type.  */
11049   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
11050     if (!strcmp (comp->name, stree->name))
11051       {
11052         gfc_error ("Procedure '%s' at %L has the same name as a component of"
11053                    " '%s'",
11054                    stree->name, &where, resolve_bindings_derived->name);
11055         goto error;
11056       }
11057
11058   /* Try to find a name collision with an inherited component.  */
11059   if (super_type && gfc_find_component (super_type, stree->name, true, true))
11060     {
11061       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
11062                  " component of '%s'",
11063                  stree->name, &where, resolve_bindings_derived->name);
11064       goto error;
11065     }
11066
11067   stree->n.tb->error = 0;
11068   return;
11069
11070 error:
11071   resolve_bindings_result = FAILURE;
11072   stree->n.tb->error = 1;
11073 }
11074
11075
11076 static gfc_try
11077 resolve_typebound_procedures (gfc_symbol* derived)
11078 {
11079   int op;
11080
11081   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
11082     return SUCCESS;
11083
11084   resolve_bindings_derived = derived;
11085   resolve_bindings_result = SUCCESS;
11086
11087   /* Make sure the vtab has been generated.  */
11088   gfc_find_derived_vtab (derived);
11089
11090   if (derived->f2k_derived->tb_sym_root)
11091     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
11092                           &resolve_typebound_procedure);
11093
11094   if (derived->f2k_derived->tb_uop_root)
11095     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
11096                           &resolve_typebound_user_op);
11097
11098   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
11099     {
11100       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
11101       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
11102                                                p) == FAILURE)
11103         resolve_bindings_result = FAILURE;
11104     }
11105
11106   return resolve_bindings_result;
11107 }
11108
11109
11110 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
11111    to give all identical derived types the same backend_decl.  */
11112 static void
11113 add_dt_to_dt_list (gfc_symbol *derived)
11114 {
11115   gfc_dt_list *dt_list;
11116
11117   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
11118     if (derived == dt_list->derived)
11119       return;
11120
11121   dt_list = gfc_get_dt_list ();
11122   dt_list->next = gfc_derived_types;
11123   dt_list->derived = derived;
11124   gfc_derived_types = dt_list;
11125 }
11126
11127
11128 /* Ensure that a derived-type is really not abstract, meaning that every
11129    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
11130
11131 static gfc_try
11132 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
11133 {
11134   if (!st)
11135     return SUCCESS;
11136
11137   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
11138     return FAILURE;
11139   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
11140     return FAILURE;
11141
11142   if (st->n.tb && st->n.tb->deferred)
11143     {
11144       gfc_symtree* overriding;
11145       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
11146       if (!overriding)
11147         return FAILURE;
11148       gcc_assert (overriding->n.tb);
11149       if (overriding->n.tb->deferred)
11150         {
11151           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
11152                      " '%s' is DEFERRED and not overridden",
11153                      sub->name, &sub->declared_at, st->name);
11154           return FAILURE;
11155         }
11156     }
11157
11158   return SUCCESS;
11159 }
11160
11161 static gfc_try
11162 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
11163 {
11164   /* The algorithm used here is to recursively travel up the ancestry of sub
11165      and for each ancestor-type, check all bindings.  If any of them is
11166      DEFERRED, look it up starting from sub and see if the found (overriding)
11167      binding is not DEFERRED.
11168      This is not the most efficient way to do this, but it should be ok and is
11169      clearer than something sophisticated.  */
11170
11171   gcc_assert (ancestor && !sub->attr.abstract);
11172   
11173   if (!ancestor->attr.abstract)
11174     return SUCCESS;
11175
11176   /* Walk bindings of this ancestor.  */
11177   if (ancestor->f2k_derived)
11178     {
11179       gfc_try t;
11180       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
11181       if (t == FAILURE)
11182         return FAILURE;
11183     }
11184
11185   /* Find next ancestor type and recurse on it.  */
11186   ancestor = gfc_get_derived_super_type (ancestor);
11187   if (ancestor)
11188     return ensure_not_abstract (sub, ancestor);
11189
11190   return SUCCESS;
11191 }
11192
11193
11194 /* Resolve the components of a derived type.  */
11195
11196 static gfc_try
11197 resolve_fl_derived (gfc_symbol *sym)
11198 {
11199   gfc_symbol* super_type;
11200   gfc_component *c;
11201
11202   super_type = gfc_get_derived_super_type (sym);
11203   
11204   if (sym->attr.is_class && sym->ts.u.derived == NULL)
11205     {
11206       /* Fix up incomplete CLASS symbols.  */
11207       gfc_component *data = gfc_find_component (sym, "_data", true, true);
11208       gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true);
11209       if (vptr->ts.u.derived == NULL)
11210         {
11211           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
11212           gcc_assert (vtab);
11213           vptr->ts.u.derived = vtab->ts.u.derived;
11214         }
11215     }
11216
11217   /* F2008, C432. */
11218   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
11219     {
11220       gfc_error ("As extending type '%s' at %L has a coarray component, "
11221                  "parent type '%s' shall also have one", sym->name,
11222                  &sym->declared_at, super_type->name);
11223       return FAILURE;
11224     }
11225
11226   /* Ensure the extended type gets resolved before we do.  */
11227   if (super_type && resolve_fl_derived (super_type) == FAILURE)
11228     return FAILURE;
11229
11230   /* An ABSTRACT type must be extensible.  */
11231   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
11232     {
11233       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
11234                  sym->name, &sym->declared_at);
11235       return FAILURE;
11236     }
11237
11238   for (c = sym->components; c != NULL; c = c->next)
11239     {
11240       /* F2008, C442.  */
11241       if (c->attr.codimension /* FIXME: c->as check due to PR 43412.  */
11242           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
11243         {
11244           gfc_error ("Coarray component '%s' at %L must be allocatable with "
11245                      "deferred shape", c->name, &c->loc);
11246           return FAILURE;
11247         }
11248
11249       /* F2008, C443.  */
11250       if (c->attr.codimension && c->ts.type == BT_DERIVED
11251           && c->ts.u.derived->ts.is_iso_c)
11252         {
11253           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11254                      "shall not be a coarray", c->name, &c->loc);
11255           return FAILURE;
11256         }
11257
11258       /* F2008, C444.  */
11259       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
11260           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
11261               || c->attr.allocatable))
11262         {
11263           gfc_error ("Component '%s' at %L with coarray component "
11264                      "shall be a nonpointer, nonallocatable scalar",
11265                      c->name, &c->loc);
11266           return FAILURE;
11267         }
11268
11269       /* F2008, C448.  */
11270       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
11271         {
11272           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
11273                      "is not an array pointer", c->name, &c->loc);
11274           return FAILURE;
11275         }
11276
11277       if (c->attr.proc_pointer && c->ts.interface)
11278         {
11279           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
11280             gfc_error ("Interface '%s', used by procedure pointer component "
11281                        "'%s' at %L, is declared in a later PROCEDURE statement",
11282                        c->ts.interface->name, c->name, &c->loc);
11283
11284           /* Get the attributes from the interface (now resolved).  */
11285           if (c->ts.interface->attr.if_source
11286               || c->ts.interface->attr.intrinsic)
11287             {
11288               gfc_symbol *ifc = c->ts.interface;
11289
11290               if (ifc->formal && !ifc->formal_ns)
11291                 resolve_symbol (ifc);
11292
11293               if (ifc->attr.intrinsic)
11294                 resolve_intrinsic (ifc, &ifc->declared_at);
11295
11296               if (ifc->result)
11297                 {
11298                   c->ts = ifc->result->ts;
11299                   c->attr.allocatable = ifc->result->attr.allocatable;
11300                   c->attr.pointer = ifc->result->attr.pointer;
11301                   c->attr.dimension = ifc->result->attr.dimension;
11302                   c->as = gfc_copy_array_spec (ifc->result->as);
11303                 }
11304               else
11305                 {   
11306                   c->ts = ifc->ts;
11307                   c->attr.allocatable = ifc->attr.allocatable;
11308                   c->attr.pointer = ifc->attr.pointer;
11309                   c->attr.dimension = ifc->attr.dimension;
11310                   c->as = gfc_copy_array_spec (ifc->as);
11311                 }
11312               c->ts.interface = ifc;
11313               c->attr.function = ifc->attr.function;
11314               c->attr.subroutine = ifc->attr.subroutine;
11315               gfc_copy_formal_args_ppc (c, ifc);
11316
11317               c->attr.pure = ifc->attr.pure;
11318               c->attr.elemental = ifc->attr.elemental;
11319               c->attr.recursive = ifc->attr.recursive;
11320               c->attr.always_explicit = ifc->attr.always_explicit;
11321               c->attr.ext_attr |= ifc->attr.ext_attr;
11322               /* Replace symbols in array spec.  */
11323               if (c->as)
11324                 {
11325                   int i;
11326                   for (i = 0; i < c->as->rank; i++)
11327                     {
11328                       gfc_expr_replace_comp (c->as->lower[i], c);
11329                       gfc_expr_replace_comp (c->as->upper[i], c);
11330                     }
11331                 }
11332               /* Copy char length.  */
11333               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11334                 {
11335                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11336                   gfc_expr_replace_comp (cl->length, c);
11337                   if (cl->length && !cl->resolved
11338                         && gfc_resolve_expr (cl->length) == FAILURE)
11339                     return FAILURE;
11340                   c->ts.u.cl = cl;
11341                 }
11342             }
11343           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
11344             {
11345               gfc_error ("Interface '%s' of procedure pointer component "
11346                          "'%s' at %L must be explicit", c->ts.interface->name,
11347                          c->name, &c->loc);
11348               return FAILURE;
11349             }
11350         }
11351       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
11352         {
11353           /* Since PPCs are not implicitly typed, a PPC without an explicit
11354              interface must be a subroutine.  */
11355           gfc_add_subroutine (&c->attr, c->name, &c->loc);
11356         }
11357
11358       /* Procedure pointer components: Check PASS arg.  */
11359       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
11360           && !sym->attr.vtype)
11361         {
11362           gfc_symbol* me_arg;
11363
11364           if (c->tb->pass_arg)
11365             {
11366               gfc_formal_arglist* i;
11367
11368               /* If an explicit passing argument name is given, walk the arg-list
11369                 and look for it.  */
11370
11371               me_arg = NULL;
11372               c->tb->pass_arg_num = 1;
11373               for (i = c->formal; i; i = i->next)
11374                 {
11375                   if (!strcmp (i->sym->name, c->tb->pass_arg))
11376                     {
11377                       me_arg = i->sym;
11378                       break;
11379                     }
11380                   c->tb->pass_arg_num++;
11381                 }
11382
11383               if (!me_arg)
11384                 {
11385                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
11386                              "at %L has no argument '%s'", c->name,
11387                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
11388                   c->tb->error = 1;
11389                   return FAILURE;
11390                 }
11391             }
11392           else
11393             {
11394               /* Otherwise, take the first one; there should in fact be at least
11395                 one.  */
11396               c->tb->pass_arg_num = 1;
11397               if (!c->formal)
11398                 {
11399                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
11400                              "must have at least one argument",
11401                              c->name, &c->loc);
11402                   c->tb->error = 1;
11403                   return FAILURE;
11404                 }
11405               me_arg = c->formal->sym;
11406             }
11407
11408           /* Now check that the argument-type matches.  */
11409           gcc_assert (me_arg);
11410           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
11411               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
11412               || (me_arg->ts.type == BT_CLASS
11413                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
11414             {
11415               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11416                          " the derived type '%s'", me_arg->name, c->name,
11417                          me_arg->name, &c->loc, sym->name);
11418               c->tb->error = 1;
11419               return FAILURE;
11420             }
11421
11422           /* Check for C453.  */
11423           if (me_arg->attr.dimension)
11424             {
11425               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11426                          "must be scalar", me_arg->name, c->name, me_arg->name,
11427                          &c->loc);
11428               c->tb->error = 1;
11429               return FAILURE;
11430             }
11431
11432           if (me_arg->attr.pointer)
11433             {
11434               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11435                          "may not have the POINTER attribute", me_arg->name,
11436                          c->name, me_arg->name, &c->loc);
11437               c->tb->error = 1;
11438               return FAILURE;
11439             }
11440
11441           if (me_arg->attr.allocatable)
11442             {
11443               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11444                          "may not be ALLOCATABLE", me_arg->name, c->name,
11445                          me_arg->name, &c->loc);
11446               c->tb->error = 1;
11447               return FAILURE;
11448             }
11449
11450           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11451             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11452                        " at %L", c->name, &c->loc);
11453
11454         }
11455
11456       /* Check type-spec if this is not the parent-type component.  */
11457       if ((!sym->attr.extension || c != sym->components) && !sym->attr.vtype
11458           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11459         return FAILURE;
11460
11461       /* If this type is an extension, set the accessibility of the parent
11462          component.  */
11463       if (super_type && c == sym->components
11464           && strcmp (super_type->name, c->name) == 0)
11465         c->attr.access = super_type->attr.access;
11466       
11467       /* If this type is an extension, see if this component has the same name
11468          as an inherited type-bound procedure.  */
11469       if (super_type && !sym->attr.is_class
11470           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11471         {
11472           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11473                      " inherited type-bound procedure",
11474                      c->name, sym->name, &c->loc);
11475           return FAILURE;
11476         }
11477
11478       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer)
11479         {
11480          if (c->ts.u.cl->length == NULL
11481              || (resolve_charlen (c->ts.u.cl) == FAILURE)
11482              || !gfc_is_constant_expr (c->ts.u.cl->length))
11483            {
11484              gfc_error ("Character length of component '%s' needs to "
11485                         "be a constant specification expression at %L",
11486                         c->name,
11487                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
11488              return FAILURE;
11489            }
11490         }
11491
11492       if (c->ts.type == BT_DERIVED
11493           && sym->component_access != ACCESS_PRIVATE
11494           && gfc_check_access (sym->attr.access, sym->ns->default_access)
11495           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11496           && !c->ts.u.derived->attr.use_assoc
11497           && !gfc_check_access (c->ts.u.derived->attr.access,
11498                                 c->ts.u.derived->ns->default_access)
11499           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11500                              "is a PRIVATE type and cannot be a component of "
11501                              "'%s', which is PUBLIC at %L", c->name,
11502                              sym->name, &sym->declared_at) == FAILURE)
11503         return FAILURE;
11504
11505       if ((sym->attr.sequence || sym->attr.is_bind_c) && c->ts.type == BT_CLASS)
11506         {
11507           gfc_error ("Polymorphic component %s at %L in SEQUENCE or BIND(C) "
11508                      "type %s", c->name, &c->loc, sym->name);
11509           return FAILURE;
11510         }
11511
11512       if (sym->attr.sequence)
11513         {
11514           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
11515             {
11516               gfc_error ("Component %s of SEQUENCE type declared at %L does "
11517                          "not have the SEQUENCE attribute",
11518                          c->ts.u.derived->name, &sym->declared_at);
11519               return FAILURE;
11520             }
11521         }
11522
11523       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && !sym->attr.vtype
11524           && c->attr.pointer && c->ts.u.derived->components == NULL
11525           && !c->ts.u.derived->attr.zero_comp)
11526         {
11527           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11528                      "that has not been declared", c->name, sym->name,
11529                      &c->loc);
11530           return FAILURE;
11531         }
11532
11533       if (c->ts.type == BT_CLASS && CLASS_DATA (c)->attr.class_pointer
11534           && CLASS_DATA (c)->ts.u.derived->components == NULL
11535           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
11536         {
11537           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11538                      "that has not been declared", c->name, sym->name,
11539                      &c->loc);
11540           return FAILURE;
11541         }
11542
11543       /* C437.  */
11544       if (c->ts.type == BT_CLASS
11545           && !(CLASS_DATA (c)->attr.class_pointer
11546                || CLASS_DATA (c)->attr.allocatable))
11547         {
11548           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
11549                      "or pointer", c->name, &c->loc);
11550           return FAILURE;
11551         }
11552
11553       /* Ensure that all the derived type components are put on the
11554          derived type list; even in formal namespaces, where derived type
11555          pointer components might not have been declared.  */
11556       if (c->ts.type == BT_DERIVED
11557             && c->ts.u.derived
11558             && c->ts.u.derived->components
11559             && c->attr.pointer
11560             && sym != c->ts.u.derived)
11561         add_dt_to_dt_list (c->ts.u.derived);
11562
11563       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
11564                                            || c->attr.proc_pointer
11565                                            || c->attr.allocatable)) == FAILURE)
11566         return FAILURE;
11567     }
11568
11569   /* Resolve the type-bound procedures.  */
11570   if (resolve_typebound_procedures (sym) == FAILURE)
11571     return FAILURE;
11572
11573   /* Resolve the finalizer procedures.  */
11574   if (gfc_resolve_finalizers (sym) == FAILURE)
11575     return FAILURE;
11576
11577   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11578      all DEFERRED bindings are overridden.  */
11579   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11580       && !sym->attr.is_class
11581       && ensure_not_abstract (sym, super_type) == FAILURE)
11582     return FAILURE;
11583
11584   /* Add derived type to the derived type list.  */
11585   add_dt_to_dt_list (sym);
11586
11587   return SUCCESS;
11588 }
11589
11590
11591 static gfc_try
11592 resolve_fl_namelist (gfc_symbol *sym)
11593 {
11594   gfc_namelist *nl;
11595   gfc_symbol *nlsym;
11596
11597   for (nl = sym->namelist; nl; nl = nl->next)
11598     {
11599       /* Reject namelist arrays of assumed shape.  */
11600       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
11601           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
11602                              "must not have assumed shape in namelist "
11603                              "'%s' at %L", nl->sym->name, sym->name,
11604                              &sym->declared_at) == FAILURE)
11605             return FAILURE;
11606
11607       /* Reject namelist arrays that are not constant shape.  */
11608       if (is_non_constant_shape_array (nl->sym))
11609         {
11610           gfc_error ("NAMELIST array object '%s' must have constant "
11611                      "shape in namelist '%s' at %L", nl->sym->name,
11612                      sym->name, &sym->declared_at);
11613           return FAILURE;
11614         }
11615
11616       /* Namelist objects cannot have allocatable or pointer components.  */
11617       if (nl->sym->ts.type != BT_DERIVED)
11618         continue;
11619
11620       if (nl->sym->ts.u.derived->attr.alloc_comp)
11621         {
11622           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11623                      "have ALLOCATABLE components",
11624                      nl->sym->name, sym->name, &sym->declared_at);
11625           return FAILURE;
11626         }
11627
11628       if (nl->sym->ts.u.derived->attr.pointer_comp)
11629         {
11630           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11631                      "have POINTER components", 
11632                      nl->sym->name, sym->name, &sym->declared_at);
11633           return FAILURE;
11634         }
11635     }
11636
11637   /* Reject PRIVATE objects in a PUBLIC namelist.  */
11638   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
11639     {
11640       for (nl = sym->namelist; nl; nl = nl->next)
11641         {
11642           if (!nl->sym->attr.use_assoc
11643               && !is_sym_host_assoc (nl->sym, sym->ns)
11644               && !gfc_check_access(nl->sym->attr.access,
11645                                 nl->sym->ns->default_access))
11646             {
11647               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
11648                          "cannot be member of PUBLIC namelist '%s' at %L",
11649                          nl->sym->name, sym->name, &sym->declared_at);
11650               return FAILURE;
11651             }
11652
11653           /* Types with private components that came here by USE-association.  */
11654           if (nl->sym->ts.type == BT_DERIVED
11655               && derived_inaccessible (nl->sym->ts.u.derived))
11656             {
11657               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
11658                          "components and cannot be member of namelist '%s' at %L",
11659                          nl->sym->name, sym->name, &sym->declared_at);
11660               return FAILURE;
11661             }
11662
11663           /* Types with private components that are defined in the same module.  */
11664           if (nl->sym->ts.type == BT_DERIVED
11665               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
11666               && !gfc_check_access (nl->sym->ts.u.derived->attr.private_comp
11667                                         ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
11668                                         nl->sym->ns->default_access))
11669             {
11670               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
11671                          "cannot be a member of PUBLIC namelist '%s' at %L",
11672                          nl->sym->name, sym->name, &sym->declared_at);
11673               return FAILURE;
11674             }
11675         }
11676     }
11677
11678
11679   /* 14.1.2 A module or internal procedure represent local entities
11680      of the same type as a namelist member and so are not allowed.  */
11681   for (nl = sym->namelist; nl; nl = nl->next)
11682     {
11683       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
11684         continue;
11685
11686       if (nl->sym->attr.function && nl->sym == nl->sym->result)
11687         if ((nl->sym == sym->ns->proc_name)
11688                ||
11689             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
11690           continue;
11691
11692       nlsym = NULL;
11693       if (nl->sym && nl->sym->name)
11694         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
11695       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
11696         {
11697           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
11698                      "attribute in '%s' at %L", nlsym->name,
11699                      &sym->declared_at);
11700           return FAILURE;
11701         }
11702     }
11703
11704   return SUCCESS;
11705 }
11706
11707
11708 static gfc_try
11709 resolve_fl_parameter (gfc_symbol *sym)
11710 {
11711   /* A parameter array's shape needs to be constant.  */
11712   if (sym->as != NULL 
11713       && (sym->as->type == AS_DEFERRED
11714           || is_non_constant_shape_array (sym)))
11715     {
11716       gfc_error ("Parameter array '%s' at %L cannot be automatic "
11717                  "or of deferred shape", sym->name, &sym->declared_at);
11718       return FAILURE;
11719     }
11720
11721   /* Make sure a parameter that has been implicitly typed still
11722      matches the implicit type, since PARAMETER statements can precede
11723      IMPLICIT statements.  */
11724   if (sym->attr.implicit_type
11725       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
11726                                                              sym->ns)))
11727     {
11728       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
11729                  "later IMPLICIT type", sym->name, &sym->declared_at);
11730       return FAILURE;
11731     }
11732
11733   /* Make sure the types of derived parameters are consistent.  This
11734      type checking is deferred until resolution because the type may
11735      refer to a derived type from the host.  */
11736   if (sym->ts.type == BT_DERIVED
11737       && !gfc_compare_types (&sym->ts, &sym->value->ts))
11738     {
11739       gfc_error ("Incompatible derived type in PARAMETER at %L",
11740                  &sym->value->where);
11741       return FAILURE;
11742     }
11743   return SUCCESS;
11744 }
11745
11746
11747 /* Do anything necessary to resolve a symbol.  Right now, we just
11748    assume that an otherwise unknown symbol is a variable.  This sort
11749    of thing commonly happens for symbols in module.  */
11750
11751 static void
11752 resolve_symbol (gfc_symbol *sym)
11753 {
11754   int check_constant, mp_flag;
11755   gfc_symtree *symtree;
11756   gfc_symtree *this_symtree;
11757   gfc_namespace *ns;
11758   gfc_component *c;
11759
11760   /* Avoid double resolution of function result symbols.  */
11761   if ((sym->result || sym->attr.result) && !sym->attr.dummy
11762       && (sym->ns != gfc_current_ns))
11763     return;
11764   
11765   if (sym->attr.flavor == FL_UNKNOWN)
11766     {
11767
11768     /* If we find that a flavorless symbol is an interface in one of the
11769        parent namespaces, find its symtree in this namespace, free the
11770        symbol and set the symtree to point to the interface symbol.  */
11771       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
11772         {
11773           symtree = gfc_find_symtree (ns->sym_root, sym->name);
11774           if (symtree && symtree->n.sym->generic)
11775             {
11776               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
11777                                                sym->name);
11778               gfc_release_symbol (sym);
11779               symtree->n.sym->refs++;
11780               this_symtree->n.sym = symtree->n.sym;
11781               return;
11782             }
11783         }
11784
11785       /* Otherwise give it a flavor according to such attributes as
11786          it has.  */
11787       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
11788         sym->attr.flavor = FL_VARIABLE;
11789       else
11790         {
11791           sym->attr.flavor = FL_PROCEDURE;
11792           if (sym->attr.dimension)
11793             sym->attr.function = 1;
11794         }
11795     }
11796
11797   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
11798     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
11799
11800   if (sym->attr.procedure && sym->ts.interface
11801       && sym->attr.if_source != IFSRC_DECL
11802       && resolve_procedure_interface (sym) == FAILURE)
11803     return;
11804
11805   if (sym->attr.is_protected && !sym->attr.proc_pointer
11806       && (sym->attr.procedure || sym->attr.external))
11807     {
11808       if (sym->attr.external)
11809         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
11810                    "at %L", &sym->declared_at);
11811       else
11812         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
11813                    "at %L", &sym->declared_at);
11814
11815       return;
11816     }
11817
11818
11819   /* F2008, C530. */
11820   if (sym->attr.contiguous
11821       && (!sym->attr.dimension || (sym->as->type != AS_ASSUMED_SHAPE
11822                                    && !sym->attr.pointer)))
11823     {
11824       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
11825                   "array pointer or an assumed-shape array", sym->name,
11826                   &sym->declared_at);
11827       return;
11828     }
11829
11830   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
11831     return;
11832
11833   /* Symbols that are module procedures with results (functions) have
11834      the types and array specification copied for type checking in
11835      procedures that call them, as well as for saving to a module
11836      file.  These symbols can't stand the scrutiny that their results
11837      can.  */
11838   mp_flag = (sym->result != NULL && sym->result != sym);
11839
11840   /* Make sure that the intrinsic is consistent with its internal 
11841      representation. This needs to be done before assigning a default 
11842      type to avoid spurious warnings.  */
11843   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
11844       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
11845     return;
11846
11847   /* Resolve associate names.  */
11848   if (sym->assoc)
11849     resolve_assoc_var (sym, true);
11850
11851   /* Assign default type to symbols that need one and don't have one.  */
11852   if (sym->ts.type == BT_UNKNOWN)
11853     {
11854       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
11855         gfc_set_default_type (sym, 1, NULL);
11856
11857       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
11858           && !sym->attr.function && !sym->attr.subroutine
11859           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
11860         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
11861
11862       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
11863         {
11864           /* The specific case of an external procedure should emit an error
11865              in the case that there is no implicit type.  */
11866           if (!mp_flag)
11867             gfc_set_default_type (sym, sym->attr.external, NULL);
11868           else
11869             {
11870               /* Result may be in another namespace.  */
11871               resolve_symbol (sym->result);
11872
11873               if (!sym->result->attr.proc_pointer)
11874                 {
11875                   sym->ts = sym->result->ts;
11876                   sym->as = gfc_copy_array_spec (sym->result->as);
11877                   sym->attr.dimension = sym->result->attr.dimension;
11878                   sym->attr.pointer = sym->result->attr.pointer;
11879                   sym->attr.allocatable = sym->result->attr.allocatable;
11880                   sym->attr.contiguous = sym->result->attr.contiguous;
11881                 }
11882             }
11883         }
11884     }
11885
11886   /* Assumed size arrays and assumed shape arrays must be dummy
11887      arguments.  Array-spec's of implied-shape should have been resolved to
11888      AS_EXPLICIT already.  */
11889
11890   if (sym->as)
11891     {
11892       gcc_assert (sym->as->type != AS_IMPLIED_SHAPE);
11893       if (((sym->as->type == AS_ASSUMED_SIZE && !sym->as->cp_was_assumed)
11894            || sym->as->type == AS_ASSUMED_SHAPE)
11895           && sym->attr.dummy == 0)
11896         {
11897           if (sym->as->type == AS_ASSUMED_SIZE)
11898             gfc_error ("Assumed size array at %L must be a dummy argument",
11899                        &sym->declared_at);
11900           else
11901             gfc_error ("Assumed shape array at %L must be a dummy argument",
11902                        &sym->declared_at);
11903           return;
11904         }
11905     }
11906
11907   /* Make sure symbols with known intent or optional are really dummy
11908      variable.  Because of ENTRY statement, this has to be deferred
11909      until resolution time.  */
11910
11911   if (!sym->attr.dummy
11912       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
11913     {
11914       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
11915       return;
11916     }
11917
11918   if (sym->attr.value && !sym->attr.dummy)
11919     {
11920       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
11921                  "it is not a dummy argument", sym->name, &sym->declared_at);
11922       return;
11923     }
11924
11925   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
11926     {
11927       gfc_charlen *cl = sym->ts.u.cl;
11928       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
11929         {
11930           gfc_error ("Character dummy variable '%s' at %L with VALUE "
11931                      "attribute must have constant length",
11932                      sym->name, &sym->declared_at);
11933           return;
11934         }
11935
11936       if (sym->ts.is_c_interop
11937           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
11938         {
11939           gfc_error ("C interoperable character dummy variable '%s' at %L "
11940                      "with VALUE attribute must have length one",
11941                      sym->name, &sym->declared_at);
11942           return;
11943         }
11944     }
11945
11946   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
11947      do this for something that was implicitly typed because that is handled
11948      in gfc_set_default_type.  Handle dummy arguments and procedure
11949      definitions separately.  Also, anything that is use associated is not
11950      handled here but instead is handled in the module it is declared in.
11951      Finally, derived type definitions are allowed to be BIND(C) since that
11952      only implies that they're interoperable, and they are checked fully for
11953      interoperability when a variable is declared of that type.  */
11954   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
11955       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
11956       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
11957     {
11958       gfc_try t = SUCCESS;
11959       
11960       /* First, make sure the variable is declared at the
11961          module-level scope (J3/04-007, Section 15.3).  */
11962       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
11963           sym->attr.in_common == 0)
11964         {
11965           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
11966                      "is neither a COMMON block nor declared at the "
11967                      "module level scope", sym->name, &(sym->declared_at));
11968           t = FAILURE;
11969         }
11970       else if (sym->common_head != NULL)
11971         {
11972           t = verify_com_block_vars_c_interop (sym->common_head);
11973         }
11974       else
11975         {
11976           /* If type() declaration, we need to verify that the components
11977              of the given type are all C interoperable, etc.  */
11978           if (sym->ts.type == BT_DERIVED &&
11979               sym->ts.u.derived->attr.is_c_interop != 1)
11980             {
11981               /* Make sure the user marked the derived type as BIND(C).  If
11982                  not, call the verify routine.  This could print an error
11983                  for the derived type more than once if multiple variables
11984                  of that type are declared.  */
11985               if (sym->ts.u.derived->attr.is_bind_c != 1)
11986                 verify_bind_c_derived_type (sym->ts.u.derived);
11987               t = FAILURE;
11988             }
11989           
11990           /* Verify the variable itself as C interoperable if it
11991              is BIND(C).  It is not possible for this to succeed if
11992              the verify_bind_c_derived_type failed, so don't have to handle
11993              any error returned by verify_bind_c_derived_type.  */
11994           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
11995                                  sym->common_block);
11996         }
11997
11998       if (t == FAILURE)
11999         {
12000           /* clear the is_bind_c flag to prevent reporting errors more than
12001              once if something failed.  */
12002           sym->attr.is_bind_c = 0;
12003           return;
12004         }
12005     }
12006
12007   /* If a derived type symbol has reached this point, without its
12008      type being declared, we have an error.  Notice that most
12009      conditions that produce undefined derived types have already
12010      been dealt with.  However, the likes of:
12011      implicit type(t) (t) ..... call foo (t) will get us here if
12012      the type is not declared in the scope of the implicit
12013      statement. Change the type to BT_UNKNOWN, both because it is so
12014      and to prevent an ICE.  */
12015   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
12016       && !sym->ts.u.derived->attr.zero_comp)
12017     {
12018       gfc_error ("The derived type '%s' at %L is of type '%s', "
12019                  "which has not been defined", sym->name,
12020                   &sym->declared_at, sym->ts.u.derived->name);
12021       sym->ts.type = BT_UNKNOWN;
12022       return;
12023     }
12024
12025   /* Make sure that the derived type has been resolved and that the
12026      derived type is visible in the symbol's namespace, if it is a
12027      module function and is not PRIVATE.  */
12028   if (sym->ts.type == BT_DERIVED
12029         && sym->ts.u.derived->attr.use_assoc
12030         && sym->ns->proc_name
12031         && sym->ns->proc_name->attr.flavor == FL_MODULE)
12032     {
12033       gfc_symbol *ds;
12034
12035       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
12036         return;
12037
12038       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
12039       if (!ds && sym->attr.function
12040             && gfc_check_access (sym->attr.access, sym->ns->default_access))
12041         {
12042           symtree = gfc_new_symtree (&sym->ns->sym_root,
12043                                      sym->ts.u.derived->name);
12044           symtree->n.sym = sym->ts.u.derived;
12045           sym->ts.u.derived->refs++;
12046         }
12047     }
12048
12049   /* Unless the derived-type declaration is use associated, Fortran 95
12050      does not allow public entries of private derived types.
12051      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
12052      161 in 95-006r3.  */
12053   if (sym->ts.type == BT_DERIVED
12054       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
12055       && !sym->ts.u.derived->attr.use_assoc
12056       && gfc_check_access (sym->attr.access, sym->ns->default_access)
12057       && !gfc_check_access (sym->ts.u.derived->attr.access,
12058                             sym->ts.u.derived->ns->default_access)
12059       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
12060                          "of PRIVATE derived type '%s'",
12061                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
12062                          : "variable", sym->name, &sym->declared_at,
12063                          sym->ts.u.derived->name) == FAILURE)
12064     return;
12065
12066   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
12067      default initialization is defined (5.1.2.4.4).  */
12068   if (sym->ts.type == BT_DERIVED
12069       && sym->attr.dummy
12070       && sym->attr.intent == INTENT_OUT
12071       && sym->as
12072       && sym->as->type == AS_ASSUMED_SIZE)
12073     {
12074       for (c = sym->ts.u.derived->components; c; c = c->next)
12075         {
12076           if (c->initializer)
12077             {
12078               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
12079                          "ASSUMED SIZE and so cannot have a default initializer",
12080                          sym->name, &sym->declared_at);
12081               return;
12082             }
12083         }
12084     }
12085
12086   /* F2008, C526.  */
12087   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12088        || sym->attr.codimension)
12089       && sym->attr.result)
12090     gfc_error ("Function result '%s' at %L shall not be a coarray or have "
12091                "a coarray component", sym->name, &sym->declared_at);
12092
12093   /* F2008, C524.  */
12094   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
12095       && sym->ts.u.derived->ts.is_iso_c)
12096     gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12097                "shall not be a coarray", sym->name, &sym->declared_at);
12098
12099   /* F2008, C525.  */
12100   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp
12101       && (sym->attr.codimension || sym->attr.pointer || sym->attr.dimension
12102           || sym->attr.allocatable))
12103     gfc_error ("Variable '%s' at %L with coarray component "
12104                "shall be a nonpointer, nonallocatable scalar",
12105                sym->name, &sym->declared_at);
12106
12107   /* F2008, C526.  The function-result case was handled above.  */
12108   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12109        || sym->attr.codimension)
12110       && !(sym->attr.allocatable || sym->attr.dummy || sym->attr.save
12111            || sym->ns->proc_name->attr.flavor == FL_MODULE
12112            || sym->ns->proc_name->attr.is_main_program
12113            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
12114     gfc_error ("Variable '%s' at %L is a coarray or has a coarray "
12115                "component and is not ALLOCATABLE, SAVE nor a "
12116                "dummy argument", sym->name, &sym->declared_at);
12117   /* F2008, C528.  */  /* FIXME: sym->as check due to PR 43412.  */
12118   else if (sym->attr.codimension && !sym->attr.allocatable
12119       && sym->as && sym->as->cotype == AS_DEFERRED)
12120     gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
12121                 "deferred shape", sym->name, &sym->declared_at);
12122   else if (sym->attr.codimension && sym->attr.allocatable
12123       && (sym->as->type != AS_DEFERRED || sym->as->cotype != AS_DEFERRED))
12124     gfc_error ("Allocatable coarray variable '%s' at %L must have "
12125                "deferred shape", sym->name, &sym->declared_at);
12126
12127
12128   /* F2008, C541.  */
12129   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12130        || (sym->attr.codimension && sym->attr.allocatable))
12131       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
12132     gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
12133                "allocatable coarray or have coarray components",
12134                sym->name, &sym->declared_at);
12135
12136   if (sym->attr.codimension && sym->attr.dummy
12137       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
12138     gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
12139                "procedure '%s'", sym->name, &sym->declared_at,
12140                sym->ns->proc_name->name);
12141
12142   switch (sym->attr.flavor)
12143     {
12144     case FL_VARIABLE:
12145       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
12146         return;
12147       break;
12148
12149     case FL_PROCEDURE:
12150       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
12151         return;
12152       break;
12153
12154     case FL_NAMELIST:
12155       if (resolve_fl_namelist (sym) == FAILURE)
12156         return;
12157       break;
12158
12159     case FL_PARAMETER:
12160       if (resolve_fl_parameter (sym) == FAILURE)
12161         return;
12162       break;
12163
12164     default:
12165       break;
12166     }
12167
12168   /* Resolve array specifier. Check as well some constraints
12169      on COMMON blocks.  */
12170
12171   check_constant = sym->attr.in_common && !sym->attr.pointer;
12172
12173   /* Set the formal_arg_flag so that check_conflict will not throw
12174      an error for host associated variables in the specification
12175      expression for an array_valued function.  */
12176   if (sym->attr.function && sym->as)
12177     formal_arg_flag = 1;
12178
12179   gfc_resolve_array_spec (sym->as, check_constant);
12180
12181   formal_arg_flag = 0;
12182
12183   /* Resolve formal namespaces.  */
12184   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
12185       && !sym->attr.contained && !sym->attr.intrinsic)
12186     gfc_resolve (sym->formal_ns);
12187
12188   /* Make sure the formal namespace is present.  */
12189   if (sym->formal && !sym->formal_ns)
12190     {
12191       gfc_formal_arglist *formal = sym->formal;
12192       while (formal && !formal->sym)
12193         formal = formal->next;
12194
12195       if (formal)
12196         {
12197           sym->formal_ns = formal->sym->ns;
12198           sym->formal_ns->refs++;
12199         }
12200     }
12201
12202   /* Check threadprivate restrictions.  */
12203   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
12204       && (!sym->attr.in_common
12205           && sym->module == NULL
12206           && (sym->ns->proc_name == NULL
12207               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
12208     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
12209
12210   /* If we have come this far we can apply default-initializers, as
12211      described in 14.7.5, to those variables that have not already
12212      been assigned one.  */
12213   if (sym->ts.type == BT_DERIVED
12214       && sym->ns == gfc_current_ns
12215       && !sym->value
12216       && !sym->attr.allocatable
12217       && !sym->attr.alloc_comp)
12218     {
12219       symbol_attribute *a = &sym->attr;
12220
12221       if ((!a->save && !a->dummy && !a->pointer
12222            && !a->in_common && !a->use_assoc
12223            && (a->referenced || a->result)
12224            && !(a->function && sym != sym->result))
12225           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
12226         apply_default_init (sym);
12227     }
12228
12229   if (sym->ts.type == BT_CLASS && sym->ns == gfc_current_ns
12230       && sym->attr.dummy && sym->attr.intent == INTENT_OUT
12231       && !CLASS_DATA (sym)->attr.class_pointer
12232       && !CLASS_DATA (sym)->attr.allocatable)
12233     apply_default_init (sym);
12234
12235   /* If this symbol has a type-spec, check it.  */
12236   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
12237       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
12238     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
12239           == FAILURE)
12240       return;
12241 }
12242
12243
12244 /************* Resolve DATA statements *************/
12245
12246 static struct
12247 {
12248   gfc_data_value *vnode;
12249   mpz_t left;
12250 }
12251 values;
12252
12253
12254 /* Advance the values structure to point to the next value in the data list.  */
12255
12256 static gfc_try
12257 next_data_value (void)
12258 {
12259   while (mpz_cmp_ui (values.left, 0) == 0)
12260     {
12261
12262       if (values.vnode->next == NULL)
12263         return FAILURE;
12264
12265       values.vnode = values.vnode->next;
12266       mpz_set (values.left, values.vnode->repeat);
12267     }
12268
12269   return SUCCESS;
12270 }
12271
12272
12273 static gfc_try
12274 check_data_variable (gfc_data_variable *var, locus *where)
12275 {
12276   gfc_expr *e;
12277   mpz_t size;
12278   mpz_t offset;
12279   gfc_try t;
12280   ar_type mark = AR_UNKNOWN;
12281   int i;
12282   mpz_t section_index[GFC_MAX_DIMENSIONS];
12283   gfc_ref *ref;
12284   gfc_array_ref *ar;
12285   gfc_symbol *sym;
12286   int has_pointer;
12287
12288   if (gfc_resolve_expr (var->expr) == FAILURE)
12289     return FAILURE;
12290
12291   ar = NULL;
12292   mpz_init_set_si (offset, 0);
12293   e = var->expr;
12294
12295   if (e->expr_type != EXPR_VARIABLE)
12296     gfc_internal_error ("check_data_variable(): Bad expression");
12297
12298   sym = e->symtree->n.sym;
12299
12300   if (sym->ns->is_block_data && !sym->attr.in_common)
12301     {
12302       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
12303                  sym->name, &sym->declared_at);
12304     }
12305
12306   if (e->ref == NULL && sym->as)
12307     {
12308       gfc_error ("DATA array '%s' at %L must be specified in a previous"
12309                  " declaration", sym->name, where);
12310       return FAILURE;
12311     }
12312
12313   has_pointer = sym->attr.pointer;
12314
12315   for (ref = e->ref; ref; ref = ref->next)
12316     {
12317       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
12318         has_pointer = 1;
12319
12320       if (ref->type == REF_ARRAY && ref->u.ar.codimen)
12321         {
12322           gfc_error ("DATA element '%s' at %L cannot have a coindex",
12323                      sym->name, where);
12324           return FAILURE;
12325         }
12326
12327       if (has_pointer
12328             && ref->type == REF_ARRAY
12329             && ref->u.ar.type != AR_FULL)
12330           {
12331             gfc_error ("DATA element '%s' at %L is a pointer and so must "
12332                         "be a full array", sym->name, where);
12333             return FAILURE;
12334           }
12335     }
12336
12337   if (e->rank == 0 || has_pointer)
12338     {
12339       mpz_init_set_ui (size, 1);
12340       ref = NULL;
12341     }
12342   else
12343     {
12344       ref = e->ref;
12345
12346       /* Find the array section reference.  */
12347       for (ref = e->ref; ref; ref = ref->next)
12348         {
12349           if (ref->type != REF_ARRAY)
12350             continue;
12351           if (ref->u.ar.type == AR_ELEMENT)
12352             continue;
12353           break;
12354         }
12355       gcc_assert (ref);
12356
12357       /* Set marks according to the reference pattern.  */
12358       switch (ref->u.ar.type)
12359         {
12360         case AR_FULL:
12361           mark = AR_FULL;
12362           break;
12363
12364         case AR_SECTION:
12365           ar = &ref->u.ar;
12366           /* Get the start position of array section.  */
12367           gfc_get_section_index (ar, section_index, &offset);
12368           mark = AR_SECTION;
12369           break;
12370
12371         default:
12372           gcc_unreachable ();
12373         }
12374
12375       if (gfc_array_size (e, &size) == FAILURE)
12376         {
12377           gfc_error ("Nonconstant array section at %L in DATA statement",
12378                      &e->where);
12379           mpz_clear (offset);
12380           return FAILURE;
12381         }
12382     }
12383
12384   t = SUCCESS;
12385
12386   while (mpz_cmp_ui (size, 0) > 0)
12387     {
12388       if (next_data_value () == FAILURE)
12389         {
12390           gfc_error ("DATA statement at %L has more variables than values",
12391                      where);
12392           t = FAILURE;
12393           break;
12394         }
12395
12396       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
12397       if (t == FAILURE)
12398         break;
12399
12400       /* If we have more than one element left in the repeat count,
12401          and we have more than one element left in the target variable,
12402          then create a range assignment.  */
12403       /* FIXME: Only done for full arrays for now, since array sections
12404          seem tricky.  */
12405       if (mark == AR_FULL && ref && ref->next == NULL
12406           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
12407         {
12408           mpz_t range;
12409
12410           if (mpz_cmp (size, values.left) >= 0)
12411             {
12412               mpz_init_set (range, values.left);
12413               mpz_sub (size, size, values.left);
12414               mpz_set_ui (values.left, 0);
12415             }
12416           else
12417             {
12418               mpz_init_set (range, size);
12419               mpz_sub (values.left, values.left, size);
12420               mpz_set_ui (size, 0);
12421             }
12422
12423           t = gfc_assign_data_value_range (var->expr, values.vnode->expr,
12424                                            offset, range);
12425
12426           mpz_add (offset, offset, range);
12427           mpz_clear (range);
12428
12429           if (t == FAILURE)
12430             break;
12431         }
12432
12433       /* Assign initial value to symbol.  */
12434       else
12435         {
12436           mpz_sub_ui (values.left, values.left, 1);
12437           mpz_sub_ui (size, size, 1);
12438
12439           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
12440           if (t == FAILURE)
12441             break;
12442
12443           if (mark == AR_FULL)
12444             mpz_add_ui (offset, offset, 1);
12445
12446           /* Modify the array section indexes and recalculate the offset
12447              for next element.  */
12448           else if (mark == AR_SECTION)
12449             gfc_advance_section (section_index, ar, &offset);
12450         }
12451     }
12452
12453   if (mark == AR_SECTION)
12454     {
12455       for (i = 0; i < ar->dimen; i++)
12456         mpz_clear (section_index[i]);
12457     }
12458
12459   mpz_clear (size);
12460   mpz_clear (offset);
12461
12462   return t;
12463 }
12464
12465
12466 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
12467
12468 /* Iterate over a list of elements in a DATA statement.  */
12469
12470 static gfc_try
12471 traverse_data_list (gfc_data_variable *var, locus *where)
12472 {
12473   mpz_t trip;
12474   iterator_stack frame;
12475   gfc_expr *e, *start, *end, *step;
12476   gfc_try retval = SUCCESS;
12477
12478   mpz_init (frame.value);
12479   mpz_init (trip);
12480
12481   start = gfc_copy_expr (var->iter.start);
12482   end = gfc_copy_expr (var->iter.end);
12483   step = gfc_copy_expr (var->iter.step);
12484
12485   if (gfc_simplify_expr (start, 1) == FAILURE
12486       || start->expr_type != EXPR_CONSTANT)
12487     {
12488       gfc_error ("start of implied-do loop at %L could not be "
12489                  "simplified to a constant value", &start->where);
12490       retval = FAILURE;
12491       goto cleanup;
12492     }
12493   if (gfc_simplify_expr (end, 1) == FAILURE
12494       || end->expr_type != EXPR_CONSTANT)
12495     {
12496       gfc_error ("end of implied-do loop at %L could not be "
12497                  "simplified to a constant value", &start->where);
12498       retval = FAILURE;
12499       goto cleanup;
12500     }
12501   if (gfc_simplify_expr (step, 1) == FAILURE
12502       || step->expr_type != EXPR_CONSTANT)
12503     {
12504       gfc_error ("step of implied-do loop at %L could not be "
12505                  "simplified to a constant value", &start->where);
12506       retval = FAILURE;
12507       goto cleanup;
12508     }
12509
12510   mpz_set (trip, end->value.integer);
12511   mpz_sub (trip, trip, start->value.integer);
12512   mpz_add (trip, trip, step->value.integer);
12513
12514   mpz_div (trip, trip, step->value.integer);
12515
12516   mpz_set (frame.value, start->value.integer);
12517
12518   frame.prev = iter_stack;
12519   frame.variable = var->iter.var->symtree;
12520   iter_stack = &frame;
12521
12522   while (mpz_cmp_ui (trip, 0) > 0)
12523     {
12524       if (traverse_data_var (var->list, where) == FAILURE)
12525         {
12526           retval = FAILURE;
12527           goto cleanup;
12528         }
12529
12530       e = gfc_copy_expr (var->expr);
12531       if (gfc_simplify_expr (e, 1) == FAILURE)
12532         {
12533           gfc_free_expr (e);
12534           retval = FAILURE;
12535           goto cleanup;
12536         }
12537
12538       mpz_add (frame.value, frame.value, step->value.integer);
12539
12540       mpz_sub_ui (trip, trip, 1);
12541     }
12542
12543 cleanup:
12544   mpz_clear (frame.value);
12545   mpz_clear (trip);
12546
12547   gfc_free_expr (start);
12548   gfc_free_expr (end);
12549   gfc_free_expr (step);
12550
12551   iter_stack = frame.prev;
12552   return retval;
12553 }
12554
12555
12556 /* Type resolve variables in the variable list of a DATA statement.  */
12557
12558 static gfc_try
12559 traverse_data_var (gfc_data_variable *var, locus *where)
12560 {
12561   gfc_try t;
12562
12563   for (; var; var = var->next)
12564     {
12565       if (var->expr == NULL)
12566         t = traverse_data_list (var, where);
12567       else
12568         t = check_data_variable (var, where);
12569
12570       if (t == FAILURE)
12571         return FAILURE;
12572     }
12573
12574   return SUCCESS;
12575 }
12576
12577
12578 /* Resolve the expressions and iterators associated with a data statement.
12579    This is separate from the assignment checking because data lists should
12580    only be resolved once.  */
12581
12582 static gfc_try
12583 resolve_data_variables (gfc_data_variable *d)
12584 {
12585   for (; d; d = d->next)
12586     {
12587       if (d->list == NULL)
12588         {
12589           if (gfc_resolve_expr (d->expr) == FAILURE)
12590             return FAILURE;
12591         }
12592       else
12593         {
12594           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
12595             return FAILURE;
12596
12597           if (resolve_data_variables (d->list) == FAILURE)
12598             return FAILURE;
12599         }
12600     }
12601
12602   return SUCCESS;
12603 }
12604
12605
12606 /* Resolve a single DATA statement.  We implement this by storing a pointer to
12607    the value list into static variables, and then recursively traversing the
12608    variables list, expanding iterators and such.  */
12609
12610 static void
12611 resolve_data (gfc_data *d)
12612 {
12613
12614   if (resolve_data_variables (d->var) == FAILURE)
12615     return;
12616
12617   values.vnode = d->value;
12618   if (d->value == NULL)
12619     mpz_set_ui (values.left, 0);
12620   else
12621     mpz_set (values.left, d->value->repeat);
12622
12623   if (traverse_data_var (d->var, &d->where) == FAILURE)
12624     return;
12625
12626   /* At this point, we better not have any values left.  */
12627
12628   if (next_data_value () == SUCCESS)
12629     gfc_error ("DATA statement at %L has more values than variables",
12630                &d->where);
12631 }
12632
12633
12634 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
12635    accessed by host or use association, is a dummy argument to a pure function,
12636    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
12637    is storage associated with any such variable, shall not be used in the
12638    following contexts: (clients of this function).  */
12639
12640 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
12641    procedure.  Returns zero if assignment is OK, nonzero if there is a
12642    problem.  */
12643 int
12644 gfc_impure_variable (gfc_symbol *sym)
12645 {
12646   gfc_symbol *proc;
12647   gfc_namespace *ns;
12648
12649   if (sym->attr.use_assoc || sym->attr.in_common)
12650     return 1;
12651
12652   /* Check if the symbol's ns is inside the pure procedure.  */
12653   for (ns = gfc_current_ns; ns; ns = ns->parent)
12654     {
12655       if (ns == sym->ns)
12656         break;
12657       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
12658         return 1;
12659     }
12660
12661   proc = sym->ns->proc_name;
12662   if (sym->attr.dummy && gfc_pure (proc)
12663         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
12664                 ||
12665              proc->attr.function))
12666     return 1;
12667
12668   /* TODO: Sort out what can be storage associated, if anything, and include
12669      it here.  In principle equivalences should be scanned but it does not
12670      seem to be possible to storage associate an impure variable this way.  */
12671   return 0;
12672 }
12673
12674
12675 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
12676    current namespace is inside a pure procedure.  */
12677
12678 int
12679 gfc_pure (gfc_symbol *sym)
12680 {
12681   symbol_attribute attr;
12682   gfc_namespace *ns;
12683
12684   if (sym == NULL)
12685     {
12686       /* Check if the current namespace or one of its parents
12687         belongs to a pure procedure.  */
12688       for (ns = gfc_current_ns; ns; ns = ns->parent)
12689         {
12690           sym = ns->proc_name;
12691           if (sym == NULL)
12692             return 0;
12693           attr = sym->attr;
12694           if (attr.flavor == FL_PROCEDURE && attr.pure)
12695             return 1;
12696         }
12697       return 0;
12698     }
12699
12700   attr = sym->attr;
12701
12702   return attr.flavor == FL_PROCEDURE && attr.pure;
12703 }
12704
12705
12706 /* Test whether the current procedure is elemental or not.  */
12707
12708 int
12709 gfc_elemental (gfc_symbol *sym)
12710 {
12711   symbol_attribute attr;
12712
12713   if (sym == NULL)
12714     sym = gfc_current_ns->proc_name;
12715   if (sym == NULL)
12716     return 0;
12717   attr = sym->attr;
12718
12719   return attr.flavor == FL_PROCEDURE && attr.elemental;
12720 }
12721
12722
12723 /* Warn about unused labels.  */
12724
12725 static void
12726 warn_unused_fortran_label (gfc_st_label *label)
12727 {
12728   if (label == NULL)
12729     return;
12730
12731   warn_unused_fortran_label (label->left);
12732
12733   if (label->defined == ST_LABEL_UNKNOWN)
12734     return;
12735
12736   switch (label->referenced)
12737     {
12738     case ST_LABEL_UNKNOWN:
12739       gfc_warning ("Label %d at %L defined but not used", label->value,
12740                    &label->where);
12741       break;
12742
12743     case ST_LABEL_BAD_TARGET:
12744       gfc_warning ("Label %d at %L defined but cannot be used",
12745                    label->value, &label->where);
12746       break;
12747
12748     default:
12749       break;
12750     }
12751
12752   warn_unused_fortran_label (label->right);
12753 }
12754
12755
12756 /* Returns the sequence type of a symbol or sequence.  */
12757
12758 static seq_type
12759 sequence_type (gfc_typespec ts)
12760 {
12761   seq_type result;
12762   gfc_component *c;
12763
12764   switch (ts.type)
12765   {
12766     case BT_DERIVED:
12767
12768       if (ts.u.derived->components == NULL)
12769         return SEQ_NONDEFAULT;
12770
12771       result = sequence_type (ts.u.derived->components->ts);
12772       for (c = ts.u.derived->components->next; c; c = c->next)
12773         if (sequence_type (c->ts) != result)
12774           return SEQ_MIXED;
12775
12776       return result;
12777
12778     case BT_CHARACTER:
12779       if (ts.kind != gfc_default_character_kind)
12780           return SEQ_NONDEFAULT;
12781
12782       return SEQ_CHARACTER;
12783
12784     case BT_INTEGER:
12785       if (ts.kind != gfc_default_integer_kind)
12786           return SEQ_NONDEFAULT;
12787
12788       return SEQ_NUMERIC;
12789
12790     case BT_REAL:
12791       if (!(ts.kind == gfc_default_real_kind
12792             || ts.kind == gfc_default_double_kind))
12793           return SEQ_NONDEFAULT;
12794
12795       return SEQ_NUMERIC;
12796
12797     case BT_COMPLEX:
12798       if (ts.kind != gfc_default_complex_kind)
12799           return SEQ_NONDEFAULT;
12800
12801       return SEQ_NUMERIC;
12802
12803     case BT_LOGICAL:
12804       if (ts.kind != gfc_default_logical_kind)
12805           return SEQ_NONDEFAULT;
12806
12807       return SEQ_NUMERIC;
12808
12809     default:
12810       return SEQ_NONDEFAULT;
12811   }
12812 }
12813
12814
12815 /* Resolve derived type EQUIVALENCE object.  */
12816
12817 static gfc_try
12818 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
12819 {
12820   gfc_component *c = derived->components;
12821
12822   if (!derived)
12823     return SUCCESS;
12824
12825   /* Shall not be an object of nonsequence derived type.  */
12826   if (!derived->attr.sequence)
12827     {
12828       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
12829                  "attribute to be an EQUIVALENCE object", sym->name,
12830                  &e->where);
12831       return FAILURE;
12832     }
12833
12834   /* Shall not have allocatable components.  */
12835   if (derived->attr.alloc_comp)
12836     {
12837       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
12838                  "components to be an EQUIVALENCE object",sym->name,
12839                  &e->where);
12840       return FAILURE;
12841     }
12842
12843   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
12844     {
12845       gfc_error ("Derived type variable '%s' at %L with default "
12846                  "initialization cannot be in EQUIVALENCE with a variable "
12847                  "in COMMON", sym->name, &e->where);
12848       return FAILURE;
12849     }
12850
12851   for (; c ; c = c->next)
12852     {
12853       if (c->ts.type == BT_DERIVED
12854           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
12855         return FAILURE;
12856
12857       /* Shall not be an object of sequence derived type containing a pointer
12858          in the structure.  */
12859       if (c->attr.pointer)
12860         {
12861           gfc_error ("Derived type variable '%s' at %L with pointer "
12862                      "component(s) cannot be an EQUIVALENCE object",
12863                      sym->name, &e->where);
12864           return FAILURE;
12865         }
12866     }
12867   return SUCCESS;
12868 }
12869
12870
12871 /* Resolve equivalence object. 
12872    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
12873    an allocatable array, an object of nonsequence derived type, an object of
12874    sequence derived type containing a pointer at any level of component
12875    selection, an automatic object, a function name, an entry name, a result
12876    name, a named constant, a structure component, or a subobject of any of
12877    the preceding objects.  A substring shall not have length zero.  A
12878    derived type shall not have components with default initialization nor
12879    shall two objects of an equivalence group be initialized.
12880    Either all or none of the objects shall have an protected attribute.
12881    The simple constraints are done in symbol.c(check_conflict) and the rest
12882    are implemented here.  */
12883
12884 static void
12885 resolve_equivalence (gfc_equiv *eq)
12886 {
12887   gfc_symbol *sym;
12888   gfc_symbol *first_sym;
12889   gfc_expr *e;
12890   gfc_ref *r;
12891   locus *last_where = NULL;
12892   seq_type eq_type, last_eq_type;
12893   gfc_typespec *last_ts;
12894   int object, cnt_protected;
12895   const char *msg;
12896
12897   last_ts = &eq->expr->symtree->n.sym->ts;
12898
12899   first_sym = eq->expr->symtree->n.sym;
12900
12901   cnt_protected = 0;
12902
12903   for (object = 1; eq; eq = eq->eq, object++)
12904     {
12905       e = eq->expr;
12906
12907       e->ts = e->symtree->n.sym->ts;
12908       /* match_varspec might not know yet if it is seeing
12909          array reference or substring reference, as it doesn't
12910          know the types.  */
12911       if (e->ref && e->ref->type == REF_ARRAY)
12912         {
12913           gfc_ref *ref = e->ref;
12914           sym = e->symtree->n.sym;
12915
12916           if (sym->attr.dimension)
12917             {
12918               ref->u.ar.as = sym->as;
12919               ref = ref->next;
12920             }
12921
12922           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
12923           if (e->ts.type == BT_CHARACTER
12924               && ref
12925               && ref->type == REF_ARRAY
12926               && ref->u.ar.dimen == 1
12927               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
12928               && ref->u.ar.stride[0] == NULL)
12929             {
12930               gfc_expr *start = ref->u.ar.start[0];
12931               gfc_expr *end = ref->u.ar.end[0];
12932               void *mem = NULL;
12933
12934               /* Optimize away the (:) reference.  */
12935               if (start == NULL && end == NULL)
12936                 {
12937                   if (e->ref == ref)
12938                     e->ref = ref->next;
12939                   else
12940                     e->ref->next = ref->next;
12941                   mem = ref;
12942                 }
12943               else
12944                 {
12945                   ref->type = REF_SUBSTRING;
12946                   if (start == NULL)
12947                     start = gfc_get_int_expr (gfc_default_integer_kind,
12948                                               NULL, 1);
12949                   ref->u.ss.start = start;
12950                   if (end == NULL && e->ts.u.cl)
12951                     end = gfc_copy_expr (e->ts.u.cl->length);
12952                   ref->u.ss.end = end;
12953                   ref->u.ss.length = e->ts.u.cl;
12954                   e->ts.u.cl = NULL;
12955                 }
12956               ref = ref->next;
12957               gfc_free (mem);
12958             }
12959
12960           /* Any further ref is an error.  */
12961           if (ref)
12962             {
12963               gcc_assert (ref->type == REF_ARRAY);
12964               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
12965                          &ref->u.ar.where);
12966               continue;
12967             }
12968         }
12969
12970       if (gfc_resolve_expr (e) == FAILURE)
12971         continue;
12972
12973       sym = e->symtree->n.sym;
12974
12975       if (sym->attr.is_protected)
12976         cnt_protected++;
12977       if (cnt_protected > 0 && cnt_protected != object)
12978         {
12979               gfc_error ("Either all or none of the objects in the "
12980                          "EQUIVALENCE set at %L shall have the "
12981                          "PROTECTED attribute",
12982                          &e->where);
12983               break;
12984         }
12985
12986       /* Shall not equivalence common block variables in a PURE procedure.  */
12987       if (sym->ns->proc_name
12988           && sym->ns->proc_name->attr.pure
12989           && sym->attr.in_common)
12990         {
12991           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
12992                      "object in the pure procedure '%s'",
12993                      sym->name, &e->where, sym->ns->proc_name->name);
12994           break;
12995         }
12996
12997       /* Shall not be a named constant.  */
12998       if (e->expr_type == EXPR_CONSTANT)
12999         {
13000           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
13001                      "object", sym->name, &e->where);
13002           continue;
13003         }
13004
13005       if (e->ts.type == BT_DERIVED
13006           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
13007         continue;
13008
13009       /* Check that the types correspond correctly:
13010          Note 5.28:
13011          A numeric sequence structure may be equivalenced to another sequence
13012          structure, an object of default integer type, default real type, double
13013          precision real type, default logical type such that components of the
13014          structure ultimately only become associated to objects of the same
13015          kind. A character sequence structure may be equivalenced to an object
13016          of default character kind or another character sequence structure.
13017          Other objects may be equivalenced only to objects of the same type and
13018          kind parameters.  */
13019
13020       /* Identical types are unconditionally OK.  */
13021       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
13022         goto identical_types;
13023
13024       last_eq_type = sequence_type (*last_ts);
13025       eq_type = sequence_type (sym->ts);
13026
13027       /* Since the pair of objects is not of the same type, mixed or
13028          non-default sequences can be rejected.  */
13029
13030       msg = "Sequence %s with mixed components in EQUIVALENCE "
13031             "statement at %L with different type objects";
13032       if ((object ==2
13033            && last_eq_type == SEQ_MIXED
13034            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
13035               == FAILURE)
13036           || (eq_type == SEQ_MIXED
13037               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13038                                  &e->where) == FAILURE))
13039         continue;
13040
13041       msg = "Non-default type object or sequence %s in EQUIVALENCE "
13042             "statement at %L with objects of different type";
13043       if ((object ==2
13044            && last_eq_type == SEQ_NONDEFAULT
13045            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
13046                               last_where) == FAILURE)
13047           || (eq_type == SEQ_NONDEFAULT
13048               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13049                                  &e->where) == FAILURE))
13050         continue;
13051
13052       msg ="Non-CHARACTER object '%s' in default CHARACTER "
13053            "EQUIVALENCE statement at %L";
13054       if (last_eq_type == SEQ_CHARACTER
13055           && eq_type != SEQ_CHARACTER
13056           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13057                              &e->where) == FAILURE)
13058                 continue;
13059
13060       msg ="Non-NUMERIC object '%s' in default NUMERIC "
13061            "EQUIVALENCE statement at %L";
13062       if (last_eq_type == SEQ_NUMERIC
13063           && eq_type != SEQ_NUMERIC
13064           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13065                              &e->where) == FAILURE)
13066                 continue;
13067
13068   identical_types:
13069       last_ts =&sym->ts;
13070       last_where = &e->where;
13071
13072       if (!e->ref)
13073         continue;
13074
13075       /* Shall not be an automatic array.  */
13076       if (e->ref->type == REF_ARRAY
13077           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
13078         {
13079           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
13080                      "an EQUIVALENCE object", sym->name, &e->where);
13081           continue;
13082         }
13083
13084       r = e->ref;
13085       while (r)
13086         {
13087           /* Shall not be a structure component.  */
13088           if (r->type == REF_COMPONENT)
13089             {
13090               gfc_error ("Structure component '%s' at %L cannot be an "
13091                          "EQUIVALENCE object",
13092                          r->u.c.component->name, &e->where);
13093               break;
13094             }
13095
13096           /* A substring shall not have length zero.  */
13097           if (r->type == REF_SUBSTRING)
13098             {
13099               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
13100                 {
13101                   gfc_error ("Substring at %L has length zero",
13102                              &r->u.ss.start->where);
13103                   break;
13104                 }
13105             }
13106           r = r->next;
13107         }
13108     }
13109 }
13110
13111
13112 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
13113
13114 static void
13115 resolve_fntype (gfc_namespace *ns)
13116 {
13117   gfc_entry_list *el;
13118   gfc_symbol *sym;
13119
13120   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
13121     return;
13122
13123   /* If there are any entries, ns->proc_name is the entry master
13124      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
13125   if (ns->entries)
13126     sym = ns->entries->sym;
13127   else
13128     sym = ns->proc_name;
13129   if (sym->result == sym
13130       && sym->ts.type == BT_UNKNOWN
13131       && gfc_set_default_type (sym, 0, NULL) == FAILURE
13132       && !sym->attr.untyped)
13133     {
13134       gfc_error ("Function '%s' at %L has no IMPLICIT type",
13135                  sym->name, &sym->declared_at);
13136       sym->attr.untyped = 1;
13137     }
13138
13139   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
13140       && !sym->attr.contained
13141       && !gfc_check_access (sym->ts.u.derived->attr.access,
13142                             sym->ts.u.derived->ns->default_access)
13143       && gfc_check_access (sym->attr.access, sym->ns->default_access))
13144     {
13145       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
13146                       "%L of PRIVATE type '%s'", sym->name,
13147                       &sym->declared_at, sym->ts.u.derived->name);
13148     }
13149
13150     if (ns->entries)
13151     for (el = ns->entries->next; el; el = el->next)
13152       {
13153         if (el->sym->result == el->sym
13154             && el->sym->ts.type == BT_UNKNOWN
13155             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
13156             && !el->sym->attr.untyped)
13157           {
13158             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
13159                        el->sym->name, &el->sym->declared_at);
13160             el->sym->attr.untyped = 1;
13161           }
13162       }
13163 }
13164
13165
13166 /* 12.3.2.1.1 Defined operators.  */
13167
13168 static gfc_try
13169 check_uop_procedure (gfc_symbol *sym, locus where)
13170 {
13171   gfc_formal_arglist *formal;
13172
13173   if (!sym->attr.function)
13174     {
13175       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
13176                  sym->name, &where);
13177       return FAILURE;
13178     }
13179
13180   if (sym->ts.type == BT_CHARACTER
13181       && !(sym->ts.u.cl && sym->ts.u.cl->length)
13182       && !(sym->result && sym->result->ts.u.cl
13183            && sym->result->ts.u.cl->length))
13184     {
13185       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
13186                  "character length", sym->name, &where);
13187       return FAILURE;
13188     }
13189
13190   formal = sym->formal;
13191   if (!formal || !formal->sym)
13192     {
13193       gfc_error ("User operator procedure '%s' at %L must have at least "
13194                  "one argument", sym->name, &where);
13195       return FAILURE;
13196     }
13197
13198   if (formal->sym->attr.intent != INTENT_IN)
13199     {
13200       gfc_error ("First argument of operator interface at %L must be "
13201                  "INTENT(IN)", &where);
13202       return FAILURE;
13203     }
13204
13205   if (formal->sym->attr.optional)
13206     {
13207       gfc_error ("First argument of operator interface at %L cannot be "
13208                  "optional", &where);
13209       return FAILURE;
13210     }
13211
13212   formal = formal->next;
13213   if (!formal || !formal->sym)
13214     return SUCCESS;
13215
13216   if (formal->sym->attr.intent != INTENT_IN)
13217     {
13218       gfc_error ("Second argument of operator interface at %L must be "
13219                  "INTENT(IN)", &where);
13220       return FAILURE;
13221     }
13222
13223   if (formal->sym->attr.optional)
13224     {
13225       gfc_error ("Second argument of operator interface at %L cannot be "
13226                  "optional", &where);
13227       return FAILURE;
13228     }
13229
13230   if (formal->next)
13231     {
13232       gfc_error ("Operator interface at %L must have, at most, two "
13233                  "arguments", &where);
13234       return FAILURE;
13235     }
13236
13237   return SUCCESS;
13238 }
13239
13240 static void
13241 gfc_resolve_uops (gfc_symtree *symtree)
13242 {
13243   gfc_interface *itr;
13244
13245   if (symtree == NULL)
13246     return;
13247
13248   gfc_resolve_uops (symtree->left);
13249   gfc_resolve_uops (symtree->right);
13250
13251   for (itr = symtree->n.uop->op; itr; itr = itr->next)
13252     check_uop_procedure (itr->sym, itr->sym->declared_at);
13253 }
13254
13255
13256 /* Examine all of the expressions associated with a program unit,
13257    assign types to all intermediate expressions, make sure that all
13258    assignments are to compatible types and figure out which names
13259    refer to which functions or subroutines.  It doesn't check code
13260    block, which is handled by resolve_code.  */
13261
13262 static void
13263 resolve_types (gfc_namespace *ns)
13264 {
13265   gfc_namespace *n;
13266   gfc_charlen *cl;
13267   gfc_data *d;
13268   gfc_equiv *eq;
13269   gfc_namespace* old_ns = gfc_current_ns;
13270
13271   /* Check that all IMPLICIT types are ok.  */
13272   if (!ns->seen_implicit_none)
13273     {
13274       unsigned letter;
13275       for (letter = 0; letter != GFC_LETTERS; ++letter)
13276         if (ns->set_flag[letter]
13277             && resolve_typespec_used (&ns->default_type[letter],
13278                                       &ns->implicit_loc[letter],
13279                                       NULL) == FAILURE)
13280           return;
13281     }
13282
13283   gfc_current_ns = ns;
13284
13285   resolve_entries (ns);
13286
13287   resolve_common_vars (ns->blank_common.head, false);
13288   resolve_common_blocks (ns->common_root);
13289
13290   resolve_contained_functions (ns);
13291
13292   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
13293
13294   for (cl = ns->cl_list; cl; cl = cl->next)
13295     resolve_charlen (cl);
13296
13297   gfc_traverse_ns (ns, resolve_symbol);
13298
13299   resolve_fntype (ns);
13300
13301   for (n = ns->contained; n; n = n->sibling)
13302     {
13303       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
13304         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
13305                    "also be PURE", n->proc_name->name,
13306                    &n->proc_name->declared_at);
13307
13308       resolve_types (n);
13309     }
13310
13311   forall_flag = 0;
13312   gfc_check_interfaces (ns);
13313
13314   gfc_traverse_ns (ns, resolve_values);
13315
13316   if (ns->save_all)
13317     gfc_save_all (ns);
13318
13319   iter_stack = NULL;
13320   for (d = ns->data; d; d = d->next)
13321     resolve_data (d);
13322
13323   iter_stack = NULL;
13324   gfc_traverse_ns (ns, gfc_formalize_init_value);
13325
13326   gfc_traverse_ns (ns, gfc_verify_binding_labels);
13327
13328   if (ns->common_root != NULL)
13329     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
13330
13331   for (eq = ns->equiv; eq; eq = eq->next)
13332     resolve_equivalence (eq);
13333
13334   /* Warn about unused labels.  */
13335   if (warn_unused_label)
13336     warn_unused_fortran_label (ns->st_labels);
13337
13338   gfc_resolve_uops (ns->uop_root);
13339
13340   gfc_current_ns = old_ns;
13341 }
13342
13343
13344 /* Call resolve_code recursively.  */
13345
13346 static void
13347 resolve_codes (gfc_namespace *ns)
13348 {
13349   gfc_namespace *n;
13350   bitmap_obstack old_obstack;
13351
13352   if (ns->resolved == 1)
13353     return;
13354
13355   for (n = ns->contained; n; n = n->sibling)
13356     resolve_codes (n);
13357
13358   gfc_current_ns = ns;
13359
13360   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
13361   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
13362     cs_base = NULL;
13363
13364   /* Set to an out of range value.  */
13365   current_entry_id = -1;
13366
13367   old_obstack = labels_obstack;
13368   bitmap_obstack_initialize (&labels_obstack);
13369
13370   resolve_code (ns->code, ns);
13371
13372   bitmap_obstack_release (&labels_obstack);
13373   labels_obstack = old_obstack;
13374 }
13375
13376
13377 /* This function is called after a complete program unit has been compiled.
13378    Its purpose is to examine all of the expressions associated with a program
13379    unit, assign types to all intermediate expressions, make sure that all
13380    assignments are to compatible types and figure out which names refer to
13381    which functions or subroutines.  */
13382
13383 void
13384 gfc_resolve (gfc_namespace *ns)
13385 {
13386   gfc_namespace *old_ns;
13387   code_stack *old_cs_base;
13388
13389   if (ns->resolved)
13390     return;
13391
13392   ns->resolved = -1;
13393   old_ns = gfc_current_ns;
13394   old_cs_base = cs_base;
13395
13396   resolve_types (ns);
13397   resolve_codes (ns);
13398
13399   gfc_current_ns = old_ns;
13400   cs_base = old_cs_base;
13401   ns->resolved = 1;
13402
13403   gfc_run_passes (ns);
13404 }