OSDN Git Service

2010-06-22 Janus Weil <janus@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010
3    Free Software Foundation, Inc.
4    Contributed by Andy Vaught
5
6 This file is part of GCC.
7
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 3, or (at your option) any later
11 version.
12
13 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
14 WARRANTY; without even the implied warranty of MERCHANTABILITY or
15 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
16 for more details.
17
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING3.  If not see
20 <http://www.gnu.org/licenses/>.  */
21
22 #include "config.h"
23 #include "system.h"
24 #include "flags.h"
25 #include "gfortran.h"
26 #include "obstack.h"
27 #include "bitmap.h"
28 #include "arith.h"  /* For gfc_compare_expr().  */
29 #include "dependency.h"
30 #include "data.h"
31 #include "target-memory.h" /* for gfc_simplify_transfer */
32 #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 /* Resolve types of formal argument lists.  These have to be done early so that
130    the formal argument lists of module procedures can be copied to the
131    containing module before the individual procedures are resolved
132    individually.  We also resolve argument lists of procedures in interface
133    blocks because they are self-contained scoping units.
134
135    Since a dummy argument cannot be a non-dummy procedure, the only
136    resort left for untyped names are the IMPLICIT types.  */
137
138 static void
139 resolve_formal_arglist (gfc_symbol *proc)
140 {
141   gfc_formal_arglist *f;
142   gfc_symbol *sym;
143   int i;
144
145   if (proc->result != NULL)
146     sym = proc->result;
147   else
148     sym = proc;
149
150   if (gfc_elemental (proc)
151       || sym->attr.pointer || sym->attr.allocatable
152       || (sym->as && sym->as->rank > 0))
153     {
154       proc->attr.always_explicit = 1;
155       sym->attr.always_explicit = 1;
156     }
157
158   formal_arg_flag = 1;
159
160   for (f = proc->formal; f; f = f->next)
161     {
162       sym = f->sym;
163
164       if (sym == NULL)
165         {
166           /* Alternate return placeholder.  */
167           if (gfc_elemental (proc))
168             gfc_error ("Alternate return specifier in elemental subroutine "
169                        "'%s' at %L is not allowed", proc->name,
170                        &proc->declared_at);
171           if (proc->attr.function)
172             gfc_error ("Alternate return specifier in function "
173                        "'%s' at %L is not allowed", proc->name,
174                        &proc->declared_at);
175           continue;
176         }
177
178       if (sym->attr.if_source != IFSRC_UNKNOWN)
179         resolve_formal_arglist (sym);
180
181       if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
182         {
183           if (gfc_pure (proc) && !gfc_pure (sym))
184             {
185               gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
186                          "also be PURE", sym->name, &sym->declared_at);
187               continue;
188             }
189
190           if (gfc_elemental (proc))
191             {
192               gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
193                          "procedure", &sym->declared_at);
194               continue;
195             }
196
197           if (sym->attr.function
198                 && sym->ts.type == BT_UNKNOWN
199                 && sym->attr.intrinsic)
200             {
201               gfc_intrinsic_sym *isym;
202               isym = gfc_find_function (sym->name);
203               if (isym == NULL || !isym->specific)
204                 {
205                   gfc_error ("Unable to find a specific INTRINSIC procedure "
206                              "for the reference '%s' at %L", sym->name,
207                              &sym->declared_at);
208                 }
209               sym->ts = isym->ts;
210             }
211
212           continue;
213         }
214
215       if (sym->ts.type == BT_UNKNOWN)
216         {
217           if (!sym->attr.function || sym->result == sym)
218             gfc_set_default_type (sym, 1, sym->ns);
219         }
220
221       gfc_resolve_array_spec (sym->as, 0);
222
223       /* We can't tell if an array with dimension (:) is assumed or deferred
224          shape until we know if it has the pointer or allocatable attributes.
225       */
226       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
227           && !(sym->attr.pointer || sym->attr.allocatable))
228         {
229           sym->as->type = AS_ASSUMED_SHAPE;
230           for (i = 0; i < sym->as->rank; i++)
231             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
232                                                   NULL, 1);
233         }
234
235       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
236           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
237           || sym->attr.optional)
238         {
239           proc->attr.always_explicit = 1;
240           if (proc->result)
241             proc->result->attr.always_explicit = 1;
242         }
243
244       /* If the flavor is unknown at this point, it has to be a variable.
245          A procedure specification would have already set the type.  */
246
247       if (sym->attr.flavor == FL_UNKNOWN)
248         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
249
250       if (gfc_pure (proc) && !sym->attr.pointer
251           && sym->attr.flavor != FL_PROCEDURE)
252         {
253           if (proc->attr.function && sym->attr.intent != INTENT_IN)
254             gfc_error ("Argument '%s' of pure function '%s' at %L must be "
255                        "INTENT(IN)", sym->name, proc->name,
256                        &sym->declared_at);
257
258           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
259             gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
260                        "have its INTENT specified", sym->name, proc->name,
261                        &sym->declared_at);
262         }
263
264       if (gfc_elemental (proc))
265         {
266           /* F2008, C1289.  */
267           if (sym->attr.codimension)
268             {
269               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
270                          "procedure", sym->name, &sym->declared_at);
271               continue;
272             }
273
274           if (sym->as != NULL)
275             {
276               gfc_error ("Argument '%s' of elemental procedure at %L must "
277                          "be scalar", sym->name, &sym->declared_at);
278               continue;
279             }
280
281           if (sym->attr.pointer)
282             {
283               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
284                          "have the POINTER attribute", sym->name,
285                          &sym->declared_at);
286               continue;
287             }
288
289           if (sym->attr.flavor == FL_PROCEDURE)
290             {
291               gfc_error ("Dummy procedure '%s' not allowed in elemental "
292                          "procedure '%s' at %L", sym->name, proc->name,
293                          &sym->declared_at);
294               continue;
295             }
296         }
297
298       /* Each dummy shall be specified to be scalar.  */
299       if (proc->attr.proc == PROC_ST_FUNCTION)
300         {
301           if (sym->as != NULL)
302             {
303               gfc_error ("Argument '%s' of statement function at %L must "
304                          "be scalar", sym->name, &sym->declared_at);
305               continue;
306             }
307
308           if (sym->ts.type == BT_CHARACTER)
309             {
310               gfc_charlen *cl = sym->ts.u.cl;
311               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
312                 {
313                   gfc_error ("Character-valued argument '%s' of statement "
314                              "function at %L must have constant length",
315                              sym->name, &sym->declared_at);
316                   continue;
317                 }
318             }
319         }
320     }
321   formal_arg_flag = 0;
322 }
323
324
325 /* Work function called when searching for symbols that have argument lists
326    associated with them.  */
327
328 static void
329 find_arglists (gfc_symbol *sym)
330 {
331   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
332     return;
333
334   resolve_formal_arglist (sym);
335 }
336
337
338 /* Given a namespace, resolve all formal argument lists within the namespace.
339  */
340
341 static void
342 resolve_formal_arglists (gfc_namespace *ns)
343 {
344   if (ns == NULL)
345     return;
346
347   gfc_traverse_ns (ns, find_arglists);
348 }
349
350
351 static void
352 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
353 {
354   gfc_try t;
355
356   /* If this namespace is not a function or an entry master function,
357      ignore it.  */
358   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
359       || sym->attr.entry_master)
360     return;
361
362   /* Try to find out of what the return type is.  */
363   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
364     {
365       t = gfc_set_default_type (sym->result, 0, ns);
366
367       if (t == FAILURE && !sym->result->attr.untyped)
368         {
369           if (sym->result == sym)
370             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
371                        sym->name, &sym->declared_at);
372           else if (!sym->result->attr.proc_pointer)
373             gfc_error ("Result '%s' of contained function '%s' at %L has "
374                        "no IMPLICIT type", sym->result->name, sym->name,
375                        &sym->result->declared_at);
376           sym->result->attr.untyped = 1;
377         }
378     }
379
380   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
381      type, lists the only ways a character length value of * can be used:
382      dummy arguments of procedures, named constants, and function results
383      in external functions.  Internal function results and results of module
384      procedures are not on this list, ergo, not permitted.  */
385
386   if (sym->result->ts.type == BT_CHARACTER)
387     {
388       gfc_charlen *cl = sym->result->ts.u.cl;
389       if (!cl || !cl->length)
390         {
391           /* See if this is a module-procedure and adapt error message
392              accordingly.  */
393           bool module_proc;
394           gcc_assert (ns->parent && ns->parent->proc_name);
395           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
396
397           gfc_error ("Character-valued %s '%s' at %L must not be"
398                      " assumed length",
399                      module_proc ? _("module procedure")
400                                  : _("internal function"),
401                      sym->name, &sym->declared_at);
402         }
403     }
404 }
405
406
407 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
408    introduce duplicates.  */
409
410 static void
411 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
412 {
413   gfc_formal_arglist *f, *new_arglist;
414   gfc_symbol *new_sym;
415
416   for (; new_args != NULL; new_args = new_args->next)
417     {
418       new_sym = new_args->sym;
419       /* See if this arg is already in the formal argument list.  */
420       for (f = proc->formal; f; f = f->next)
421         {
422           if (new_sym == f->sym)
423             break;
424         }
425
426       if (f)
427         continue;
428
429       /* Add a new argument.  Argument order is not important.  */
430       new_arglist = gfc_get_formal_arglist ();
431       new_arglist->sym = new_sym;
432       new_arglist->next = proc->formal;
433       proc->formal  = new_arglist;
434     }
435 }
436
437
438 /* Flag the arguments that are not present in all entries.  */
439
440 static void
441 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
442 {
443   gfc_formal_arglist *f, *head;
444   head = new_args;
445
446   for (f = proc->formal; f; f = f->next)
447     {
448       if (f->sym == NULL)
449         continue;
450
451       for (new_args = head; new_args; new_args = new_args->next)
452         {
453           if (new_args->sym == f->sym)
454             break;
455         }
456
457       if (new_args)
458         continue;
459
460       f->sym->attr.not_always_present = 1;
461     }
462 }
463
464
465 /* Resolve alternate entry points.  If a symbol has multiple entry points we
466    create a new master symbol for the main routine, and turn the existing
467    symbol into an entry point.  */
468
469 static void
470 resolve_entries (gfc_namespace *ns)
471 {
472   gfc_namespace *old_ns;
473   gfc_code *c;
474   gfc_symbol *proc;
475   gfc_entry_list *el;
476   char name[GFC_MAX_SYMBOL_LEN + 1];
477   static int master_count = 0;
478
479   if (ns->proc_name == NULL)
480     return;
481
482   /* No need to do anything if this procedure doesn't have alternate entry
483      points.  */
484   if (!ns->entries)
485     return;
486
487   /* We may already have resolved alternate entry points.  */
488   if (ns->proc_name->attr.entry_master)
489     return;
490
491   /* If this isn't a procedure something has gone horribly wrong.  */
492   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
493
494   /* Remember the current namespace.  */
495   old_ns = gfc_current_ns;
496
497   gfc_current_ns = ns;
498
499   /* Add the main entry point to the list of entry points.  */
500   el = gfc_get_entry_list ();
501   el->sym = ns->proc_name;
502   el->id = 0;
503   el->next = ns->entries;
504   ns->entries = el;
505   ns->proc_name->attr.entry = 1;
506
507   /* If it is a module function, it needs to be in the right namespace
508      so that gfc_get_fake_result_decl can gather up the results. The
509      need for this arose in get_proc_name, where these beasts were
510      left in their own namespace, to keep prior references linked to
511      the entry declaration.*/
512   if (ns->proc_name->attr.function
513       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
514     el->sym->ns = ns;
515
516   /* Do the same for entries where the master is not a module
517      procedure.  These are retained in the module namespace because
518      of the module procedure declaration.  */
519   for (el = el->next; el; el = el->next)
520     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
521           && el->sym->attr.mod_proc)
522       el->sym->ns = ns;
523   el = ns->entries;
524
525   /* Add an entry statement for it.  */
526   c = gfc_get_code ();
527   c->op = EXEC_ENTRY;
528   c->ext.entry = el;
529   c->next = ns->code;
530   ns->code = c;
531
532   /* Create a new symbol for the master function.  */
533   /* Give the internal function a unique name (within this file).
534      Also include the function name so the user has some hope of figuring
535      out what is going on.  */
536   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
537             master_count++, ns->proc_name->name);
538   gfc_get_ha_symbol (name, &proc);
539   gcc_assert (proc != NULL);
540
541   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
542   if (ns->proc_name->attr.subroutine)
543     gfc_add_subroutine (&proc->attr, proc->name, NULL);
544   else
545     {
546       gfc_symbol *sym;
547       gfc_typespec *ts, *fts;
548       gfc_array_spec *as, *fas;
549       gfc_add_function (&proc->attr, proc->name, NULL);
550       proc->result = proc;
551       fas = ns->entries->sym->as;
552       fas = fas ? fas : ns->entries->sym->result->as;
553       fts = &ns->entries->sym->result->ts;
554       if (fts->type == BT_UNKNOWN)
555         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
556       for (el = ns->entries->next; el; el = el->next)
557         {
558           ts = &el->sym->result->ts;
559           as = el->sym->as;
560           as = as ? as : el->sym->result->as;
561           if (ts->type == BT_UNKNOWN)
562             ts = gfc_get_default_type (el->sym->result->name, NULL);
563
564           if (! gfc_compare_types (ts, fts)
565               || (el->sym->result->attr.dimension
566                   != ns->entries->sym->result->attr.dimension)
567               || (el->sym->result->attr.pointer
568                   != ns->entries->sym->result->attr.pointer))
569             break;
570           else if (as && fas && ns->entries->sym->result != el->sym->result
571                       && gfc_compare_array_spec (as, fas) == 0)
572             gfc_error ("Function %s at %L has entries with mismatched "
573                        "array specifications", ns->entries->sym->name,
574                        &ns->entries->sym->declared_at);
575           /* The characteristics need to match and thus both need to have
576              the same string length, i.e. both len=*, or both len=4.
577              Having both len=<variable> is also possible, but difficult to
578              check at compile time.  */
579           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
580                    && (((ts->u.cl->length && !fts->u.cl->length)
581                         ||(!ts->u.cl->length && fts->u.cl->length))
582                        || (ts->u.cl->length
583                            && ts->u.cl->length->expr_type
584                               != fts->u.cl->length->expr_type)
585                        || (ts->u.cl->length
586                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
587                            && mpz_cmp (ts->u.cl->length->value.integer,
588                                        fts->u.cl->length->value.integer) != 0)))
589             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
590                             "entries returning variables of different "
591                             "string lengths", ns->entries->sym->name,
592                             &ns->entries->sym->declared_at);
593         }
594
595       if (el == NULL)
596         {
597           sym = ns->entries->sym->result;
598           /* All result types the same.  */
599           proc->ts = *fts;
600           if (sym->attr.dimension)
601             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
602           if (sym->attr.pointer)
603             gfc_add_pointer (&proc->attr, NULL);
604         }
605       else
606         {
607           /* Otherwise the result will be passed through a union by
608              reference.  */
609           proc->attr.mixed_entry_master = 1;
610           for (el = ns->entries; el; el = el->next)
611             {
612               sym = el->sym->result;
613               if (sym->attr.dimension)
614                 {
615                   if (el == ns->entries)
616                     gfc_error ("FUNCTION result %s can't be an array in "
617                                "FUNCTION %s at %L", sym->name,
618                                ns->entries->sym->name, &sym->declared_at);
619                   else
620                     gfc_error ("ENTRY result %s can't be an array in "
621                                "FUNCTION %s at %L", sym->name,
622                                ns->entries->sym->name, &sym->declared_at);
623                 }
624               else if (sym->attr.pointer)
625                 {
626                   if (el == ns->entries)
627                     gfc_error ("FUNCTION result %s can't be a POINTER in "
628                                "FUNCTION %s at %L", sym->name,
629                                ns->entries->sym->name, &sym->declared_at);
630                   else
631                     gfc_error ("ENTRY result %s can't be a POINTER in "
632                                "FUNCTION %s at %L", sym->name,
633                                ns->entries->sym->name, &sym->declared_at);
634                 }
635               else
636                 {
637                   ts = &sym->ts;
638                   if (ts->type == BT_UNKNOWN)
639                     ts = gfc_get_default_type (sym->name, NULL);
640                   switch (ts->type)
641                     {
642                     case BT_INTEGER:
643                       if (ts->kind == gfc_default_integer_kind)
644                         sym = NULL;
645                       break;
646                     case BT_REAL:
647                       if (ts->kind == gfc_default_real_kind
648                           || ts->kind == gfc_default_double_kind)
649                         sym = NULL;
650                       break;
651                     case BT_COMPLEX:
652                       if (ts->kind == gfc_default_complex_kind)
653                         sym = NULL;
654                       break;
655                     case BT_LOGICAL:
656                       if (ts->kind == gfc_default_logical_kind)
657                         sym = NULL;
658                       break;
659                     case BT_UNKNOWN:
660                       /* We will issue error elsewhere.  */
661                       sym = NULL;
662                       break;
663                     default:
664                       break;
665                     }
666                   if (sym)
667                     {
668                       if (el == ns->entries)
669                         gfc_error ("FUNCTION result %s can't be of type %s "
670                                    "in FUNCTION %s at %L", sym->name,
671                                    gfc_typename (ts), ns->entries->sym->name,
672                                    &sym->declared_at);
673                       else
674                         gfc_error ("ENTRY result %s can't be of type %s "
675                                    "in FUNCTION %s at %L", sym->name,
676                                    gfc_typename (ts), ns->entries->sym->name,
677                                    &sym->declared_at);
678                     }
679                 }
680             }
681         }
682     }
683   proc->attr.access = ACCESS_PRIVATE;
684   proc->attr.entry_master = 1;
685
686   /* Merge all the entry point arguments.  */
687   for (el = ns->entries; el; el = el->next)
688     merge_argument_lists (proc, el->sym->formal);
689
690   /* Check the master formal arguments for any that are not
691      present in all entry points.  */
692   for (el = ns->entries; el; el = el->next)
693     check_argument_lists (proc, el->sym->formal);
694
695   /* Use the master function for the function body.  */
696   ns->proc_name = proc;
697
698   /* Finalize the new symbols.  */
699   gfc_commit_symbols ();
700
701   /* Restore the original namespace.  */
702   gfc_current_ns = old_ns;
703 }
704
705
706 /* Resolve common variables.  */
707 static void
708 resolve_common_vars (gfc_symbol *sym, bool named_common)
709 {
710   gfc_symbol *csym = sym;
711
712   for (; csym; csym = csym->common_next)
713     {
714       if (csym->value || csym->attr.data)
715         {
716           if (!csym->ns->is_block_data)
717             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
718                             "but only in BLOCK DATA initialization is "
719                             "allowed", csym->name, &csym->declared_at);
720           else if (!named_common)
721             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
722                             "in a blank COMMON but initialization is only "
723                             "allowed in named common blocks", csym->name,
724                             &csym->declared_at);
725         }
726
727       if (csym->ts.type != BT_DERIVED)
728         continue;
729
730       if (!(csym->ts.u.derived->attr.sequence
731             || csym->ts.u.derived->attr.is_bind_c))
732         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
733                        "has neither the SEQUENCE nor the BIND(C) "
734                        "attribute", csym->name, &csym->declared_at);
735       if (csym->ts.u.derived->attr.alloc_comp)
736         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
737                        "has an ultimate component that is "
738                        "allocatable", csym->name, &csym->declared_at);
739       if (gfc_has_default_initializer (csym->ts.u.derived))
740         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
741                        "may not have default initializer", csym->name,
742                        &csym->declared_at);
743
744       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
745         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
746     }
747 }
748
749 /* Resolve common blocks.  */
750 static void
751 resolve_common_blocks (gfc_symtree *common_root)
752 {
753   gfc_symbol *sym;
754
755   if (common_root == NULL)
756     return;
757
758   if (common_root->left)
759     resolve_common_blocks (common_root->left);
760   if (common_root->right)
761     resolve_common_blocks (common_root->right);
762
763   resolve_common_vars (common_root->n.common->head, true);
764
765   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
766   if (sym == NULL)
767     return;
768
769   if (sym->attr.flavor == FL_PARAMETER)
770     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
771                sym->name, &common_root->n.common->where, &sym->declared_at);
772
773   if (sym->attr.intrinsic)
774     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
775                sym->name, &common_root->n.common->where);
776   else if (sym->attr.result
777            || gfc_is_function_return_value (sym, gfc_current_ns))
778     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
779                     "that is also a function result", sym->name,
780                     &common_root->n.common->where);
781   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
782            && sym->attr.proc != PROC_ST_FUNCTION)
783     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
784                     "that is also a global procedure", sym->name,
785                     &common_root->n.common->where);
786 }
787
788
789 /* Resolve contained function types.  Because contained functions can call one
790    another, they have to be worked out before any of the contained procedures
791    can be resolved.
792
793    The good news is that if a function doesn't already have a type, the only
794    way it can get one is through an IMPLICIT type or a RESULT variable, because
795    by definition contained functions are contained namespace they're contained
796    in, not in a sibling or parent namespace.  */
797
798 static void
799 resolve_contained_functions (gfc_namespace *ns)
800 {
801   gfc_namespace *child;
802   gfc_entry_list *el;
803
804   resolve_formal_arglists (ns);
805
806   for (child = ns->contained; child; child = child->sibling)
807     {
808       /* Resolve alternate entry points first.  */
809       resolve_entries (child);
810
811       /* Then check function return types.  */
812       resolve_contained_fntype (child->proc_name, child);
813       for (el = child->entries; el; el = el->next)
814         resolve_contained_fntype (el->sym, child);
815     }
816 }
817
818
819 /* Resolve all of the elements of a structure constructor and make sure that
820    the types are correct.  */
821
822 static gfc_try
823 resolve_structure_cons (gfc_expr *expr)
824 {
825   gfc_constructor *cons;
826   gfc_component *comp;
827   gfc_try t;
828   symbol_attribute a;
829
830   t = SUCCESS;
831   cons = gfc_constructor_first (expr->value.constructor);
832   /* A constructor may have references if it is the result of substituting a
833      parameter variable.  In this case we just pull out the component we
834      want.  */
835   if (expr->ref)
836     comp = expr->ref->u.c.sym->components;
837   else
838     comp = expr->ts.u.derived->components;
839
840   /* See if the user is trying to invoke a structure constructor for one of
841      the iso_c_binding derived types.  */
842   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
843       && expr->ts.u.derived->ts.is_iso_c && cons
844       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
845     {
846       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
847                  expr->ts.u.derived->name, &(expr->where));
848       return FAILURE;
849     }
850
851   /* Return if structure constructor is c_null_(fun)prt.  */
852   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
853       && expr->ts.u.derived->ts.is_iso_c && cons
854       && cons->expr && cons->expr->expr_type == EXPR_NULL)
855     return SUCCESS;
856
857   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
858     {
859       int rank;
860
861       if (!cons->expr)
862         continue;
863
864       if (gfc_resolve_expr (cons->expr) == FAILURE)
865         {
866           t = FAILURE;
867           continue;
868         }
869
870       rank = comp->as ? comp->as->rank : 0;
871       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
872           && (comp->attr.allocatable || cons->expr->rank))
873         {
874           gfc_error ("The rank of the element in the derived type "
875                      "constructor at %L does not match that of the "
876                      "component (%d/%d)", &cons->expr->where,
877                      cons->expr->rank, rank);
878           t = FAILURE;
879         }
880
881       /* If we don't have the right type, try to convert it.  */
882
883       if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
884         {
885           t = FAILURE;
886           if (strcmp (comp->name, "$extends") == 0)
887             {
888               /* Can afford to be brutal with the $extends initializer.
889                  The derived type can get lost because it is PRIVATE
890                  but it is not usage constrained by the standard.  */
891               cons->expr->ts = comp->ts;
892               t = SUCCESS;
893             }
894           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
895             gfc_error ("The element in the derived type constructor at %L, "
896                        "for pointer component '%s', is %s but should be %s",
897                        &cons->expr->where, comp->name,
898                        gfc_basic_typename (cons->expr->ts.type),
899                        gfc_basic_typename (comp->ts.type));
900           else
901             t = gfc_convert_type (cons->expr, &comp->ts, 1);
902         }
903
904       if (cons->expr->expr_type == EXPR_NULL
905           && !(comp->attr.pointer || comp->attr.allocatable
906                || comp->attr.proc_pointer
907                || (comp->ts.type == BT_CLASS
908                    && (CLASS_DATA (comp)->attr.pointer
909                        || CLASS_DATA (comp)->attr.allocatable))))
910         {
911           t = FAILURE;
912           gfc_error ("The NULL in the derived type constructor at %L is "
913                      "being applied to component '%s', which is neither "
914                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
915                      comp->name);
916         }
917
918       if (!comp->attr.pointer || cons->expr->expr_type == EXPR_NULL)
919         continue;
920
921       a = gfc_expr_attr (cons->expr);
922
923       if (!a.pointer && !a.target)
924         {
925           t = FAILURE;
926           gfc_error ("The element in the derived type constructor at %L, "
927                      "for pointer component '%s' should be a POINTER or "
928                      "a TARGET", &cons->expr->where, comp->name);
929         }
930
931       /* F2003, C1272 (3).  */
932       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
933           && (gfc_impure_variable (cons->expr->symtree->n.sym)
934               || gfc_is_coindexed (cons->expr)))
935         {
936           t = FAILURE;
937           gfc_error ("Invalid expression in the derived type constructor for "
938                      "pointer component '%s' at %L in PURE procedure",
939                      comp->name, &cons->expr->where);
940         }
941     }
942
943   return t;
944 }
945
946
947 /****************** Expression name resolution ******************/
948
949 /* Returns 0 if a symbol was not declared with a type or
950    attribute declaration statement, nonzero otherwise.  */
951
952 static int
953 was_declared (gfc_symbol *sym)
954 {
955   symbol_attribute a;
956
957   a = sym->attr;
958
959   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
960     return 1;
961
962   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
963       || a.optional || a.pointer || a.save || a.target || a.volatile_
964       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
965       || a.asynchronous || a.codimension)
966     return 1;
967
968   return 0;
969 }
970
971
972 /* Determine if a symbol is generic or not.  */
973
974 static int
975 generic_sym (gfc_symbol *sym)
976 {
977   gfc_symbol *s;
978
979   if (sym->attr.generic ||
980       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
981     return 1;
982
983   if (was_declared (sym) || sym->ns->parent == NULL)
984     return 0;
985
986   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
987   
988   if (s != NULL)
989     {
990       if (s == sym)
991         return 0;
992       else
993         return generic_sym (s);
994     }
995
996   return 0;
997 }
998
999
1000 /* Determine if a symbol is specific or not.  */
1001
1002 static int
1003 specific_sym (gfc_symbol *sym)
1004 {
1005   gfc_symbol *s;
1006
1007   if (sym->attr.if_source == IFSRC_IFBODY
1008       || sym->attr.proc == PROC_MODULE
1009       || sym->attr.proc == PROC_INTERNAL
1010       || sym->attr.proc == PROC_ST_FUNCTION
1011       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1012       || sym->attr.external)
1013     return 1;
1014
1015   if (was_declared (sym) || sym->ns->parent == NULL)
1016     return 0;
1017
1018   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1019
1020   return (s == NULL) ? 0 : specific_sym (s);
1021 }
1022
1023
1024 /* Figure out if the procedure is specific, generic or unknown.  */
1025
1026 typedef enum
1027 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1028 proc_type;
1029
1030 static proc_type
1031 procedure_kind (gfc_symbol *sym)
1032 {
1033   if (generic_sym (sym))
1034     return PTYPE_GENERIC;
1035
1036   if (specific_sym (sym))
1037     return PTYPE_SPECIFIC;
1038
1039   return PTYPE_UNKNOWN;
1040 }
1041
1042 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1043    is nonzero when matching actual arguments.  */
1044
1045 static int need_full_assumed_size = 0;
1046
1047 static bool
1048 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1049 {
1050   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1051       return false;
1052
1053   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1054      What should it be?  */
1055   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1056           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1057                && (e->ref->u.ar.type == AR_FULL))
1058     {
1059       gfc_error ("The upper bound in the last dimension must "
1060                  "appear in the reference to the assumed size "
1061                  "array '%s' at %L", sym->name, &e->where);
1062       return true;
1063     }
1064   return false;
1065 }
1066
1067
1068 /* Look for bad assumed size array references in argument expressions
1069   of elemental and array valued intrinsic procedures.  Since this is
1070   called from procedure resolution functions, it only recurses at
1071   operators.  */
1072
1073 static bool
1074 resolve_assumed_size_actual (gfc_expr *e)
1075 {
1076   if (e == NULL)
1077    return false;
1078
1079   switch (e->expr_type)
1080     {
1081     case EXPR_VARIABLE:
1082       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1083         return true;
1084       break;
1085
1086     case EXPR_OP:
1087       if (resolve_assumed_size_actual (e->value.op.op1)
1088           || resolve_assumed_size_actual (e->value.op.op2))
1089         return true;
1090       break;
1091
1092     default:
1093       break;
1094     }
1095   return false;
1096 }
1097
1098
1099 /* Check a generic procedure, passed as an actual argument, to see if
1100    there is a matching specific name.  If none, it is an error, and if
1101    more than one, the reference is ambiguous.  */
1102 static int
1103 count_specific_procs (gfc_expr *e)
1104 {
1105   int n;
1106   gfc_interface *p;
1107   gfc_symbol *sym;
1108         
1109   n = 0;
1110   sym = e->symtree->n.sym;
1111
1112   for (p = sym->generic; p; p = p->next)
1113     if (strcmp (sym->name, p->sym->name) == 0)
1114       {
1115         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1116                                        sym->name);
1117         n++;
1118       }
1119
1120   if (n > 1)
1121     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1122                &e->where);
1123
1124   if (n == 0)
1125     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1126                "argument at %L", sym->name, &e->where);
1127
1128   return n;
1129 }
1130
1131
1132 /* See if a call to sym could possibly be a not allowed RECURSION because of
1133    a missing RECURIVE declaration.  This means that either sym is the current
1134    context itself, or sym is the parent of a contained procedure calling its
1135    non-RECURSIVE containing procedure.
1136    This also works if sym is an ENTRY.  */
1137
1138 static bool
1139 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1140 {
1141   gfc_symbol* proc_sym;
1142   gfc_symbol* context_proc;
1143   gfc_namespace* real_context;
1144
1145   if (sym->attr.flavor == FL_PROGRAM)
1146     return false;
1147
1148   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1149
1150   /* If we've got an ENTRY, find real procedure.  */
1151   if (sym->attr.entry && sym->ns->entries)
1152     proc_sym = sym->ns->entries->sym;
1153   else
1154     proc_sym = sym;
1155
1156   /* If sym is RECURSIVE, all is well of course.  */
1157   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1158     return false;
1159
1160   /* Find the context procedure's "real" symbol if it has entries.
1161      We look for a procedure symbol, so recurse on the parents if we don't
1162      find one (like in case of a BLOCK construct).  */
1163   for (real_context = context; ; real_context = real_context->parent)
1164     {
1165       /* We should find something, eventually!  */
1166       gcc_assert (real_context);
1167
1168       context_proc = (real_context->entries ? real_context->entries->sym
1169                                             : real_context->proc_name);
1170
1171       /* In some special cases, there may not be a proc_name, like for this
1172          invalid code:
1173          real(bad_kind()) function foo () ...
1174          when checking the call to bad_kind ().
1175          In these cases, we simply return here and assume that the
1176          call is ok.  */
1177       if (!context_proc)
1178         return false;
1179
1180       if (context_proc->attr.flavor != FL_LABEL)
1181         break;
1182     }
1183
1184   /* A call from sym's body to itself is recursion, of course.  */
1185   if (context_proc == proc_sym)
1186     return true;
1187
1188   /* The same is true if context is a contained procedure and sym the
1189      containing one.  */
1190   if (context_proc->attr.contained)
1191     {
1192       gfc_symbol* parent_proc;
1193
1194       gcc_assert (context->parent);
1195       parent_proc = (context->parent->entries ? context->parent->entries->sym
1196                                               : context->parent->proc_name);
1197
1198       if (parent_proc == proc_sym)
1199         return true;
1200     }
1201
1202   return false;
1203 }
1204
1205
1206 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1207    its typespec and formal argument list.  */
1208
1209 static gfc_try
1210 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1211 {
1212   gfc_intrinsic_sym* isym;
1213   const char* symstd;
1214
1215   if (sym->formal)
1216     return SUCCESS;
1217
1218   /* We already know this one is an intrinsic, so we don't call
1219      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1220      gfc_find_subroutine directly to check whether it is a function or
1221      subroutine.  */
1222
1223   if ((isym = gfc_find_function (sym->name)))
1224     {
1225       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1226           && !sym->attr.implicit_type)
1227         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1228                       " ignored", sym->name, &sym->declared_at);
1229
1230       if (!sym->attr.function &&
1231           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1232         return FAILURE;
1233
1234       sym->ts = isym->ts;
1235     }
1236   else if ((isym = gfc_find_subroutine (sym->name)))
1237     {
1238       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1239         {
1240           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1241                       " specifier", sym->name, &sym->declared_at);
1242           return FAILURE;
1243         }
1244
1245       if (!sym->attr.subroutine &&
1246           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1247         return FAILURE;
1248     }
1249   else
1250     {
1251       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1252                  &sym->declared_at);
1253       return FAILURE;
1254     }
1255
1256   gfc_copy_formal_args_intr (sym, isym);
1257
1258   /* Check it is actually available in the standard settings.  */
1259   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1260       == FAILURE)
1261     {
1262       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1263                  " available in the current standard settings but %s.  Use"
1264                  " an appropriate -std=* option or enable -fall-intrinsics"
1265                  " in order to use it.",
1266                  sym->name, &sym->declared_at, symstd);
1267       return FAILURE;
1268     }
1269
1270   return SUCCESS;
1271 }
1272
1273
1274 /* Resolve a procedure expression, like passing it to a called procedure or as
1275    RHS for a procedure pointer assignment.  */
1276
1277 static gfc_try
1278 resolve_procedure_expression (gfc_expr* expr)
1279 {
1280   gfc_symbol* sym;
1281
1282   if (expr->expr_type != EXPR_VARIABLE)
1283     return SUCCESS;
1284   gcc_assert (expr->symtree);
1285
1286   sym = expr->symtree->n.sym;
1287
1288   if (sym->attr.intrinsic)
1289     resolve_intrinsic (sym, &expr->where);
1290
1291   if (sym->attr.flavor != FL_PROCEDURE
1292       || (sym->attr.function && sym->result == sym))
1293     return SUCCESS;
1294
1295   /* A non-RECURSIVE procedure that is used as procedure expression within its
1296      own body is in danger of being called recursively.  */
1297   if (is_illegal_recursion (sym, gfc_current_ns))
1298     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1299                  " itself recursively.  Declare it RECURSIVE or use"
1300                  " -frecursive", sym->name, &expr->where);
1301   
1302   return SUCCESS;
1303 }
1304
1305
1306 /* Resolve an actual argument list.  Most of the time, this is just
1307    resolving the expressions in the list.
1308    The exception is that we sometimes have to decide whether arguments
1309    that look like procedure arguments are really simple variable
1310    references.  */
1311
1312 static gfc_try
1313 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1314                         bool no_formal_args)
1315 {
1316   gfc_symbol *sym;
1317   gfc_symtree *parent_st;
1318   gfc_expr *e;
1319   int save_need_full_assumed_size;
1320   gfc_component *comp;
1321
1322   for (; arg; arg = arg->next)
1323     {
1324       e = arg->expr;
1325       if (e == NULL)
1326         {
1327           /* Check the label is a valid branching target.  */
1328           if (arg->label)
1329             {
1330               if (arg->label->defined == ST_LABEL_UNKNOWN)
1331                 {
1332                   gfc_error ("Label %d referenced at %L is never defined",
1333                              arg->label->value, &arg->label->where);
1334                   return FAILURE;
1335                 }
1336             }
1337           continue;
1338         }
1339
1340       if (gfc_is_proc_ptr_comp (e, &comp))
1341         {
1342           e->ts = comp->ts;
1343           if (e->expr_type == EXPR_PPC)
1344             {
1345               if (comp->as != NULL)
1346                 e->rank = comp->as->rank;
1347               e->expr_type = EXPR_FUNCTION;
1348             }
1349           if (gfc_resolve_expr (e) == FAILURE)                          
1350             return FAILURE; 
1351           goto argument_list;
1352         }
1353
1354       if (e->expr_type == EXPR_VARIABLE
1355             && e->symtree->n.sym->attr.generic
1356             && no_formal_args
1357             && count_specific_procs (e) != 1)
1358         return FAILURE;
1359
1360       if (e->ts.type != BT_PROCEDURE)
1361         {
1362           save_need_full_assumed_size = need_full_assumed_size;
1363           if (e->expr_type != EXPR_VARIABLE)
1364             need_full_assumed_size = 0;
1365           if (gfc_resolve_expr (e) != SUCCESS)
1366             return FAILURE;
1367           need_full_assumed_size = save_need_full_assumed_size;
1368           goto argument_list;
1369         }
1370
1371       /* See if the expression node should really be a variable reference.  */
1372
1373       sym = e->symtree->n.sym;
1374
1375       if (sym->attr.flavor == FL_PROCEDURE
1376           || sym->attr.intrinsic
1377           || sym->attr.external)
1378         {
1379           int actual_ok;
1380
1381           /* If a procedure is not already determined to be something else
1382              check if it is intrinsic.  */
1383           if (!sym->attr.intrinsic
1384               && !(sym->attr.external || sym->attr.use_assoc
1385                    || sym->attr.if_source == IFSRC_IFBODY)
1386               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1387             sym->attr.intrinsic = 1;
1388
1389           if (sym->attr.proc == PROC_ST_FUNCTION)
1390             {
1391               gfc_error ("Statement function '%s' at %L is not allowed as an "
1392                          "actual argument", sym->name, &e->where);
1393             }
1394
1395           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1396                                                sym->attr.subroutine);
1397           if (sym->attr.intrinsic && actual_ok == 0)
1398             {
1399               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1400                          "actual argument", sym->name, &e->where);
1401             }
1402
1403           if (sym->attr.contained && !sym->attr.use_assoc
1404               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1405             {
1406               gfc_error ("Internal procedure '%s' is not allowed as an "
1407                          "actual argument at %L", sym->name, &e->where);
1408             }
1409
1410           if (sym->attr.elemental && !sym->attr.intrinsic)
1411             {
1412               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1413                          "allowed as an actual argument at %L", sym->name,
1414                          &e->where);
1415             }
1416
1417           /* Check if a generic interface has a specific procedure
1418             with the same name before emitting an error.  */
1419           if (sym->attr.generic && count_specific_procs (e) != 1)
1420             return FAILURE;
1421           
1422           /* Just in case a specific was found for the expression.  */
1423           sym = e->symtree->n.sym;
1424
1425           /* If the symbol is the function that names the current (or
1426              parent) scope, then we really have a variable reference.  */
1427
1428           if (gfc_is_function_return_value (sym, sym->ns))
1429             goto got_variable;
1430
1431           /* If all else fails, see if we have a specific intrinsic.  */
1432           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1433             {
1434               gfc_intrinsic_sym *isym;
1435
1436               isym = gfc_find_function (sym->name);
1437               if (isym == NULL || !isym->specific)
1438                 {
1439                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1440                              "for the reference '%s' at %L", sym->name,
1441                              &e->where);
1442                   return FAILURE;
1443                 }
1444               sym->ts = isym->ts;
1445               sym->attr.intrinsic = 1;
1446               sym->attr.function = 1;
1447             }
1448
1449           if (gfc_resolve_expr (e) == FAILURE)
1450             return FAILURE;
1451           goto argument_list;
1452         }
1453
1454       /* See if the name is a module procedure in a parent unit.  */
1455
1456       if (was_declared (sym) || sym->ns->parent == NULL)
1457         goto got_variable;
1458
1459       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1460         {
1461           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1462           return FAILURE;
1463         }
1464
1465       if (parent_st == NULL)
1466         goto got_variable;
1467
1468       sym = parent_st->n.sym;
1469       e->symtree = parent_st;           /* Point to the right thing.  */
1470
1471       if (sym->attr.flavor == FL_PROCEDURE
1472           || sym->attr.intrinsic
1473           || sym->attr.external)
1474         {
1475           if (gfc_resolve_expr (e) == FAILURE)
1476             return FAILURE;
1477           goto argument_list;
1478         }
1479
1480     got_variable:
1481       e->expr_type = EXPR_VARIABLE;
1482       e->ts = sym->ts;
1483       if (sym->as != NULL)
1484         {
1485           e->rank = sym->as->rank;
1486           e->ref = gfc_get_ref ();
1487           e->ref->type = REF_ARRAY;
1488           e->ref->u.ar.type = AR_FULL;
1489           e->ref->u.ar.as = sym->as;
1490         }
1491
1492       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1493          primary.c (match_actual_arg). If above code determines that it
1494          is a  variable instead, it needs to be resolved as it was not
1495          done at the beginning of this function.  */
1496       save_need_full_assumed_size = need_full_assumed_size;
1497       if (e->expr_type != EXPR_VARIABLE)
1498         need_full_assumed_size = 0;
1499       if (gfc_resolve_expr (e) != SUCCESS)
1500         return FAILURE;
1501       need_full_assumed_size = save_need_full_assumed_size;
1502
1503     argument_list:
1504       /* Check argument list functions %VAL, %LOC and %REF.  There is
1505          nothing to do for %REF.  */
1506       if (arg->name && arg->name[0] == '%')
1507         {
1508           if (strncmp ("%VAL", arg->name, 4) == 0)
1509             {
1510               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1511                 {
1512                   gfc_error ("By-value argument at %L is not of numeric "
1513                              "type", &e->where);
1514                   return FAILURE;
1515                 }
1516
1517               if (e->rank)
1518                 {
1519                   gfc_error ("By-value argument at %L cannot be an array or "
1520                              "an array section", &e->where);
1521                 return FAILURE;
1522                 }
1523
1524               /* Intrinsics are still PROC_UNKNOWN here.  However,
1525                  since same file external procedures are not resolvable
1526                  in gfortran, it is a good deal easier to leave them to
1527                  intrinsic.c.  */
1528               if (ptype != PROC_UNKNOWN
1529                   && ptype != PROC_DUMMY
1530                   && ptype != PROC_EXTERNAL
1531                   && ptype != PROC_MODULE)
1532                 {
1533                   gfc_error ("By-value argument at %L is not allowed "
1534                              "in this context", &e->where);
1535                   return FAILURE;
1536                 }
1537             }
1538
1539           /* Statement functions have already been excluded above.  */
1540           else if (strncmp ("%LOC", arg->name, 4) == 0
1541                    && e->ts.type == BT_PROCEDURE)
1542             {
1543               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1544                 {
1545                   gfc_error ("Passing internal procedure at %L by location "
1546                              "not allowed", &e->where);
1547                   return FAILURE;
1548                 }
1549             }
1550         }
1551
1552       /* Fortran 2008, C1237.  */
1553       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1554           && gfc_has_ultimate_pointer (e))
1555         {
1556           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1557                      "component", &e->where);
1558           return FAILURE;
1559         }
1560     }
1561
1562   return SUCCESS;
1563 }
1564
1565
1566 /* Do the checks of the actual argument list that are specific to elemental
1567    procedures.  If called with c == NULL, we have a function, otherwise if
1568    expr == NULL, we have a subroutine.  */
1569
1570 static gfc_try
1571 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1572 {
1573   gfc_actual_arglist *arg0;
1574   gfc_actual_arglist *arg;
1575   gfc_symbol *esym = NULL;
1576   gfc_intrinsic_sym *isym = NULL;
1577   gfc_expr *e = NULL;
1578   gfc_intrinsic_arg *iformal = NULL;
1579   gfc_formal_arglist *eformal = NULL;
1580   bool formal_optional = false;
1581   bool set_by_optional = false;
1582   int i;
1583   int rank = 0;
1584
1585   /* Is this an elemental procedure?  */
1586   if (expr && expr->value.function.actual != NULL)
1587     {
1588       if (expr->value.function.esym != NULL
1589           && expr->value.function.esym->attr.elemental)
1590         {
1591           arg0 = expr->value.function.actual;
1592           esym = expr->value.function.esym;
1593         }
1594       else if (expr->value.function.isym != NULL
1595                && expr->value.function.isym->elemental)
1596         {
1597           arg0 = expr->value.function.actual;
1598           isym = expr->value.function.isym;
1599         }
1600       else
1601         return SUCCESS;
1602     }
1603   else if (c && c->ext.actual != NULL)
1604     {
1605       arg0 = c->ext.actual;
1606       
1607       if (c->resolved_sym)
1608         esym = c->resolved_sym;
1609       else
1610         esym = c->symtree->n.sym;
1611       gcc_assert (esym);
1612
1613       if (!esym->attr.elemental)
1614         return SUCCESS;
1615     }
1616   else
1617     return SUCCESS;
1618
1619   /* The rank of an elemental is the rank of its array argument(s).  */
1620   for (arg = arg0; arg; arg = arg->next)
1621     {
1622       if (arg->expr != NULL && arg->expr->rank > 0)
1623         {
1624           rank = arg->expr->rank;
1625           if (arg->expr->expr_type == EXPR_VARIABLE
1626               && arg->expr->symtree->n.sym->attr.optional)
1627             set_by_optional = true;
1628
1629           /* Function specific; set the result rank and shape.  */
1630           if (expr)
1631             {
1632               expr->rank = rank;
1633               if (!expr->shape && arg->expr->shape)
1634                 {
1635                   expr->shape = gfc_get_shape (rank);
1636                   for (i = 0; i < rank; i++)
1637                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1638                 }
1639             }
1640           break;
1641         }
1642     }
1643
1644   /* If it is an array, it shall not be supplied as an actual argument
1645      to an elemental procedure unless an array of the same rank is supplied
1646      as an actual argument corresponding to a nonoptional dummy argument of
1647      that elemental procedure(12.4.1.5).  */
1648   formal_optional = false;
1649   if (isym)
1650     iformal = isym->formal;
1651   else
1652     eformal = esym->formal;
1653
1654   for (arg = arg0; arg; arg = arg->next)
1655     {
1656       if (eformal)
1657         {
1658           if (eformal->sym && eformal->sym->attr.optional)
1659             formal_optional = true;
1660           eformal = eformal->next;
1661         }
1662       else if (isym && iformal)
1663         {
1664           if (iformal->optional)
1665             formal_optional = true;
1666           iformal = iformal->next;
1667         }
1668       else if (isym)
1669         formal_optional = true;
1670
1671       if (pedantic && arg->expr != NULL
1672           && arg->expr->expr_type == EXPR_VARIABLE
1673           && arg->expr->symtree->n.sym->attr.optional
1674           && formal_optional
1675           && arg->expr->rank
1676           && (set_by_optional || arg->expr->rank != rank)
1677           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1678         {
1679           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1680                        "MISSING, it cannot be the actual argument of an "
1681                        "ELEMENTAL procedure unless there is a non-optional "
1682                        "argument with the same rank (12.4.1.5)",
1683                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1684           return FAILURE;
1685         }
1686     }
1687
1688   for (arg = arg0; arg; arg = arg->next)
1689     {
1690       if (arg->expr == NULL || arg->expr->rank == 0)
1691         continue;
1692
1693       /* Being elemental, the last upper bound of an assumed size array
1694          argument must be present.  */
1695       if (resolve_assumed_size_actual (arg->expr))
1696         return FAILURE;
1697
1698       /* Elemental procedure's array actual arguments must conform.  */
1699       if (e != NULL)
1700         {
1701           if (gfc_check_conformance (arg->expr, e,
1702                                      "elemental procedure") == FAILURE)
1703             return FAILURE;
1704         }
1705       else
1706         e = arg->expr;
1707     }
1708
1709   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1710      is an array, the intent inout/out variable needs to be also an array.  */
1711   if (rank > 0 && esym && expr == NULL)
1712     for (eformal = esym->formal, arg = arg0; arg && eformal;
1713          arg = arg->next, eformal = eformal->next)
1714       if ((eformal->sym->attr.intent == INTENT_OUT
1715            || eformal->sym->attr.intent == INTENT_INOUT)
1716           && arg->expr && arg->expr->rank == 0)
1717         {
1718           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1719                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1720                      "actual argument is an array", &arg->expr->where,
1721                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1722                      : "INOUT", eformal->sym->name, esym->name);
1723           return FAILURE;
1724         }
1725   return SUCCESS;
1726 }
1727
1728
1729 /* Go through each actual argument in ACTUAL and see if it can be
1730    implemented as an inlined, non-copying intrinsic.  FNSYM is the
1731    function being called, or NULL if not known.  */
1732
1733 static void
1734 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1735 {
1736   gfc_actual_arglist *ap;
1737   gfc_expr *expr;
1738
1739   for (ap = actual; ap; ap = ap->next)
1740     if (ap->expr
1741         && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1742         && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual,
1743                                          NOT_ELEMENTAL))
1744       ap->expr->inline_noncopying_intrinsic = 1;
1745 }
1746
1747
1748 /* This function does the checking of references to global procedures
1749    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1750    77 and 95 standards.  It checks for a gsymbol for the name, making
1751    one if it does not already exist.  If it already exists, then the
1752    reference being resolved must correspond to the type of gsymbol.
1753    Otherwise, the new symbol is equipped with the attributes of the
1754    reference.  The corresponding code that is called in creating
1755    global entities is parse.c.
1756
1757    In addition, for all but -std=legacy, the gsymbols are used to
1758    check the interfaces of external procedures from the same file.
1759    The namespace of the gsymbol is resolved and then, once this is
1760    done the interface is checked.  */
1761
1762
1763 static bool
1764 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1765 {
1766   if (!gsym_ns->proc_name->attr.recursive)
1767     return true;
1768
1769   if (sym->ns == gsym_ns)
1770     return false;
1771
1772   if (sym->ns->parent && sym->ns->parent == gsym_ns)
1773     return false;
1774
1775   return true;
1776 }
1777
1778 static bool
1779 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
1780 {
1781   if (gsym_ns->entries)
1782     {
1783       gfc_entry_list *entry = gsym_ns->entries;
1784
1785       for (; entry; entry = entry->next)
1786         {
1787           if (strcmp (sym->name, entry->sym->name) == 0)
1788             {
1789               if (strcmp (gsym_ns->proc_name->name,
1790                           sym->ns->proc_name->name) == 0)
1791                 return false;
1792
1793               if (sym->ns->parent
1794                   && strcmp (gsym_ns->proc_name->name,
1795                              sym->ns->parent->proc_name->name) == 0)
1796                 return false;
1797             }
1798         }
1799     }
1800   return true;
1801 }
1802
1803 static void
1804 resolve_global_procedure (gfc_symbol *sym, locus *where,
1805                           gfc_actual_arglist **actual, int sub)
1806 {
1807   gfc_gsymbol * gsym;
1808   gfc_namespace *ns;
1809   enum gfc_symbol_type type;
1810
1811   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1812
1813   gsym = gfc_get_gsymbol (sym->name);
1814
1815   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1816     gfc_global_used (gsym, where);
1817
1818   if (gfc_option.flag_whole_file
1819         && sym->attr.if_source == IFSRC_UNKNOWN
1820         && gsym->type != GSYM_UNKNOWN
1821         && gsym->ns
1822         && gsym->ns->resolved != -1
1823         && gsym->ns->proc_name
1824         && not_in_recursive (sym, gsym->ns)
1825         && not_entry_self_reference (sym, gsym->ns))
1826     {
1827       /* Resolve the gsymbol namespace if needed.  */
1828       if (!gsym->ns->resolved)
1829         {
1830           gfc_dt_list *old_dt_list;
1831
1832           /* Stash away derived types so that the backend_decls do not
1833              get mixed up.  */
1834           old_dt_list = gfc_derived_types;
1835           gfc_derived_types = NULL;
1836
1837           gfc_resolve (gsym->ns);
1838
1839           /* Store the new derived types with the global namespace.  */
1840           if (gfc_derived_types)
1841             gsym->ns->derived_types = gfc_derived_types;
1842
1843           /* Restore the derived types of this namespace.  */
1844           gfc_derived_types = old_dt_list;
1845         }
1846
1847       /* Make sure that translation for the gsymbol occurs before
1848          the procedure currently being resolved.  */
1849       ns = gfc_global_ns_list;
1850       for (; ns && ns != gsym->ns; ns = ns->sibling)
1851         {
1852           if (ns->sibling == gsym->ns)
1853             {
1854               ns->sibling = gsym->ns->sibling;
1855               gsym->ns->sibling = gfc_global_ns_list;
1856               gfc_global_ns_list = gsym->ns;
1857               break;
1858             }
1859         }
1860
1861       /* Differences in constant character lengths.  */
1862       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
1863         {
1864           long int l1 = 0, l2 = 0;
1865           gfc_charlen *cl1 = sym->ts.u.cl;
1866           gfc_charlen *cl2 = gsym->ns->proc_name->ts.u.cl;
1867
1868           if (cl1 != NULL
1869               && cl1->length != NULL
1870               && cl1->length->expr_type == EXPR_CONSTANT)
1871             l1 = mpz_get_si (cl1->length->value.integer);
1872
1873           if (cl2 != NULL
1874               && cl2->length != NULL
1875               && cl2->length->expr_type == EXPR_CONSTANT)
1876             l2 = mpz_get_si (cl2->length->value.integer);
1877
1878           if (l1 && l2 && l1 != l2)
1879             gfc_error ("Character length mismatch in return type of "
1880                        "function '%s' at %L (%ld/%ld)", sym->name,
1881                        &sym->declared_at, l1, l2);
1882         }
1883
1884      /* Type mismatch of function return type and expected type.  */
1885      if (sym->attr.function
1886          && !gfc_compare_types (&sym->ts, &gsym->ns->proc_name->ts))
1887         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
1888                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
1889                    gfc_typename (&gsym->ns->proc_name->ts));
1890
1891       if (gsym->ns->proc_name->formal)
1892         {
1893           gfc_formal_arglist *arg = gsym->ns->proc_name->formal;
1894           for ( ; arg; arg = arg->next)
1895             if (!arg->sym)
1896               continue;
1897             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
1898             else if (arg->sym->attr.allocatable
1899                      || arg->sym->attr.asynchronous
1900                      || arg->sym->attr.optional
1901                      || arg->sym->attr.pointer
1902                      || arg->sym->attr.target
1903                      || arg->sym->attr.value
1904                      || arg->sym->attr.volatile_)
1905               {
1906                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
1907                            "has an attribute that requires an explicit "
1908                            "interface for this procedure", arg->sym->name,
1909                            sym->name, &sym->declared_at);
1910                 break;
1911               }
1912             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
1913             else if (arg->sym && arg->sym->as
1914                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
1915               {
1916                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
1917                            "argument '%s' must have an explicit interface",
1918                            sym->name, &sym->declared_at, arg->sym->name);
1919                 break;
1920               }
1921             /* F2008, 12.4.2.2 (2c)  */
1922             else if (arg->sym->attr.codimension)
1923               {
1924                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
1925                            "'%s' must have an explicit interface",
1926                            sym->name, &sym->declared_at, arg->sym->name);
1927                 break;
1928               }
1929             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
1930             else if (false) /* TODO: is a parametrized derived type  */
1931               {
1932                 gfc_error ("Procedure '%s' at %L with parametrized derived "
1933                            "type argument '%s' must have an explicit "
1934                            "interface", sym->name, &sym->declared_at,
1935                            arg->sym->name);
1936                 break;
1937               }
1938             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
1939             else if (arg->sym->ts.type == BT_CLASS)
1940               {
1941                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
1942                            "argument '%s' must have an explicit interface",
1943                            sym->name, &sym->declared_at, arg->sym->name);
1944                 break;
1945               }
1946         }
1947
1948       if (gsym->ns->proc_name->attr.function)
1949         {
1950           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
1951           if (gsym->ns->proc_name->as
1952               && gsym->ns->proc_name->as->rank
1953               && (!sym->as || sym->as->rank != gsym->ns->proc_name->as->rank))
1954             gfc_error ("The reference to function '%s' at %L either needs an "
1955                        "explicit INTERFACE or the rank is incorrect", sym->name,
1956                        where);
1957
1958           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
1959           if (gsym->ns->proc_name->result->attr.pointer
1960               || gsym->ns->proc_name->result->attr.allocatable)
1961             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
1962                        "result must have an explicit interface", sym->name,
1963                        where);
1964
1965           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
1966           if (sym->ts.type == BT_CHARACTER
1967               && gsym->ns->proc_name->ts.u.cl->length != NULL)
1968             {
1969               gfc_charlen *cl = sym->ts.u.cl;
1970
1971               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
1972                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
1973                 {
1974                   gfc_error ("Nonconstant character-length function '%s' at %L "
1975                              "must have an explicit interface", sym->name,
1976                              &sym->declared_at);
1977                 }
1978             }
1979         }
1980
1981       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
1982       if (gsym->ns->proc_name->attr.elemental)
1983         {
1984           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
1985                      "interface", sym->name, &sym->declared_at);
1986         }
1987
1988       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
1989       if (gsym->ns->proc_name->attr.is_bind_c)
1990         {
1991           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
1992                      "an explicit interface", sym->name, &sym->declared_at);
1993         }
1994
1995       if (gfc_option.flag_whole_file == 1
1996           || ((gfc_option.warn_std & GFC_STD_LEGACY)
1997               && !(gfc_option.warn_std & GFC_STD_GNU)))
1998         gfc_errors_to_warnings (1);
1999
2000       gfc_procedure_use (gsym->ns->proc_name, actual, where);
2001
2002       gfc_errors_to_warnings (0);
2003     }
2004
2005   if (gsym->type == GSYM_UNKNOWN)
2006     {
2007       gsym->type = type;
2008       gsym->where = *where;
2009     }
2010
2011   gsym->used = 1;
2012 }
2013
2014
2015 /************* Function resolution *************/
2016
2017 /* Resolve a function call known to be generic.
2018    Section 14.1.2.4.1.  */
2019
2020 static match
2021 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2022 {
2023   gfc_symbol *s;
2024
2025   if (sym->attr.generic)
2026     {
2027       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2028       if (s != NULL)
2029         {
2030           expr->value.function.name = s->name;
2031           expr->value.function.esym = s;
2032
2033           if (s->ts.type != BT_UNKNOWN)
2034             expr->ts = s->ts;
2035           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2036             expr->ts = s->result->ts;
2037
2038           if (s->as != NULL)
2039             expr->rank = s->as->rank;
2040           else if (s->result != NULL && s->result->as != NULL)
2041             expr->rank = s->result->as->rank;
2042
2043           gfc_set_sym_referenced (expr->value.function.esym);
2044
2045           return MATCH_YES;
2046         }
2047
2048       /* TODO: Need to search for elemental references in generic
2049          interface.  */
2050     }
2051
2052   if (sym->attr.intrinsic)
2053     return gfc_intrinsic_func_interface (expr, 0);
2054
2055   return MATCH_NO;
2056 }
2057
2058
2059 static gfc_try
2060 resolve_generic_f (gfc_expr *expr)
2061 {
2062   gfc_symbol *sym;
2063   match m;
2064
2065   sym = expr->symtree->n.sym;
2066
2067   for (;;)
2068     {
2069       m = resolve_generic_f0 (expr, sym);
2070       if (m == MATCH_YES)
2071         return SUCCESS;
2072       else if (m == MATCH_ERROR)
2073         return FAILURE;
2074
2075 generic:
2076       if (sym->ns->parent == NULL)
2077         break;
2078       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2079
2080       if (sym == NULL)
2081         break;
2082       if (!generic_sym (sym))
2083         goto generic;
2084     }
2085
2086   /* Last ditch attempt.  See if the reference is to an intrinsic
2087      that possesses a matching interface.  14.1.2.4  */
2088   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
2089     {
2090       gfc_error ("There is no specific function for the generic '%s' at %L",
2091                  expr->symtree->n.sym->name, &expr->where);
2092       return FAILURE;
2093     }
2094
2095   m = gfc_intrinsic_func_interface (expr, 0);
2096   if (m == MATCH_YES)
2097     return SUCCESS;
2098   if (m == MATCH_NO)
2099     gfc_error ("Generic function '%s' at %L is not consistent with a "
2100                "specific intrinsic interface", expr->symtree->n.sym->name,
2101                &expr->where);
2102
2103   return FAILURE;
2104 }
2105
2106
2107 /* Resolve a function call known to be specific.  */
2108
2109 static match
2110 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2111 {
2112   match m;
2113
2114   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2115     {
2116       if (sym->attr.dummy)
2117         {
2118           sym->attr.proc = PROC_DUMMY;
2119           goto found;
2120         }
2121
2122       sym->attr.proc = PROC_EXTERNAL;
2123       goto found;
2124     }
2125
2126   if (sym->attr.proc == PROC_MODULE
2127       || sym->attr.proc == PROC_ST_FUNCTION
2128       || sym->attr.proc == PROC_INTERNAL)
2129     goto found;
2130
2131   if (sym->attr.intrinsic)
2132     {
2133       m = gfc_intrinsic_func_interface (expr, 1);
2134       if (m == MATCH_YES)
2135         return MATCH_YES;
2136       if (m == MATCH_NO)
2137         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2138                    "with an intrinsic", sym->name, &expr->where);
2139
2140       return MATCH_ERROR;
2141     }
2142
2143   return MATCH_NO;
2144
2145 found:
2146   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2147
2148   if (sym->result)
2149     expr->ts = sym->result->ts;
2150   else
2151     expr->ts = sym->ts;
2152   expr->value.function.name = sym->name;
2153   expr->value.function.esym = sym;
2154   if (sym->as != NULL)
2155     expr->rank = sym->as->rank;
2156
2157   return MATCH_YES;
2158 }
2159
2160
2161 static gfc_try
2162 resolve_specific_f (gfc_expr *expr)
2163 {
2164   gfc_symbol *sym;
2165   match m;
2166
2167   sym = expr->symtree->n.sym;
2168
2169   for (;;)
2170     {
2171       m = resolve_specific_f0 (sym, expr);
2172       if (m == MATCH_YES)
2173         return SUCCESS;
2174       if (m == MATCH_ERROR)
2175         return FAILURE;
2176
2177       if (sym->ns->parent == NULL)
2178         break;
2179
2180       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2181
2182       if (sym == NULL)
2183         break;
2184     }
2185
2186   gfc_error ("Unable to resolve the specific function '%s' at %L",
2187              expr->symtree->n.sym->name, &expr->where);
2188
2189   return SUCCESS;
2190 }
2191
2192
2193 /* Resolve a procedure call not known to be generic nor specific.  */
2194
2195 static gfc_try
2196 resolve_unknown_f (gfc_expr *expr)
2197 {
2198   gfc_symbol *sym;
2199   gfc_typespec *ts;
2200
2201   sym = expr->symtree->n.sym;
2202
2203   if (sym->attr.dummy)
2204     {
2205       sym->attr.proc = PROC_DUMMY;
2206       expr->value.function.name = sym->name;
2207       goto set_type;
2208     }
2209
2210   /* See if we have an intrinsic function reference.  */
2211
2212   if (gfc_is_intrinsic (sym, 0, expr->where))
2213     {
2214       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2215         return SUCCESS;
2216       return FAILURE;
2217     }
2218
2219   /* The reference is to an external name.  */
2220
2221   sym->attr.proc = PROC_EXTERNAL;
2222   expr->value.function.name = sym->name;
2223   expr->value.function.esym = expr->symtree->n.sym;
2224
2225   if (sym->as != NULL)
2226     expr->rank = sym->as->rank;
2227
2228   /* Type of the expression is either the type of the symbol or the
2229      default type of the symbol.  */
2230
2231 set_type:
2232   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2233
2234   if (sym->ts.type != BT_UNKNOWN)
2235     expr->ts = sym->ts;
2236   else
2237     {
2238       ts = gfc_get_default_type (sym->name, sym->ns);
2239
2240       if (ts->type == BT_UNKNOWN)
2241         {
2242           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2243                      sym->name, &expr->where);
2244           return FAILURE;
2245         }
2246       else
2247         expr->ts = *ts;
2248     }
2249
2250   return SUCCESS;
2251 }
2252
2253
2254 /* Return true, if the symbol is an external procedure.  */
2255 static bool
2256 is_external_proc (gfc_symbol *sym)
2257 {
2258   if (!sym->attr.dummy && !sym->attr.contained
2259         && !(sym->attr.intrinsic
2260               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2261         && sym->attr.proc != PROC_ST_FUNCTION
2262         && !sym->attr.use_assoc
2263         && sym->name)
2264     return true;
2265
2266   return false;
2267 }
2268
2269
2270 /* Figure out if a function reference is pure or not.  Also set the name
2271    of the function for a potential error message.  Return nonzero if the
2272    function is PURE, zero if not.  */
2273 static int
2274 pure_stmt_function (gfc_expr *, gfc_symbol *);
2275
2276 static int
2277 pure_function (gfc_expr *e, const char **name)
2278 {
2279   int pure;
2280
2281   *name = NULL;
2282
2283   if (e->symtree != NULL
2284         && e->symtree->n.sym != NULL
2285         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2286     return pure_stmt_function (e, e->symtree->n.sym);
2287
2288   if (e->value.function.esym)
2289     {
2290       pure = gfc_pure (e->value.function.esym);
2291       *name = e->value.function.esym->name;
2292     }
2293   else if (e->value.function.isym)
2294     {
2295       pure = e->value.function.isym->pure
2296              || e->value.function.isym->elemental;
2297       *name = e->value.function.isym->name;
2298     }
2299   else
2300     {
2301       /* Implicit functions are not pure.  */
2302       pure = 0;
2303       *name = e->value.function.name;
2304     }
2305
2306   return pure;
2307 }
2308
2309
2310 static bool
2311 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2312                  int *f ATTRIBUTE_UNUSED)
2313 {
2314   const char *name;
2315
2316   /* Don't bother recursing into other statement functions
2317      since they will be checked individually for purity.  */
2318   if (e->expr_type != EXPR_FUNCTION
2319         || !e->symtree
2320         || e->symtree->n.sym == sym
2321         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2322     return false;
2323
2324   return pure_function (e, &name) ? false : true;
2325 }
2326
2327
2328 static int
2329 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2330 {
2331   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2332 }
2333
2334
2335 static gfc_try
2336 is_scalar_expr_ptr (gfc_expr *expr)
2337 {
2338   gfc_try retval = SUCCESS;
2339   gfc_ref *ref;
2340   int start;
2341   int end;
2342
2343   /* See if we have a gfc_ref, which means we have a substring, array
2344      reference, or a component.  */
2345   if (expr->ref != NULL)
2346     {
2347       ref = expr->ref;
2348       while (ref->next != NULL)
2349         ref = ref->next;
2350
2351       switch (ref->type)
2352         {
2353         case REF_SUBSTRING:
2354           if (ref->u.ss.length != NULL 
2355               && ref->u.ss.length->length != NULL
2356               && ref->u.ss.start
2357               && ref->u.ss.start->expr_type == EXPR_CONSTANT 
2358               && ref->u.ss.end
2359               && ref->u.ss.end->expr_type == EXPR_CONSTANT)
2360             {
2361               start = (int) mpz_get_si (ref->u.ss.start->value.integer);
2362               end = (int) mpz_get_si (ref->u.ss.end->value.integer);
2363               if (end - start + 1 != 1)
2364                 retval = FAILURE;
2365             }
2366           else
2367             retval = FAILURE;
2368           break;
2369         case REF_ARRAY:
2370           if (ref->u.ar.type == AR_ELEMENT)
2371             retval = SUCCESS;
2372           else if (ref->u.ar.type == AR_FULL)
2373             {
2374               /* The user can give a full array if the array is of size 1.  */
2375               if (ref->u.ar.as != NULL
2376                   && ref->u.ar.as->rank == 1
2377                   && ref->u.ar.as->type == AS_EXPLICIT
2378                   && ref->u.ar.as->lower[0] != NULL
2379                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2380                   && ref->u.ar.as->upper[0] != NULL
2381                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2382                 {
2383                   /* If we have a character string, we need to check if
2384                      its length is one.  */
2385                   if (expr->ts.type == BT_CHARACTER)
2386                     {
2387                       if (expr->ts.u.cl == NULL
2388                           || expr->ts.u.cl->length == NULL
2389                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2390                           != 0)
2391                         retval = FAILURE;
2392                     }
2393                   else
2394                     {
2395                       /* We have constant lower and upper bounds.  If the
2396                          difference between is 1, it can be considered a
2397                          scalar.  */
2398                       start = (int) mpz_get_si
2399                                 (ref->u.ar.as->lower[0]->value.integer);
2400                       end = (int) mpz_get_si
2401                                 (ref->u.ar.as->upper[0]->value.integer);
2402                       if (end - start + 1 != 1)
2403                         retval = FAILURE;
2404                    }
2405                 }
2406               else
2407                 retval = FAILURE;
2408             }
2409           else
2410             retval = FAILURE;
2411           break;
2412         default:
2413           retval = SUCCESS;
2414           break;
2415         }
2416     }
2417   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2418     {
2419       /* Character string.  Make sure it's of length 1.  */
2420       if (expr->ts.u.cl == NULL
2421           || expr->ts.u.cl->length == NULL
2422           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2423         retval = FAILURE;
2424     }
2425   else if (expr->rank != 0)
2426     retval = FAILURE;
2427
2428   return retval;
2429 }
2430
2431
2432 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2433    and, in the case of c_associated, set the binding label based on
2434    the arguments.  */
2435
2436 static gfc_try
2437 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2438                           gfc_symbol **new_sym)
2439 {
2440   char name[GFC_MAX_SYMBOL_LEN + 1];
2441   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2442   int optional_arg = 0, is_pointer = 0;
2443   gfc_try retval = SUCCESS;
2444   gfc_symbol *args_sym;
2445   gfc_typespec *arg_ts;
2446
2447   if (args->expr->expr_type == EXPR_CONSTANT
2448       || args->expr->expr_type == EXPR_OP
2449       || args->expr->expr_type == EXPR_NULL)
2450     {
2451       gfc_error ("Argument to '%s' at %L is not a variable",
2452                  sym->name, &(args->expr->where));
2453       return FAILURE;
2454     }
2455
2456   args_sym = args->expr->symtree->n.sym;
2457
2458   /* The typespec for the actual arg should be that stored in the expr
2459      and not necessarily that of the expr symbol (args_sym), because
2460      the actual expression could be a part-ref of the expr symbol.  */
2461   arg_ts = &(args->expr->ts);
2462
2463   is_pointer = gfc_is_data_pointer (args->expr);
2464     
2465   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2466     {
2467       /* If the user gave two args then they are providing something for
2468          the optional arg (the second cptr).  Therefore, set the name and
2469          binding label to the c_associated for two cptrs.  Otherwise,
2470          set c_associated to expect one cptr.  */
2471       if (args->next)
2472         {
2473           /* two args.  */
2474           sprintf (name, "%s_2", sym->name);
2475           sprintf (binding_label, "%s_2", sym->binding_label);
2476           optional_arg = 1;
2477         }
2478       else
2479         {
2480           /* one arg.  */
2481           sprintf (name, "%s_1", sym->name);
2482           sprintf (binding_label, "%s_1", sym->binding_label);
2483           optional_arg = 0;
2484         }
2485
2486       /* Get a new symbol for the version of c_associated that
2487          will get called.  */
2488       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2489     }
2490   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2491            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2492     {
2493       sprintf (name, "%s", sym->name);
2494       sprintf (binding_label, "%s", sym->binding_label);
2495
2496       /* Error check the call.  */
2497       if (args->next != NULL)
2498         {
2499           gfc_error_now ("More actual than formal arguments in '%s' "
2500                          "call at %L", name, &(args->expr->where));
2501           retval = FAILURE;
2502         }
2503       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2504         {
2505           /* Make sure we have either the target or pointer attribute.  */
2506           if (!args_sym->attr.target && !is_pointer)
2507             {
2508               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2509                              "a TARGET or an associated pointer",
2510                              args_sym->name,
2511                              sym->name, &(args->expr->where));
2512               retval = FAILURE;
2513             }
2514
2515           /* See if we have interoperable type and type param.  */
2516           if (verify_c_interop (arg_ts) == SUCCESS
2517               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2518             {
2519               if (args_sym->attr.target == 1)
2520                 {
2521                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2522                      has the target attribute and is interoperable.  */
2523                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2524                      allocatable variable that has the TARGET attribute and
2525                      is not an array of zero size.  */
2526                   if (args_sym->attr.allocatable == 1)
2527                     {
2528                       if (args_sym->attr.dimension != 0 
2529                           && (args_sym->as && args_sym->as->rank == 0))
2530                         {
2531                           gfc_error_now ("Allocatable variable '%s' used as a "
2532                                          "parameter to '%s' at %L must not be "
2533                                          "an array of zero size",
2534                                          args_sym->name, sym->name,
2535                                          &(args->expr->where));
2536                           retval = FAILURE;
2537                         }
2538                     }
2539                   else
2540                     {
2541                       /* A non-allocatable target variable with C
2542                          interoperable type and type parameters must be
2543                          interoperable.  */
2544                       if (args_sym && args_sym->attr.dimension)
2545                         {
2546                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2547                             {
2548                               gfc_error ("Assumed-shape array '%s' at %L "
2549                                          "cannot be an argument to the "
2550                                          "procedure '%s' because "
2551                                          "it is not C interoperable",
2552                                          args_sym->name,
2553                                          &(args->expr->where), sym->name);
2554                               retval = FAILURE;
2555                             }
2556                           else if (args_sym->as->type == AS_DEFERRED)
2557                             {
2558                               gfc_error ("Deferred-shape array '%s' at %L "
2559                                          "cannot be an argument to the "
2560                                          "procedure '%s' because "
2561                                          "it is not C interoperable",
2562                                          args_sym->name,
2563                                          &(args->expr->where), sym->name);
2564                               retval = FAILURE;
2565                             }
2566                         }
2567                               
2568                       /* Make sure it's not a character string.  Arrays of
2569                          any type should be ok if the variable is of a C
2570                          interoperable type.  */
2571                       if (arg_ts->type == BT_CHARACTER)
2572                         if (arg_ts->u.cl != NULL
2573                             && (arg_ts->u.cl->length == NULL
2574                                 || arg_ts->u.cl->length->expr_type
2575                                    != EXPR_CONSTANT
2576                                 || mpz_cmp_si
2577                                     (arg_ts->u.cl->length->value.integer, 1)
2578                                    != 0)
2579                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2580                           {
2581                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2582                                            "at %L must have a length of 1",
2583                                            args_sym->name, sym->name,
2584                                            &(args->expr->where));
2585                             retval = FAILURE;
2586                           }
2587                     }
2588                 }
2589               else if (is_pointer
2590                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2591                 {
2592                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2593                      scalar pointer.  */
2594                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2595                                  "associated scalar POINTER", args_sym->name,
2596                                  sym->name, &(args->expr->where));
2597                   retval = FAILURE;
2598                 }
2599             }
2600           else
2601             {
2602               /* The parameter is not required to be C interoperable.  If it
2603                  is not C interoperable, it must be a nonpolymorphic scalar
2604                  with no length type parameters.  It still must have either
2605                  the pointer or target attribute, and it can be
2606                  allocatable (but must be allocated when c_loc is called).  */
2607               if (args->expr->rank != 0 
2608                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2609                 {
2610                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2611                                  "scalar", args_sym->name, sym->name,
2612                                  &(args->expr->where));
2613                   retval = FAILURE;
2614                 }
2615               else if (arg_ts->type == BT_CHARACTER 
2616                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2617                 {
2618                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2619                                  "%L must have a length of 1",
2620                                  args_sym->name, sym->name,
2621                                  &(args->expr->where));
2622                   retval = FAILURE;
2623                 }
2624             }
2625         }
2626       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2627         {
2628           if (args_sym->attr.flavor != FL_PROCEDURE)
2629             {
2630               /* TODO: Update this error message to allow for procedure
2631                  pointers once they are implemented.  */
2632               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2633                              "procedure",
2634                              args_sym->name, sym->name,
2635                              &(args->expr->where));
2636               retval = FAILURE;
2637             }
2638           else if (args_sym->attr.is_bind_c != 1)
2639             {
2640               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2641                              "BIND(C)",
2642                              args_sym->name, sym->name,
2643                              &(args->expr->where));
2644               retval = FAILURE;
2645             }
2646         }
2647       
2648       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2649       *new_sym = sym;
2650     }
2651   else
2652     {
2653       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2654                           "iso_c_binding function: '%s'!\n", sym->name);
2655     }
2656
2657   return retval;
2658 }
2659
2660
2661 /* Resolve a function call, which means resolving the arguments, then figuring
2662    out which entity the name refers to.  */
2663 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2664    to INTENT(OUT) or INTENT(INOUT).  */
2665
2666 static gfc_try
2667 resolve_function (gfc_expr *expr)
2668 {
2669   gfc_actual_arglist *arg;
2670   gfc_symbol *sym;
2671   const char *name;
2672   gfc_try t;
2673   int temp;
2674   procedure_type p = PROC_INTRINSIC;
2675   bool no_formal_args;
2676
2677   sym = NULL;
2678   if (expr->symtree)
2679     sym = expr->symtree->n.sym;
2680
2681   /* If this is a procedure pointer component, it has already been resolved.  */
2682   if (gfc_is_proc_ptr_comp (expr, NULL))
2683     return SUCCESS;
2684   
2685   if (sym && sym->attr.intrinsic
2686       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2687     return FAILURE;
2688
2689   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2690     {
2691       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2692       return FAILURE;
2693     }
2694
2695   /* If this ia a deferred TBP with an abstract interface (which may
2696      of course be referenced), expr->value.function.esym will be set.  */
2697   if (sym && sym->attr.abstract && !expr->value.function.esym)
2698     {
2699       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2700                  sym->name, &expr->where);
2701       return FAILURE;
2702     }
2703
2704   /* Switch off assumed size checking and do this again for certain kinds
2705      of procedure, once the procedure itself is resolved.  */
2706   need_full_assumed_size++;
2707
2708   if (expr->symtree && expr->symtree->n.sym)
2709     p = expr->symtree->n.sym->attr.proc;
2710
2711   if (expr->value.function.isym && expr->value.function.isym->inquiry)
2712     inquiry_argument = true;
2713   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2714
2715   if (resolve_actual_arglist (expr->value.function.actual,
2716                               p, no_formal_args) == FAILURE)
2717     {
2718       inquiry_argument = false;
2719       return FAILURE;
2720     }
2721
2722   inquiry_argument = false;
2723  
2724   /* Need to setup the call to the correct c_associated, depending on
2725      the number of cptrs to user gives to compare.  */
2726   if (sym && sym->attr.is_iso_c == 1)
2727     {
2728       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2729           == FAILURE)
2730         return FAILURE;
2731       
2732       /* Get the symtree for the new symbol (resolved func).
2733          the old one will be freed later, when it's no longer used.  */
2734       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2735     }
2736   
2737   /* Resume assumed_size checking.  */
2738   need_full_assumed_size--;
2739
2740   /* If the procedure is external, check for usage.  */
2741   if (sym && is_external_proc (sym))
2742     resolve_global_procedure (sym, &expr->where,
2743                               &expr->value.function.actual, 0);
2744
2745   if (sym && sym->ts.type == BT_CHARACTER
2746       && sym->ts.u.cl
2747       && sym->ts.u.cl->length == NULL
2748       && !sym->attr.dummy
2749       && expr->value.function.esym == NULL
2750       && !sym->attr.contained)
2751     {
2752       /* Internal procedures are taken care of in resolve_contained_fntype.  */
2753       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2754                  "be used at %L since it is not a dummy argument",
2755                  sym->name, &expr->where);
2756       return FAILURE;
2757     }
2758
2759   /* See if function is already resolved.  */
2760
2761   if (expr->value.function.name != NULL)
2762     {
2763       if (expr->ts.type == BT_UNKNOWN)
2764         expr->ts = sym->ts;
2765       t = SUCCESS;
2766     }
2767   else
2768     {
2769       /* Apply the rules of section 14.1.2.  */
2770
2771       switch (procedure_kind (sym))
2772         {
2773         case PTYPE_GENERIC:
2774           t = resolve_generic_f (expr);
2775           break;
2776
2777         case PTYPE_SPECIFIC:
2778           t = resolve_specific_f (expr);
2779           break;
2780
2781         case PTYPE_UNKNOWN:
2782           t = resolve_unknown_f (expr);
2783           break;
2784
2785         default:
2786           gfc_internal_error ("resolve_function(): bad function type");
2787         }
2788     }
2789
2790   /* If the expression is still a function (it might have simplified),
2791      then we check to see if we are calling an elemental function.  */
2792
2793   if (expr->expr_type != EXPR_FUNCTION)
2794     return t;
2795
2796   temp = need_full_assumed_size;
2797   need_full_assumed_size = 0;
2798
2799   if (resolve_elemental_actual (expr, NULL) == FAILURE)
2800     return FAILURE;
2801
2802   if (omp_workshare_flag
2803       && expr->value.function.esym
2804       && ! gfc_elemental (expr->value.function.esym))
2805     {
2806       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2807                  "in WORKSHARE construct", expr->value.function.esym->name,
2808                  &expr->where);
2809       t = FAILURE;
2810     }
2811
2812 #define GENERIC_ID expr->value.function.isym->id
2813   else if (expr->value.function.actual != NULL
2814            && expr->value.function.isym != NULL
2815            && GENERIC_ID != GFC_ISYM_LBOUND
2816            && GENERIC_ID != GFC_ISYM_LEN
2817            && GENERIC_ID != GFC_ISYM_LOC
2818            && GENERIC_ID != GFC_ISYM_PRESENT)
2819     {
2820       /* Array intrinsics must also have the last upper bound of an
2821          assumed size array argument.  UBOUND and SIZE have to be
2822          excluded from the check if the second argument is anything
2823          than a constant.  */
2824
2825       for (arg = expr->value.function.actual; arg; arg = arg->next)
2826         {
2827           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
2828               && arg->next != NULL && arg->next->expr)
2829             {
2830               if (arg->next->expr->expr_type != EXPR_CONSTANT)
2831                 break;
2832
2833               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
2834                 break;
2835
2836               if ((int)mpz_get_si (arg->next->expr->value.integer)
2837                         < arg->expr->rank)
2838                 break;
2839             }
2840
2841           if (arg->expr != NULL
2842               && arg->expr->rank > 0
2843               && resolve_assumed_size_actual (arg->expr))
2844             return FAILURE;
2845         }
2846     }
2847 #undef GENERIC_ID
2848
2849   need_full_assumed_size = temp;
2850   name = NULL;
2851
2852   if (!pure_function (expr, &name) && name)
2853     {
2854       if (forall_flag)
2855         {
2856           gfc_error ("reference to non-PURE function '%s' at %L inside a "
2857                      "FORALL %s", name, &expr->where,
2858                      forall_flag == 2 ? "mask" : "block");
2859           t = FAILURE;
2860         }
2861       else if (gfc_pure (NULL))
2862         {
2863           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2864                      "procedure within a PURE procedure", name, &expr->where);
2865           t = FAILURE;
2866         }
2867     }
2868
2869   /* Functions without the RECURSIVE attribution are not allowed to
2870    * call themselves.  */
2871   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2872     {
2873       gfc_symbol *esym;
2874       esym = expr->value.function.esym;
2875
2876       if (is_illegal_recursion (esym, gfc_current_ns))
2877       {
2878         if (esym->attr.entry && esym->ns->entries)
2879           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
2880                      " function '%s' is not RECURSIVE",
2881                      esym->name, &expr->where, esym->ns->entries->sym->name);
2882         else
2883           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
2884                      " is not RECURSIVE", esym->name, &expr->where);
2885
2886         t = FAILURE;
2887       }
2888     }
2889
2890   /* Character lengths of use associated functions may contains references to
2891      symbols not referenced from the current program unit otherwise.  Make sure
2892      those symbols are marked as referenced.  */
2893
2894   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2895       && expr->value.function.esym->attr.use_assoc)
2896     {
2897       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
2898     }
2899
2900   if (t == SUCCESS
2901         && !((expr->value.function.esym
2902                 && expr->value.function.esym->attr.elemental)
2903                         ||
2904              (expr->value.function.isym
2905                 && expr->value.function.isym->elemental)))
2906     find_noncopying_intrinsics (expr->value.function.esym,
2907                                 expr->value.function.actual);
2908
2909   /* Make sure that the expression has a typespec that works.  */
2910   if (expr->ts.type == BT_UNKNOWN)
2911     {
2912       if (expr->symtree->n.sym->result
2913             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
2914             && !expr->symtree->n.sym->result->attr.proc_pointer)
2915         expr->ts = expr->symtree->n.sym->result->ts;
2916     }
2917
2918   return t;
2919 }
2920
2921
2922 /************* Subroutine resolution *************/
2923
2924 static void
2925 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2926 {
2927   if (gfc_pure (sym))
2928     return;
2929
2930   if (forall_flag)
2931     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2932                sym->name, &c->loc);
2933   else if (gfc_pure (NULL))
2934     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2935                &c->loc);
2936 }
2937
2938
2939 static match
2940 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2941 {
2942   gfc_symbol *s;
2943
2944   if (sym->attr.generic)
2945     {
2946       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2947       if (s != NULL)
2948         {
2949           c->resolved_sym = s;
2950           pure_subroutine (c, s);
2951           return MATCH_YES;
2952         }
2953
2954       /* TODO: Need to search for elemental references in generic interface.  */
2955     }
2956
2957   if (sym->attr.intrinsic)
2958     return gfc_intrinsic_sub_interface (c, 0);
2959
2960   return MATCH_NO;
2961 }
2962
2963
2964 static gfc_try
2965 resolve_generic_s (gfc_code *c)
2966 {
2967   gfc_symbol *sym;
2968   match m;
2969
2970   sym = c->symtree->n.sym;
2971
2972   for (;;)
2973     {
2974       m = resolve_generic_s0 (c, sym);
2975       if (m == MATCH_YES)
2976         return SUCCESS;
2977       else if (m == MATCH_ERROR)
2978         return FAILURE;
2979
2980 generic:
2981       if (sym->ns->parent == NULL)
2982         break;
2983       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2984
2985       if (sym == NULL)
2986         break;
2987       if (!generic_sym (sym))
2988         goto generic;
2989     }
2990
2991   /* Last ditch attempt.  See if the reference is to an intrinsic
2992      that possesses a matching interface.  14.1.2.4  */
2993   sym = c->symtree->n.sym;
2994
2995   if (!gfc_is_intrinsic (sym, 1, c->loc))
2996     {
2997       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2998                  sym->name, &c->loc);
2999       return FAILURE;
3000     }
3001
3002   m = gfc_intrinsic_sub_interface (c, 0);
3003   if (m == MATCH_YES)
3004     return SUCCESS;
3005   if (m == MATCH_NO)
3006     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3007                "intrinsic subroutine interface", sym->name, &c->loc);
3008
3009   return FAILURE;
3010 }
3011
3012
3013 /* Set the name and binding label of the subroutine symbol in the call
3014    expression represented by 'c' to include the type and kind of the
3015    second parameter.  This function is for resolving the appropriate
3016    version of c_f_pointer() and c_f_procpointer().  For example, a
3017    call to c_f_pointer() for a default integer pointer could have a
3018    name of c_f_pointer_i4.  If no second arg exists, which is an error
3019    for these two functions, it defaults to the generic symbol's name
3020    and binding label.  */
3021
3022 static void
3023 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3024                     char *name, char *binding_label)
3025 {
3026   gfc_expr *arg = NULL;
3027   char type;
3028   int kind;
3029
3030   /* The second arg of c_f_pointer and c_f_procpointer determines
3031      the type and kind for the procedure name.  */
3032   arg = c->ext.actual->next->expr;
3033
3034   if (arg != NULL)
3035     {
3036       /* Set up the name to have the given symbol's name,
3037          plus the type and kind.  */
3038       /* a derived type is marked with the type letter 'u' */
3039       if (arg->ts.type == BT_DERIVED)
3040         {
3041           type = 'd';
3042           kind = 0; /* set the kind as 0 for now */
3043         }
3044       else
3045         {
3046           type = gfc_type_letter (arg->ts.type);
3047           kind = arg->ts.kind;
3048         }
3049
3050       if (arg->ts.type == BT_CHARACTER)
3051         /* Kind info for character strings not needed.  */
3052         kind = 0;
3053
3054       sprintf (name, "%s_%c%d", sym->name, type, kind);
3055       /* Set up the binding label as the given symbol's label plus
3056          the type and kind.  */
3057       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
3058     }
3059   else
3060     {
3061       /* If the second arg is missing, set the name and label as
3062          was, cause it should at least be found, and the missing
3063          arg error will be caught by compare_parameters().  */
3064       sprintf (name, "%s", sym->name);
3065       sprintf (binding_label, "%s", sym->binding_label);
3066     }
3067    
3068   return;
3069 }
3070
3071
3072 /* Resolve a generic version of the iso_c_binding procedure given
3073    (sym) to the specific one based on the type and kind of the
3074    argument(s).  Currently, this function resolves c_f_pointer() and
3075    c_f_procpointer based on the type and kind of the second argument
3076    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3077    Upon successfully exiting, c->resolved_sym will hold the resolved
3078    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3079    otherwise.  */
3080
3081 match
3082 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3083 {
3084   gfc_symbol *new_sym;
3085   /* this is fine, since we know the names won't use the max */
3086   char name[GFC_MAX_SYMBOL_LEN + 1];
3087   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3088   /* default to success; will override if find error */
3089   match m = MATCH_YES;
3090
3091   /* Make sure the actual arguments are in the necessary order (based on the 
3092      formal args) before resolving.  */
3093   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3094
3095   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3096       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3097     {
3098       set_name_and_label (c, sym, name, binding_label);
3099       
3100       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3101         {
3102           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3103             {
3104               /* Make sure we got a third arg if the second arg has non-zero
3105                  rank.  We must also check that the type and rank are
3106                  correct since we short-circuit this check in
3107                  gfc_procedure_use() (called above to sort actual args).  */
3108               if (c->ext.actual->next->expr->rank != 0)
3109                 {
3110                   if(c->ext.actual->next->next == NULL 
3111                      || c->ext.actual->next->next->expr == NULL)
3112                     {
3113                       m = MATCH_ERROR;
3114                       gfc_error ("Missing SHAPE parameter for call to %s "
3115                                  "at %L", sym->name, &(c->loc));
3116                     }
3117                   else if (c->ext.actual->next->next->expr->ts.type
3118                            != BT_INTEGER
3119                            || c->ext.actual->next->next->expr->rank != 1)
3120                     {
3121                       m = MATCH_ERROR;
3122                       gfc_error ("SHAPE parameter for call to %s at %L must "
3123                                  "be a rank 1 INTEGER array", sym->name,
3124                                  &(c->loc));
3125                     }
3126                 }
3127             }
3128         }
3129       
3130       if (m != MATCH_ERROR)
3131         {
3132           /* the 1 means to add the optional arg to formal list */
3133           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3134          
3135           /* for error reporting, say it's declared where the original was */
3136           new_sym->declared_at = sym->declared_at;
3137         }
3138     }
3139   else
3140     {
3141       /* no differences for c_loc or c_funloc */
3142       new_sym = sym;
3143     }
3144
3145   /* set the resolved symbol */
3146   if (m != MATCH_ERROR)
3147     c->resolved_sym = new_sym;
3148   else
3149     c->resolved_sym = sym;
3150   
3151   return m;
3152 }
3153
3154
3155 /* Resolve a subroutine call known to be specific.  */
3156
3157 static match
3158 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3159 {
3160   match m;
3161
3162   if(sym->attr.is_iso_c)
3163     {
3164       m = gfc_iso_c_sub_interface (c,sym);
3165       return m;
3166     }
3167   
3168   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3169     {
3170       if (sym->attr.dummy)
3171         {
3172           sym->attr.proc = PROC_DUMMY;
3173           goto found;
3174         }
3175
3176       sym->attr.proc = PROC_EXTERNAL;
3177       goto found;
3178     }
3179
3180   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3181     goto found;
3182
3183   if (sym->attr.intrinsic)
3184     {
3185       m = gfc_intrinsic_sub_interface (c, 1);
3186       if (m == MATCH_YES)
3187         return MATCH_YES;
3188       if (m == MATCH_NO)
3189         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3190                    "with an intrinsic", sym->name, &c->loc);
3191
3192       return MATCH_ERROR;
3193     }
3194
3195   return MATCH_NO;
3196
3197 found:
3198   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3199
3200   c->resolved_sym = sym;
3201   pure_subroutine (c, sym);
3202
3203   return MATCH_YES;
3204 }
3205
3206
3207 static gfc_try
3208 resolve_specific_s (gfc_code *c)
3209 {
3210   gfc_symbol *sym;
3211   match m;
3212
3213   sym = c->symtree->n.sym;
3214
3215   for (;;)
3216     {
3217       m = resolve_specific_s0 (c, sym);
3218       if (m == MATCH_YES)
3219         return SUCCESS;
3220       if (m == MATCH_ERROR)
3221         return FAILURE;
3222
3223       if (sym->ns->parent == NULL)
3224         break;
3225
3226       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3227
3228       if (sym == NULL)
3229         break;
3230     }
3231
3232   sym = c->symtree->n.sym;
3233   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3234              sym->name, &c->loc);
3235
3236   return FAILURE;
3237 }
3238
3239
3240 /* Resolve a subroutine call not known to be generic nor specific.  */
3241
3242 static gfc_try
3243 resolve_unknown_s (gfc_code *c)
3244 {
3245   gfc_symbol *sym;
3246
3247   sym = c->symtree->n.sym;
3248
3249   if (sym->attr.dummy)
3250     {
3251       sym->attr.proc = PROC_DUMMY;
3252       goto found;
3253     }
3254
3255   /* See if we have an intrinsic function reference.  */
3256
3257   if (gfc_is_intrinsic (sym, 1, c->loc))
3258     {
3259       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3260         return SUCCESS;
3261       return FAILURE;
3262     }
3263
3264   /* The reference is to an external name.  */
3265
3266 found:
3267   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3268
3269   c->resolved_sym = sym;
3270
3271   pure_subroutine (c, sym);
3272
3273   return SUCCESS;
3274 }
3275
3276
3277 /* Resolve a subroutine call.  Although it was tempting to use the same code
3278    for functions, subroutines and functions are stored differently and this
3279    makes things awkward.  */
3280
3281 static gfc_try
3282 resolve_call (gfc_code *c)
3283 {
3284   gfc_try t;
3285   procedure_type ptype = PROC_INTRINSIC;
3286   gfc_symbol *csym, *sym;
3287   bool no_formal_args;
3288
3289   csym = c->symtree ? c->symtree->n.sym : NULL;
3290
3291   if (csym && csym->ts.type != BT_UNKNOWN)
3292     {
3293       gfc_error ("'%s' at %L has a type, which is not consistent with "
3294                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3295       return FAILURE;
3296     }
3297
3298   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3299     {
3300       gfc_symtree *st;
3301       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3302       sym = st ? st->n.sym : NULL;
3303       if (sym && csym != sym
3304               && sym->ns == gfc_current_ns
3305               && sym->attr.flavor == FL_PROCEDURE
3306               && sym->attr.contained)
3307         {
3308           sym->refs++;
3309           if (csym->attr.generic)
3310             c->symtree->n.sym = sym;
3311           else
3312             c->symtree = st;
3313           csym = c->symtree->n.sym;
3314         }
3315     }
3316
3317   /* If this ia a deferred TBP with an abstract interface
3318      (which may of course be referenced), c->expr1 will be set.  */
3319   if (csym && csym->attr.abstract && !c->expr1)
3320     {
3321       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3322                  csym->name, &c->loc);
3323       return FAILURE;
3324     }
3325
3326   /* Subroutines without the RECURSIVE attribution are not allowed to
3327    * call themselves.  */
3328   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3329     {
3330       if (csym->attr.entry && csym->ns->entries)
3331         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3332                    " subroutine '%s' is not RECURSIVE",
3333                    csym->name, &c->loc, csym->ns->entries->sym->name);
3334       else
3335         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3336                    " is not RECURSIVE", csym->name, &c->loc);
3337
3338       t = FAILURE;
3339     }
3340
3341   /* Switch off assumed size checking and do this again for certain kinds
3342      of procedure, once the procedure itself is resolved.  */
3343   need_full_assumed_size++;
3344
3345   if (csym)
3346     ptype = csym->attr.proc;
3347
3348   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3349   if (resolve_actual_arglist (c->ext.actual, ptype,
3350                               no_formal_args) == FAILURE)
3351     return FAILURE;
3352
3353   /* Resume assumed_size checking.  */
3354   need_full_assumed_size--;
3355
3356   /* If external, check for usage.  */
3357   if (csym && is_external_proc (csym))
3358     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3359
3360   t = SUCCESS;
3361   if (c->resolved_sym == NULL)
3362     {
3363       c->resolved_isym = NULL;
3364       switch (procedure_kind (csym))
3365         {
3366         case PTYPE_GENERIC:
3367           t = resolve_generic_s (c);
3368           break;
3369
3370         case PTYPE_SPECIFIC:
3371           t = resolve_specific_s (c);
3372           break;
3373
3374         case PTYPE_UNKNOWN:
3375           t = resolve_unknown_s (c);
3376           break;
3377
3378         default:
3379           gfc_internal_error ("resolve_subroutine(): bad function type");
3380         }
3381     }
3382
3383   /* Some checks of elemental subroutine actual arguments.  */
3384   if (resolve_elemental_actual (NULL, c) == FAILURE)
3385     return FAILURE;
3386
3387   if (t == SUCCESS && !(c->resolved_sym && c->resolved_sym->attr.elemental))
3388     find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
3389   return t;
3390 }
3391
3392
3393 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3394    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3395    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3396    if their shapes do not match.  If either op1->shape or op2->shape is
3397    NULL, return SUCCESS.  */
3398
3399 static gfc_try
3400 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3401 {
3402   gfc_try t;
3403   int i;
3404
3405   t = SUCCESS;
3406
3407   if (op1->shape != NULL && op2->shape != NULL)
3408     {
3409       for (i = 0; i < op1->rank; i++)
3410         {
3411           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3412            {
3413              gfc_error ("Shapes for operands at %L and %L are not conformable",
3414                          &op1->where, &op2->where);
3415              t = FAILURE;
3416              break;
3417            }
3418         }
3419     }
3420
3421   return t;
3422 }
3423
3424
3425 /* Resolve an operator expression node.  This can involve replacing the
3426    operation with a user defined function call.  */
3427
3428 static gfc_try
3429 resolve_operator (gfc_expr *e)
3430 {
3431   gfc_expr *op1, *op2;
3432   char msg[200];
3433   bool dual_locus_error;
3434   gfc_try t;
3435
3436   /* Resolve all subnodes-- give them types.  */
3437
3438   switch (e->value.op.op)
3439     {
3440     default:
3441       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3442         return FAILURE;
3443
3444     /* Fall through...  */
3445
3446     case INTRINSIC_NOT:
3447     case INTRINSIC_UPLUS:
3448     case INTRINSIC_UMINUS:
3449     case INTRINSIC_PARENTHESES:
3450       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3451         return FAILURE;
3452       break;
3453     }
3454
3455   /* Typecheck the new node.  */
3456
3457   op1 = e->value.op.op1;
3458   op2 = e->value.op.op2;
3459   dual_locus_error = false;
3460
3461   if ((op1 && op1->expr_type == EXPR_NULL)
3462       || (op2 && op2->expr_type == EXPR_NULL))
3463     {
3464       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3465       goto bad_op;
3466     }
3467
3468   switch (e->value.op.op)
3469     {
3470     case INTRINSIC_UPLUS:
3471     case INTRINSIC_UMINUS:
3472       if (op1->ts.type == BT_INTEGER
3473           || op1->ts.type == BT_REAL
3474           || op1->ts.type == BT_COMPLEX)
3475         {
3476           e->ts = op1->ts;
3477           break;
3478         }
3479
3480       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3481                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3482       goto bad_op;
3483
3484     case INTRINSIC_PLUS:
3485     case INTRINSIC_MINUS:
3486     case INTRINSIC_TIMES:
3487     case INTRINSIC_DIVIDE:
3488     case INTRINSIC_POWER:
3489       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3490         {
3491           gfc_type_convert_binary (e, 1);
3492           break;
3493         }
3494
3495       sprintf (msg,
3496                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3497                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3498                gfc_typename (&op2->ts));
3499       goto bad_op;
3500
3501     case INTRINSIC_CONCAT:
3502       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3503           && op1->ts.kind == op2->ts.kind)
3504         {
3505           e->ts.type = BT_CHARACTER;
3506           e->ts.kind = op1->ts.kind;
3507           break;
3508         }
3509
3510       sprintf (msg,
3511                _("Operands of string concatenation operator at %%L are %s/%s"),
3512                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3513       goto bad_op;
3514
3515     case INTRINSIC_AND:
3516     case INTRINSIC_OR:
3517     case INTRINSIC_EQV:
3518     case INTRINSIC_NEQV:
3519       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3520         {
3521           e->ts.type = BT_LOGICAL;
3522           e->ts.kind = gfc_kind_max (op1, op2);
3523           if (op1->ts.kind < e->ts.kind)
3524             gfc_convert_type (op1, &e->ts, 2);
3525           else if (op2->ts.kind < e->ts.kind)
3526             gfc_convert_type (op2, &e->ts, 2);
3527           break;
3528         }
3529
3530       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3531                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3532                gfc_typename (&op2->ts));
3533
3534       goto bad_op;
3535
3536     case INTRINSIC_NOT:
3537       if (op1->ts.type == BT_LOGICAL)
3538         {
3539           e->ts.type = BT_LOGICAL;
3540           e->ts.kind = op1->ts.kind;
3541           break;
3542         }
3543
3544       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3545                gfc_typename (&op1->ts));
3546       goto bad_op;
3547
3548     case INTRINSIC_GT:
3549     case INTRINSIC_GT_OS:
3550     case INTRINSIC_GE:
3551     case INTRINSIC_GE_OS:
3552     case INTRINSIC_LT:
3553     case INTRINSIC_LT_OS:
3554     case INTRINSIC_LE:
3555     case INTRINSIC_LE_OS:
3556       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3557         {
3558           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3559           goto bad_op;
3560         }
3561
3562       /* Fall through...  */
3563
3564     case INTRINSIC_EQ:
3565     case INTRINSIC_EQ_OS:
3566     case INTRINSIC_NE:
3567     case INTRINSIC_NE_OS:
3568       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3569           && op1->ts.kind == op2->ts.kind)
3570         {
3571           e->ts.type = BT_LOGICAL;
3572           e->ts.kind = gfc_default_logical_kind;
3573           break;
3574         }
3575
3576       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3577         {
3578           gfc_type_convert_binary (e, 1);
3579
3580           e->ts.type = BT_LOGICAL;
3581           e->ts.kind = gfc_default_logical_kind;
3582           break;
3583         }
3584
3585       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3586         sprintf (msg,
3587                  _("Logicals at %%L must be compared with %s instead of %s"),
3588                  (e->value.op.op == INTRINSIC_EQ 
3589                   || e->value.op.op == INTRINSIC_EQ_OS)
3590                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3591       else
3592         sprintf (msg,
3593                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3594                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3595                  gfc_typename (&op2->ts));
3596
3597       goto bad_op;
3598
3599     case INTRINSIC_USER:
3600       if (e->value.op.uop->op == NULL)
3601         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3602       else if (op2 == NULL)
3603         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3604                  e->value.op.uop->name, gfc_typename (&op1->ts));
3605       else
3606         sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3607                  e->value.op.uop->name, gfc_typename (&op1->ts),
3608                  gfc_typename (&op2->ts));
3609
3610       goto bad_op;
3611
3612     case INTRINSIC_PARENTHESES:
3613       e->ts = op1->ts;
3614       if (e->ts.type == BT_CHARACTER)
3615         e->ts.u.cl = op1->ts.u.cl;
3616       break;
3617
3618     default:
3619       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3620     }
3621
3622   /* Deal with arrayness of an operand through an operator.  */
3623
3624   t = SUCCESS;
3625
3626   switch (e->value.op.op)
3627     {
3628     case INTRINSIC_PLUS:
3629     case INTRINSIC_MINUS:
3630     case INTRINSIC_TIMES:
3631     case INTRINSIC_DIVIDE:
3632     case INTRINSIC_POWER:
3633     case INTRINSIC_CONCAT:
3634     case INTRINSIC_AND:
3635     case INTRINSIC_OR:
3636     case INTRINSIC_EQV:
3637     case INTRINSIC_NEQV:
3638     case INTRINSIC_EQ:
3639     case INTRINSIC_EQ_OS:
3640     case INTRINSIC_NE:
3641     case INTRINSIC_NE_OS:
3642     case INTRINSIC_GT:
3643     case INTRINSIC_GT_OS:
3644     case INTRINSIC_GE:
3645     case INTRINSIC_GE_OS:
3646     case INTRINSIC_LT:
3647     case INTRINSIC_LT_OS:
3648     case INTRINSIC_LE:
3649     case INTRINSIC_LE_OS:
3650
3651       if (op1->rank == 0 && op2->rank == 0)
3652         e->rank = 0;
3653
3654       if (op1->rank == 0 && op2->rank != 0)
3655         {
3656           e->rank = op2->rank;
3657
3658           if (e->shape == NULL)
3659             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3660         }
3661
3662       if (op1->rank != 0 && op2->rank == 0)
3663         {
3664           e->rank = op1->rank;
3665
3666           if (e->shape == NULL)
3667             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3668         }
3669
3670       if (op1->rank != 0 && op2->rank != 0)
3671         {
3672           if (op1->rank == op2->rank)
3673             {
3674               e->rank = op1->rank;
3675               if (e->shape == NULL)
3676                 {
3677                   t = compare_shapes (op1, op2);
3678                   if (t == FAILURE)
3679                     e->shape = NULL;
3680                   else
3681                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
3682                 }
3683             }
3684           else
3685             {
3686               /* Allow higher level expressions to work.  */
3687               e->rank = 0;
3688
3689               /* Try user-defined operators, and otherwise throw an error.  */
3690               dual_locus_error = true;
3691               sprintf (msg,
3692                        _("Inconsistent ranks for operator at %%L and %%L"));
3693               goto bad_op;
3694             }
3695         }
3696
3697       break;
3698
3699     case INTRINSIC_PARENTHESES:
3700     case INTRINSIC_NOT:
3701     case INTRINSIC_UPLUS:
3702     case INTRINSIC_UMINUS:
3703       /* Simply copy arrayness attribute */
3704       e->rank = op1->rank;
3705
3706       if (e->shape == NULL)
3707         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3708
3709       break;
3710
3711     default:
3712       break;
3713     }
3714
3715   /* Attempt to simplify the expression.  */
3716   if (t == SUCCESS)
3717     {
3718       t = gfc_simplify_expr (e, 0);
3719       /* Some calls do not succeed in simplification and return FAILURE
3720          even though there is no error; e.g. variable references to
3721          PARAMETER arrays.  */
3722       if (!gfc_is_constant_expr (e))
3723         t = SUCCESS;
3724     }
3725   return t;
3726
3727 bad_op:
3728
3729   {
3730     bool real_error;
3731     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3732       return SUCCESS;
3733
3734     if (real_error)
3735       return FAILURE;
3736   }
3737
3738   if (dual_locus_error)
3739     gfc_error (msg, &op1->where, &op2->where);
3740   else
3741     gfc_error (msg, &e->where);
3742
3743   return FAILURE;
3744 }
3745
3746
3747 /************** Array resolution subroutines **************/
3748
3749 typedef enum
3750 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3751 comparison;
3752
3753 /* Compare two integer expressions.  */
3754
3755 static comparison
3756 compare_bound (gfc_expr *a, gfc_expr *b)
3757 {
3758   int i;
3759
3760   if (a == NULL || a->expr_type != EXPR_CONSTANT
3761       || b == NULL || b->expr_type != EXPR_CONSTANT)
3762     return CMP_UNKNOWN;
3763
3764   /* If either of the types isn't INTEGER, we must have
3765      raised an error earlier.  */
3766
3767   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3768     return CMP_UNKNOWN;
3769
3770   i = mpz_cmp (a->value.integer, b->value.integer);
3771
3772   if (i < 0)
3773     return CMP_LT;
3774   if (i > 0)
3775     return CMP_GT;
3776   return CMP_EQ;
3777 }
3778
3779
3780 /* Compare an integer expression with an integer.  */
3781
3782 static comparison
3783 compare_bound_int (gfc_expr *a, int b)
3784 {
3785   int i;
3786
3787   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3788     return CMP_UNKNOWN;
3789
3790   if (a->ts.type != BT_INTEGER)
3791     gfc_internal_error ("compare_bound_int(): Bad expression");
3792
3793   i = mpz_cmp_si (a->value.integer, b);
3794
3795   if (i < 0)
3796     return CMP_LT;
3797   if (i > 0)
3798     return CMP_GT;
3799   return CMP_EQ;
3800 }
3801
3802
3803 /* Compare an integer expression with a mpz_t.  */
3804
3805 static comparison
3806 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3807 {
3808   int i;
3809
3810   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3811     return CMP_UNKNOWN;
3812
3813   if (a->ts.type != BT_INTEGER)
3814     gfc_internal_error ("compare_bound_int(): Bad expression");
3815
3816   i = mpz_cmp (a->value.integer, b);
3817
3818   if (i < 0)
3819     return CMP_LT;
3820   if (i > 0)
3821     return CMP_GT;
3822   return CMP_EQ;
3823 }
3824
3825
3826 /* Compute the last value of a sequence given by a triplet.  
3827    Return 0 if it wasn't able to compute the last value, or if the
3828    sequence if empty, and 1 otherwise.  */
3829
3830 static int
3831 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
3832                                 gfc_expr *stride, mpz_t last)
3833 {
3834   mpz_t rem;
3835
3836   if (start == NULL || start->expr_type != EXPR_CONSTANT
3837       || end == NULL || end->expr_type != EXPR_CONSTANT
3838       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
3839     return 0;
3840
3841   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
3842       || (stride != NULL && stride->ts.type != BT_INTEGER))
3843     return 0;
3844
3845   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
3846     {
3847       if (compare_bound (start, end) == CMP_GT)
3848         return 0;
3849       mpz_set (last, end->value.integer);
3850       return 1;
3851     }
3852
3853   if (compare_bound_int (stride, 0) == CMP_GT)
3854     {
3855       /* Stride is positive */
3856       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
3857         return 0;
3858     }
3859   else
3860     {
3861       /* Stride is negative */
3862       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
3863         return 0;
3864     }
3865
3866   mpz_init (rem);
3867   mpz_sub (rem, end->value.integer, start->value.integer);
3868   mpz_tdiv_r (rem, rem, stride->value.integer);
3869   mpz_sub (last, end->value.integer, rem);
3870   mpz_clear (rem);
3871
3872   return 1;
3873 }
3874
3875
3876 /* Compare a single dimension of an array reference to the array
3877    specification.  */
3878
3879 static gfc_try
3880 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
3881 {
3882   mpz_t last_value;
3883
3884   if (ar->dimen_type[i] == DIMEN_STAR)
3885     {
3886       gcc_assert (ar->stride[i] == NULL);
3887       /* This implies [*] as [*:] and [*:3] are not possible.  */
3888       if (ar->start[i] == NULL)
3889         {
3890           gcc_assert (ar->end[i] == NULL);
3891           return SUCCESS;
3892         }
3893     }
3894
3895 /* Given start, end and stride values, calculate the minimum and
3896    maximum referenced indexes.  */
3897
3898   switch (ar->dimen_type[i])
3899     {
3900     case DIMEN_VECTOR:
3901       break;
3902
3903     case DIMEN_STAR:
3904     case DIMEN_ELEMENT:
3905       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
3906         {
3907           if (i < as->rank)
3908             gfc_warning ("Array reference at %L is out of bounds "
3909                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
3910                          mpz_get_si (ar->start[i]->value.integer),
3911                          mpz_get_si (as->lower[i]->value.integer), i+1);
3912           else
3913             gfc_warning ("Array reference at %L is out of bounds "
3914                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
3915                          mpz_get_si (ar->start[i]->value.integer),
3916                          mpz_get_si (as->lower[i]->value.integer),
3917                          i + 1 - as->rank);
3918           return SUCCESS;
3919         }
3920       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
3921         {
3922           if (i < as->rank)
3923             gfc_warning ("Array reference at %L is out of bounds "
3924                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
3925                          mpz_get_si (ar->start[i]->value.integer),
3926                          mpz_get_si (as->upper[i]->value.integer), i+1);
3927           else
3928             gfc_warning ("Array reference at %L is out of bounds "
3929                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
3930                          mpz_get_si (ar->start[i]->value.integer),
3931                          mpz_get_si (as->upper[i]->value.integer),
3932                          i + 1 - as->rank);
3933           return SUCCESS;
3934         }
3935
3936       break;
3937
3938     case DIMEN_RANGE:
3939       {
3940 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
3941 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
3942
3943         comparison comp_start_end = compare_bound (AR_START, AR_END);
3944
3945         /* Check for zero stride, which is not allowed.  */
3946         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
3947           {
3948             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
3949             return FAILURE;
3950           }
3951
3952         /* if start == len || (stride > 0 && start < len)
3953                            || (stride < 0 && start > len),
3954            then the array section contains at least one element.  In this
3955            case, there is an out-of-bounds access if
3956            (start < lower || start > upper).  */
3957         if (compare_bound (AR_START, AR_END) == CMP_EQ
3958             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
3959                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
3960             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
3961                 && comp_start_end == CMP_GT))
3962           {
3963             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
3964               {
3965                 gfc_warning ("Lower array reference at %L is out of bounds "
3966                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3967                        mpz_get_si (AR_START->value.integer),
3968                        mpz_get_si (as->lower[i]->value.integer), i+1);
3969                 return SUCCESS;
3970               }
3971             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
3972               {
3973                 gfc_warning ("Lower array reference at %L is out of bounds "
3974                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3975                        mpz_get_si (AR_START->value.integer),
3976                        mpz_get_si (as->upper[i]->value.integer), i+1);
3977                 return SUCCESS;
3978               }
3979           }
3980
3981         /* If we can compute the highest index of the array section,
3982            then it also has to be between lower and upper.  */
3983         mpz_init (last_value);
3984         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
3985                                             last_value))
3986           {
3987             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
3988               {
3989                 gfc_warning ("Upper array reference at %L is out of bounds "
3990                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3991                        mpz_get_si (last_value),
3992                        mpz_get_si (as->lower[i]->value.integer), i+1);
3993                 mpz_clear (last_value);
3994                 return SUCCESS;
3995               }
3996             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
3997               {
3998                 gfc_warning ("Upper array reference at %L is out of bounds "
3999                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4000                        mpz_get_si (last_value),
4001                        mpz_get_si (as->upper[i]->value.integer), i+1);
4002                 mpz_clear (last_value);
4003                 return SUCCESS;
4004               }
4005           }
4006         mpz_clear (last_value);
4007
4008 #undef AR_START
4009 #undef AR_END
4010       }
4011       break;
4012
4013     default:
4014       gfc_internal_error ("check_dimension(): Bad array reference");
4015     }
4016
4017   return SUCCESS;
4018 }
4019
4020
4021 /* Compare an array reference with an array specification.  */
4022
4023 static gfc_try
4024 compare_spec_to_ref (gfc_array_ref *ar)
4025 {
4026   gfc_array_spec *as;
4027   int i;
4028
4029   as = ar->as;
4030   i = as->rank - 1;
4031   /* TODO: Full array sections are only allowed as actual parameters.  */
4032   if (as->type == AS_ASSUMED_SIZE
4033       && (/*ar->type == AR_FULL
4034           ||*/ (ar->type == AR_SECTION
4035               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4036     {
4037       gfc_error ("Rightmost upper bound of assumed size array section "
4038                  "not specified at %L", &ar->where);
4039       return FAILURE;
4040     }
4041
4042   if (ar->type == AR_FULL)
4043     return SUCCESS;
4044
4045   if (as->rank != ar->dimen)
4046     {
4047       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4048                  &ar->where, ar->dimen, as->rank);
4049       return FAILURE;
4050     }
4051
4052   /* ar->codimen == 0 is a local array.  */
4053   if (as->corank != ar->codimen && ar->codimen != 0)
4054     {
4055       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4056                  &ar->where, ar->codimen, as->corank);
4057       return FAILURE;
4058     }
4059
4060   for (i = 0; i < as->rank; i++)
4061     if (check_dimension (i, ar, as) == FAILURE)
4062       return FAILURE;
4063
4064   /* Local access has no coarray spec.  */
4065   if (ar->codimen != 0)
4066     for (i = as->rank; i < as->rank + as->corank; i++)
4067       {
4068         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate)
4069           {
4070             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4071                        i + 1 - as->rank, &ar->where);
4072             return FAILURE;
4073           }
4074         if (check_dimension (i, ar, as) == FAILURE)
4075           return FAILURE;
4076       }
4077
4078   return SUCCESS;
4079 }
4080
4081
4082 /* Resolve one part of an array index.  */
4083
4084 static gfc_try
4085 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4086                      int force_index_integer_kind)
4087 {
4088   gfc_typespec ts;
4089
4090   if (index == NULL)
4091     return SUCCESS;
4092
4093   if (gfc_resolve_expr (index) == FAILURE)
4094     return FAILURE;
4095
4096   if (check_scalar && index->rank != 0)
4097     {
4098       gfc_error ("Array index at %L must be scalar", &index->where);
4099       return FAILURE;
4100     }
4101
4102   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4103     {
4104       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4105                  &index->where, gfc_basic_typename (index->ts.type));
4106       return FAILURE;
4107     }
4108
4109   if (index->ts.type == BT_REAL)
4110     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4111                         &index->where) == FAILURE)
4112       return FAILURE;
4113
4114   if ((index->ts.kind != gfc_index_integer_kind
4115        && force_index_integer_kind)
4116       || index->ts.type != BT_INTEGER)
4117     {
4118       gfc_clear_ts (&ts);
4119       ts.type = BT_INTEGER;
4120       ts.kind = gfc_index_integer_kind;
4121
4122       gfc_convert_type_warn (index, &ts, 2, 0);
4123     }
4124
4125   return SUCCESS;
4126 }
4127
4128 /* Resolve one part of an array index.  */
4129
4130 gfc_try
4131 gfc_resolve_index (gfc_expr *index, int check_scalar)
4132 {
4133   return gfc_resolve_index_1 (index, check_scalar, 1);
4134 }
4135
4136 /* Resolve a dim argument to an intrinsic function.  */
4137
4138 gfc_try
4139 gfc_resolve_dim_arg (gfc_expr *dim)
4140 {
4141   if (dim == NULL)
4142     return SUCCESS;
4143
4144   if (gfc_resolve_expr (dim) == FAILURE)
4145     return FAILURE;
4146
4147   if (dim->rank != 0)
4148     {
4149       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4150       return FAILURE;
4151
4152     }
4153
4154   if (dim->ts.type != BT_INTEGER)
4155     {
4156       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4157       return FAILURE;
4158     }
4159
4160   if (dim->ts.kind != gfc_index_integer_kind)
4161     {
4162       gfc_typespec ts;
4163
4164       gfc_clear_ts (&ts);
4165       ts.type = BT_INTEGER;
4166       ts.kind = gfc_index_integer_kind;
4167
4168       gfc_convert_type_warn (dim, &ts, 2, 0);
4169     }
4170
4171   return SUCCESS;
4172 }
4173
4174 /* Given an expression that contains array references, update those array
4175    references to point to the right array specifications.  While this is
4176    filled in during matching, this information is difficult to save and load
4177    in a module, so we take care of it here.
4178
4179    The idea here is that the original array reference comes from the
4180    base symbol.  We traverse the list of reference structures, setting
4181    the stored reference to references.  Component references can
4182    provide an additional array specification.  */
4183
4184 static void
4185 find_array_spec (gfc_expr *e)
4186 {
4187   gfc_array_spec *as;
4188   gfc_component *c;
4189   gfc_symbol *derived;
4190   gfc_ref *ref;
4191
4192   if (e->symtree->n.sym->ts.type == BT_CLASS)
4193     as = CLASS_DATA (e->symtree->n.sym)->as;
4194   else
4195     as = e->symtree->n.sym->as;
4196   derived = NULL;
4197
4198   for (ref = e->ref; ref; ref = ref->next)
4199     switch (ref->type)
4200       {
4201       case REF_ARRAY:
4202         if (as == NULL)
4203           gfc_internal_error ("find_array_spec(): Missing spec");
4204
4205         ref->u.ar.as = as;
4206         as = NULL;
4207         break;
4208
4209       case REF_COMPONENT:
4210         if (derived == NULL)
4211           derived = e->symtree->n.sym->ts.u.derived;
4212
4213         if (derived->attr.is_class)
4214           derived = derived->components->ts.u.derived;
4215
4216         c = derived->components;
4217
4218         for (; c; c = c->next)
4219           if (c == ref->u.c.component)
4220             {
4221               /* Track the sequence of component references.  */
4222               if (c->ts.type == BT_DERIVED)
4223                 derived = c->ts.u.derived;
4224               break;
4225             }
4226
4227         if (c == NULL)
4228           gfc_internal_error ("find_array_spec(): Component not found");
4229
4230         if (c->attr.dimension)
4231           {
4232             if (as != NULL)
4233               gfc_internal_error ("find_array_spec(): unused as(1)");
4234             as = c->as;
4235           }
4236
4237         break;
4238
4239       case REF_SUBSTRING:
4240         break;
4241       }
4242
4243   if (as != NULL)
4244     gfc_internal_error ("find_array_spec(): unused as(2)");
4245 }
4246
4247
4248 /* Resolve an array reference.  */
4249
4250 static gfc_try
4251 resolve_array_ref (gfc_array_ref *ar)
4252 {
4253   int i, check_scalar;
4254   gfc_expr *e;
4255
4256   for (i = 0; i < ar->dimen + ar->codimen; i++)
4257     {
4258       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4259
4260       /* Do not force gfc_index_integer_kind for the start.  We can
4261          do fine with any integer kind.  This avoids temporary arrays
4262          created for indexing with a vector.  */
4263       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4264         return FAILURE;
4265       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4266         return FAILURE;
4267       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4268         return FAILURE;
4269
4270       e = ar->start[i];
4271
4272       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4273         switch (e->rank)
4274           {
4275           case 0:
4276             ar->dimen_type[i] = DIMEN_ELEMENT;
4277             break;
4278
4279           case 1:
4280             ar->dimen_type[i] = DIMEN_VECTOR;
4281             if (e->expr_type == EXPR_VARIABLE
4282                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4283               ar->start[i] = gfc_get_parentheses (e);
4284             break;
4285
4286           default:
4287             gfc_error ("Array index at %L is an array of rank %d",
4288                        &ar->c_where[i], e->rank);
4289             return FAILURE;
4290           }
4291     }
4292
4293   if (ar->type == AR_FULL && ar->as->rank == 0)
4294     ar->type = AR_ELEMENT;
4295
4296   /* If the reference type is unknown, figure out what kind it is.  */
4297
4298   if (ar->type == AR_UNKNOWN)
4299     {
4300       ar->type = AR_ELEMENT;
4301       for (i = 0; i < ar->dimen; i++)
4302         if (ar->dimen_type[i] == DIMEN_RANGE
4303             || ar->dimen_type[i] == DIMEN_VECTOR)
4304           {
4305             ar->type = AR_SECTION;
4306             break;
4307           }
4308     }
4309
4310   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4311     return FAILURE;
4312
4313   return SUCCESS;
4314 }
4315
4316
4317 static gfc_try
4318 resolve_substring (gfc_ref *ref)
4319 {
4320   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4321
4322   if (ref->u.ss.start != NULL)
4323     {
4324       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4325         return FAILURE;
4326
4327       if (ref->u.ss.start->ts.type != BT_INTEGER)
4328         {
4329           gfc_error ("Substring start index at %L must be of type INTEGER",
4330                      &ref->u.ss.start->where);
4331           return FAILURE;
4332         }
4333
4334       if (ref->u.ss.start->rank != 0)
4335         {
4336           gfc_error ("Substring start index at %L must be scalar",
4337                      &ref->u.ss.start->where);
4338           return FAILURE;
4339         }
4340
4341       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4342           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4343               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4344         {
4345           gfc_error ("Substring start index at %L is less than one",
4346                      &ref->u.ss.start->where);
4347           return FAILURE;
4348         }
4349     }
4350
4351   if (ref->u.ss.end != NULL)
4352     {
4353       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4354         return FAILURE;
4355
4356       if (ref->u.ss.end->ts.type != BT_INTEGER)
4357         {
4358           gfc_error ("Substring end index at %L must be of type INTEGER",
4359                      &ref->u.ss.end->where);
4360           return FAILURE;
4361         }
4362
4363       if (ref->u.ss.end->rank != 0)
4364         {
4365           gfc_error ("Substring end index at %L must be scalar",
4366                      &ref->u.ss.end->where);
4367           return FAILURE;
4368         }
4369
4370       if (ref->u.ss.length != NULL
4371           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4372           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4373               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4374         {
4375           gfc_error ("Substring end index at %L exceeds the string length",
4376                      &ref->u.ss.start->where);
4377           return FAILURE;
4378         }
4379
4380       if (compare_bound_mpz_t (ref->u.ss.end,
4381                                gfc_integer_kinds[k].huge) == CMP_GT
4382           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4383               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4384         {
4385           gfc_error ("Substring end index at %L is too large",
4386                      &ref->u.ss.end->where);
4387           return FAILURE;
4388         }
4389     }
4390
4391   return SUCCESS;
4392 }
4393
4394
4395 /* This function supplies missing substring charlens.  */
4396
4397 void
4398 gfc_resolve_substring_charlen (gfc_expr *e)
4399 {
4400   gfc_ref *char_ref;
4401   gfc_expr *start, *end;
4402
4403   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4404     if (char_ref->type == REF_SUBSTRING)
4405       break;
4406
4407   if (!char_ref)
4408     return;
4409
4410   gcc_assert (char_ref->next == NULL);
4411
4412   if (e->ts.u.cl)
4413     {
4414       if (e->ts.u.cl->length)
4415         gfc_free_expr (e->ts.u.cl->length);
4416       else if (e->expr_type == EXPR_VARIABLE
4417                  && e->symtree->n.sym->attr.dummy)
4418         return;
4419     }
4420
4421   e->ts.type = BT_CHARACTER;
4422   e->ts.kind = gfc_default_character_kind;
4423
4424   if (!e->ts.u.cl)
4425     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4426
4427   if (char_ref->u.ss.start)
4428     start = gfc_copy_expr (char_ref->u.ss.start);
4429   else
4430     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4431
4432   if (char_ref->u.ss.end)
4433     end = gfc_copy_expr (char_ref->u.ss.end);
4434   else if (e->expr_type == EXPR_VARIABLE)
4435     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4436   else
4437     end = NULL;
4438
4439   if (!start || !end)
4440     return;
4441
4442   /* Length = (end - start +1).  */
4443   e->ts.u.cl->length = gfc_subtract (end, start);
4444   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4445                                 gfc_get_int_expr (gfc_default_integer_kind,
4446                                                   NULL, 1));
4447
4448   e->ts.u.cl->length->ts.type = BT_INTEGER;
4449   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4450
4451   /* Make sure that the length is simplified.  */
4452   gfc_simplify_expr (e->ts.u.cl->length, 1);
4453   gfc_resolve_expr (e->ts.u.cl->length);
4454 }
4455
4456
4457 /* Resolve subtype references.  */
4458
4459 static gfc_try
4460 resolve_ref (gfc_expr *expr)
4461 {
4462   int current_part_dimension, n_components, seen_part_dimension;
4463   gfc_ref *ref;
4464
4465   for (ref = expr->ref; ref; ref = ref->next)
4466     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4467       {
4468         find_array_spec (expr);
4469         break;
4470       }
4471
4472   for (ref = expr->ref; ref; ref = ref->next)
4473     switch (ref->type)
4474       {
4475       case REF_ARRAY:
4476         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4477           return FAILURE;
4478         break;
4479
4480       case REF_COMPONENT:
4481         break;
4482
4483       case REF_SUBSTRING:
4484         resolve_substring (ref);
4485         break;
4486       }
4487
4488   /* Check constraints on part references.  */
4489
4490   current_part_dimension = 0;
4491   seen_part_dimension = 0;
4492   n_components = 0;
4493
4494   for (ref = expr->ref; ref; ref = ref->next)
4495     {
4496       switch (ref->type)
4497         {
4498         case REF_ARRAY:
4499           switch (ref->u.ar.type)
4500             {
4501             case AR_FULL:
4502               /* Coarray scalar.  */
4503               if (ref->u.ar.as->rank == 0)
4504                 {
4505                   current_part_dimension = 0;
4506                   break;
4507                 }
4508               /* Fall through.  */
4509             case AR_SECTION:
4510               current_part_dimension = 1;
4511               break;
4512
4513             case AR_ELEMENT:
4514               current_part_dimension = 0;
4515               break;
4516
4517             case AR_UNKNOWN:
4518               gfc_internal_error ("resolve_ref(): Bad array reference");
4519             }
4520
4521           break;
4522
4523         case REF_COMPONENT:
4524           if (current_part_dimension || seen_part_dimension)
4525             {
4526               /* F03:C614.  */
4527               if (ref->u.c.component->attr.pointer
4528                   || ref->u.c.component->attr.proc_pointer)
4529                 {
4530                   gfc_error ("Component to the right of a part reference "
4531                              "with nonzero rank must not have the POINTER "
4532                              "attribute at %L", &expr->where);
4533                   return FAILURE;
4534                 }
4535               else if (ref->u.c.component->attr.allocatable)
4536                 {
4537                   gfc_error ("Component to the right of a part reference "
4538                              "with nonzero rank must not have the ALLOCATABLE "
4539                              "attribute at %L", &expr->where);
4540                   return FAILURE;
4541                 }
4542             }
4543
4544           n_components++;
4545           break;
4546
4547         case REF_SUBSTRING:
4548           break;
4549         }
4550
4551       if (((ref->type == REF_COMPONENT && n_components > 1)
4552            || ref->next == NULL)
4553           && current_part_dimension
4554           && seen_part_dimension)
4555         {
4556           gfc_error ("Two or more part references with nonzero rank must "
4557                      "not be specified at %L", &expr->where);
4558           return FAILURE;
4559         }
4560
4561       if (ref->type == REF_COMPONENT)
4562         {
4563           if (current_part_dimension)
4564             seen_part_dimension = 1;
4565
4566           /* reset to make sure */
4567           current_part_dimension = 0;
4568         }
4569     }
4570
4571   return SUCCESS;
4572 }
4573
4574
4575 /* Given an expression, determine its shape.  This is easier than it sounds.
4576    Leaves the shape array NULL if it is not possible to determine the shape.  */
4577
4578 static void
4579 expression_shape (gfc_expr *e)
4580 {
4581   mpz_t array[GFC_MAX_DIMENSIONS];
4582   int i;
4583
4584   if (e->rank == 0 || e->shape != NULL)
4585     return;
4586
4587   for (i = 0; i < e->rank; i++)
4588     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4589       goto fail;
4590
4591   e->shape = gfc_get_shape (e->rank);
4592
4593   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4594
4595   return;
4596
4597 fail:
4598   for (i--; i >= 0; i--)
4599     mpz_clear (array[i]);
4600 }
4601
4602
4603 /* Given a variable expression node, compute the rank of the expression by
4604    examining the base symbol and any reference structures it may have.  */
4605
4606 static void
4607 expression_rank (gfc_expr *e)
4608 {
4609   gfc_ref *ref;
4610   int i, rank;
4611
4612   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4613      could lead to serious confusion...  */
4614   gcc_assert (e->expr_type != EXPR_COMPCALL);
4615
4616   if (e->ref == NULL)
4617     {
4618       if (e->expr_type == EXPR_ARRAY)
4619         goto done;
4620       /* Constructors can have a rank different from one via RESHAPE().  */
4621
4622       if (e->symtree == NULL)
4623         {
4624           e->rank = 0;
4625           goto done;
4626         }
4627
4628       e->rank = (e->symtree->n.sym->as == NULL)
4629                 ? 0 : e->symtree->n.sym->as->rank;
4630       goto done;
4631     }
4632
4633   rank = 0;
4634
4635   for (ref = e->ref; ref; ref = ref->next)
4636     {
4637       if (ref->type != REF_ARRAY)
4638         continue;
4639
4640       if (ref->u.ar.type == AR_FULL)
4641         {
4642           rank = ref->u.ar.as->rank;
4643           break;
4644         }
4645
4646       if (ref->u.ar.type == AR_SECTION)
4647         {
4648           /* Figure out the rank of the section.  */
4649           if (rank != 0)
4650             gfc_internal_error ("expression_rank(): Two array specs");
4651
4652           for (i = 0; i < ref->u.ar.dimen; i++)
4653             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4654                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4655               rank++;
4656
4657           break;
4658         }
4659     }
4660
4661   e->rank = rank;
4662
4663 done:
4664   expression_shape (e);
4665 }
4666
4667
4668 /* Resolve a variable expression.  */
4669
4670 static gfc_try
4671 resolve_variable (gfc_expr *e)
4672 {
4673   gfc_symbol *sym;
4674   gfc_try t;
4675
4676   t = SUCCESS;
4677
4678   if (e->symtree == NULL)
4679     return FAILURE;
4680
4681   if (e->ref && resolve_ref (e) == FAILURE)
4682     return FAILURE;
4683
4684   sym = e->symtree->n.sym;
4685   if (sym->attr.flavor == FL_PROCEDURE
4686       && (!sym->attr.function
4687           || (sym->attr.function && sym->result
4688               && sym->result->attr.proc_pointer
4689               && !sym->result->attr.function)))
4690     {
4691       e->ts.type = BT_PROCEDURE;
4692       goto resolve_procedure;
4693     }
4694
4695   if (sym->ts.type != BT_UNKNOWN)
4696     gfc_variable_attr (e, &e->ts);
4697   else
4698     {
4699       /* Must be a simple variable reference.  */
4700       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
4701         return FAILURE;
4702       e->ts = sym->ts;
4703     }
4704
4705   if (check_assumed_size_reference (sym, e))
4706     return FAILURE;
4707
4708   /* Deal with forward references to entries during resolve_code, to
4709      satisfy, at least partially, 12.5.2.5.  */
4710   if (gfc_current_ns->entries
4711       && current_entry_id == sym->entry_id
4712       && cs_base
4713       && cs_base->current
4714       && cs_base->current->op != EXEC_ENTRY)
4715     {
4716       gfc_entry_list *entry;
4717       gfc_formal_arglist *formal;
4718       int n;
4719       bool seen;
4720
4721       /* If the symbol is a dummy...  */
4722       if (sym->attr.dummy && sym->ns == gfc_current_ns)
4723         {
4724           entry = gfc_current_ns->entries;
4725           seen = false;
4726
4727           /* ...test if the symbol is a parameter of previous entries.  */
4728           for (; entry && entry->id <= current_entry_id; entry = entry->next)
4729             for (formal = entry->sym->formal; formal; formal = formal->next)
4730               {
4731                 if (formal->sym && sym->name == formal->sym->name)
4732                   seen = true;
4733               }
4734
4735           /*  If it has not been seen as a dummy, this is an error.  */
4736           if (!seen)
4737             {
4738               if (specification_expr)
4739                 gfc_error ("Variable '%s', used in a specification expression"
4740                            ", is referenced at %L before the ENTRY statement "
4741                            "in which it is a parameter",
4742                            sym->name, &cs_base->current->loc);
4743               else
4744                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
4745                            "statement in which it is a parameter",
4746                            sym->name, &cs_base->current->loc);
4747               t = FAILURE;
4748             }
4749         }
4750
4751       /* Now do the same check on the specification expressions.  */
4752       specification_expr = 1;
4753       if (sym->ts.type == BT_CHARACTER
4754           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
4755         t = FAILURE;
4756
4757       if (sym->as)
4758         for (n = 0; n < sym->as->rank; n++)
4759           {
4760              specification_expr = 1;
4761              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
4762                t = FAILURE;
4763              specification_expr = 1;
4764              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
4765                t = FAILURE;
4766           }
4767       specification_expr = 0;
4768
4769       if (t == SUCCESS)
4770         /* Update the symbol's entry level.  */
4771         sym->entry_id = current_entry_id + 1;
4772     }
4773
4774 resolve_procedure:
4775   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
4776     t = FAILURE;
4777
4778   /* F2008, C617 and C1229.  */
4779   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
4780       && gfc_is_coindexed (e))
4781     {
4782       gfc_ref *ref, *ref2 = NULL;
4783
4784       if (e->ts.type == BT_CLASS)
4785         {
4786           gfc_error ("Polymorphic subobject of coindexed object at %L",
4787                      &e->where);
4788           t = FAILURE;
4789         }
4790
4791       for (ref = e->ref; ref; ref = ref->next)
4792         {
4793           if (ref->type == REF_COMPONENT)
4794             ref2 = ref;
4795           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
4796             break;
4797         }
4798
4799       for ( ; ref; ref = ref->next)
4800         if (ref->type == REF_COMPONENT)
4801           break;
4802
4803       /* Expression itself is coindexed object.  */
4804       if (ref == NULL)
4805         {
4806           gfc_component *c;
4807           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
4808           for ( ; c; c = c->next)
4809             if (c->attr.allocatable && c->ts.type == BT_CLASS)
4810               {
4811                 gfc_error ("Coindexed object with polymorphic allocatable "
4812                          "subcomponent at %L", &e->where);
4813                 t = FAILURE;
4814                 break;
4815               }
4816         }
4817     }
4818
4819   return t;
4820 }
4821
4822
4823 /* Checks to see that the correct symbol has been host associated.
4824    The only situation where this arises is that in which a twice
4825    contained function is parsed after the host association is made.
4826    Therefore, on detecting this, change the symbol in the expression
4827    and convert the array reference into an actual arglist if the old
4828    symbol is a variable.  */
4829 static bool
4830 check_host_association (gfc_expr *e)
4831 {
4832   gfc_symbol *sym, *old_sym;
4833   gfc_symtree *st;
4834   int n;
4835   gfc_ref *ref;
4836   gfc_actual_arglist *arg, *tail = NULL;
4837   bool retval = e->expr_type == EXPR_FUNCTION;
4838
4839   /*  If the expression is the result of substitution in
4840       interface.c(gfc_extend_expr) because there is no way in
4841       which the host association can be wrong.  */
4842   if (e->symtree == NULL
4843         || e->symtree->n.sym == NULL
4844         || e->user_operator)
4845     return retval;
4846
4847   old_sym = e->symtree->n.sym;
4848
4849   if (gfc_current_ns->parent
4850         && old_sym->ns != gfc_current_ns)
4851     {
4852       /* Use the 'USE' name so that renamed module symbols are
4853          correctly handled.  */
4854       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
4855
4856       if (sym && old_sym != sym
4857               && sym->ts.type == old_sym->ts.type
4858               && sym->attr.flavor == FL_PROCEDURE
4859               && sym->attr.contained)
4860         {
4861           /* Clear the shape, since it might not be valid.  */
4862           if (e->shape != NULL)
4863             {
4864               for (n = 0; n < e->rank; n++)
4865                 mpz_clear (e->shape[n]);
4866
4867               gfc_free (e->shape);
4868             }
4869
4870           /* Give the expression the right symtree!  */
4871           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
4872           gcc_assert (st != NULL);
4873
4874           if (old_sym->attr.flavor == FL_PROCEDURE
4875                 || e->expr_type == EXPR_FUNCTION)
4876             {
4877               /* Original was function so point to the new symbol, since
4878                  the actual argument list is already attached to the
4879                  expression. */
4880               e->value.function.esym = NULL;
4881               e->symtree = st;
4882             }
4883           else
4884             {
4885               /* Original was variable so convert array references into
4886                  an actual arglist. This does not need any checking now
4887                  since gfc_resolve_function will take care of it.  */
4888               e->value.function.actual = NULL;
4889               e->expr_type = EXPR_FUNCTION;
4890               e->symtree = st;
4891
4892               /* Ambiguity will not arise if the array reference is not
4893                  the last reference.  */
4894               for (ref = e->ref; ref; ref = ref->next)
4895                 if (ref->type == REF_ARRAY && ref->next == NULL)
4896                   break;
4897
4898               gcc_assert (ref->type == REF_ARRAY);
4899
4900               /* Grab the start expressions from the array ref and
4901                  copy them into actual arguments.  */
4902               for (n = 0; n < ref->u.ar.dimen; n++)
4903                 {
4904                   arg = gfc_get_actual_arglist ();
4905                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
4906                   if (e->value.function.actual == NULL)
4907                     tail = e->value.function.actual = arg;
4908                   else
4909                     {
4910                       tail->next = arg;
4911                       tail = arg;
4912                     }
4913                 }
4914
4915               /* Dump the reference list and set the rank.  */
4916               gfc_free_ref_list (e->ref);
4917               e->ref = NULL;
4918               e->rank = sym->as ? sym->as->rank : 0;
4919             }
4920
4921           gfc_resolve_expr (e);
4922           sym->refs++;
4923         }
4924     }
4925   /* This might have changed!  */
4926   return e->expr_type == EXPR_FUNCTION;
4927 }
4928
4929
4930 static void
4931 gfc_resolve_character_operator (gfc_expr *e)
4932 {
4933   gfc_expr *op1 = e->value.op.op1;
4934   gfc_expr *op2 = e->value.op.op2;
4935   gfc_expr *e1 = NULL;
4936   gfc_expr *e2 = NULL;
4937
4938   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
4939
4940   if (op1->ts.u.cl && op1->ts.u.cl->length)
4941     e1 = gfc_copy_expr (op1->ts.u.cl->length);
4942   else if (op1->expr_type == EXPR_CONSTANT)
4943     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
4944                            op1->value.character.length);
4945
4946   if (op2->ts.u.cl && op2->ts.u.cl->length)
4947     e2 = gfc_copy_expr (op2->ts.u.cl->length);
4948   else if (op2->expr_type == EXPR_CONSTANT)
4949     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
4950                            op2->value.character.length);
4951
4952   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4953
4954   if (!e1 || !e2)
4955     return;
4956
4957   e->ts.u.cl->length = gfc_add (e1, e2);
4958   e->ts.u.cl->length->ts.type = BT_INTEGER;
4959   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4960   gfc_simplify_expr (e->ts.u.cl->length, 0);
4961   gfc_resolve_expr (e->ts.u.cl->length);
4962
4963   return;
4964 }
4965
4966
4967 /*  Ensure that an character expression has a charlen and, if possible, a
4968     length expression.  */
4969
4970 static void
4971 fixup_charlen (gfc_expr *e)
4972 {
4973   /* The cases fall through so that changes in expression type and the need
4974      for multiple fixes are picked up.  In all circumstances, a charlen should
4975      be available for the middle end to hang a backend_decl on.  */
4976   switch (e->expr_type)
4977     {
4978     case EXPR_OP:
4979       gfc_resolve_character_operator (e);
4980
4981     case EXPR_ARRAY:
4982       if (e->expr_type == EXPR_ARRAY)
4983         gfc_resolve_character_array_constructor (e);
4984
4985     case EXPR_SUBSTRING:
4986       if (!e->ts.u.cl && e->ref)
4987         gfc_resolve_substring_charlen (e);
4988
4989     default:
4990       if (!e->ts.u.cl)
4991         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4992
4993       break;
4994     }
4995 }
4996
4997
4998 /* Update an actual argument to include the passed-object for type-bound
4999    procedures at the right position.  */
5000
5001 static gfc_actual_arglist*
5002 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5003                      const char *name)
5004 {
5005   gcc_assert (argpos > 0);
5006
5007   if (argpos == 1)
5008     {
5009       gfc_actual_arglist* result;
5010
5011       result = gfc_get_actual_arglist ();
5012       result->expr = po;
5013       result->next = lst;
5014       if (name)
5015         result->name = name;
5016
5017       return result;
5018     }
5019
5020   if (lst)
5021     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5022   else
5023     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5024   return lst;
5025 }
5026
5027
5028 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5029
5030 static gfc_expr*
5031 extract_compcall_passed_object (gfc_expr* e)
5032 {
5033   gfc_expr* po;
5034
5035   gcc_assert (e->expr_type == EXPR_COMPCALL);
5036
5037   if (e->value.compcall.base_object)
5038     po = gfc_copy_expr (e->value.compcall.base_object);
5039   else
5040     {
5041       po = gfc_get_expr ();
5042       po->expr_type = EXPR_VARIABLE;
5043       po->symtree = e->symtree;
5044       po->ref = gfc_copy_ref (e->ref);
5045       po->where = e->where;
5046     }
5047
5048   if (gfc_resolve_expr (po) == FAILURE)
5049     return NULL;
5050
5051   return po;
5052 }
5053
5054
5055 /* Update the arglist of an EXPR_COMPCALL expression to include the
5056    passed-object.  */
5057
5058 static gfc_try
5059 update_compcall_arglist (gfc_expr* e)
5060 {
5061   gfc_expr* po;
5062   gfc_typebound_proc* tbp;
5063
5064   tbp = e->value.compcall.tbp;
5065
5066   if (tbp->error)
5067     return FAILURE;
5068
5069   po = extract_compcall_passed_object (e);
5070   if (!po)
5071     return FAILURE;
5072
5073   if (tbp->nopass || e->value.compcall.ignore_pass)
5074     {
5075       gfc_free_expr (po);
5076       return SUCCESS;
5077     }
5078
5079   gcc_assert (tbp->pass_arg_num > 0);
5080   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5081                                                   tbp->pass_arg_num,
5082                                                   tbp->pass_arg);
5083
5084   return SUCCESS;
5085 }
5086
5087
5088 /* Extract the passed object from a PPC call (a copy of it).  */
5089
5090 static gfc_expr*
5091 extract_ppc_passed_object (gfc_expr *e)
5092 {
5093   gfc_expr *po;
5094   gfc_ref **ref;
5095
5096   po = gfc_get_expr ();
5097   po->expr_type = EXPR_VARIABLE;
5098   po->symtree = e->symtree;
5099   po->ref = gfc_copy_ref (e->ref);
5100   po->where = e->where;
5101
5102   /* Remove PPC reference.  */
5103   ref = &po->ref;
5104   while ((*ref)->next)
5105     ref = &(*ref)->next;
5106   gfc_free_ref_list (*ref);
5107   *ref = NULL;
5108
5109   if (gfc_resolve_expr (po) == FAILURE)
5110     return NULL;
5111
5112   return po;
5113 }
5114
5115
5116 /* Update the actual arglist of a procedure pointer component to include the
5117    passed-object.  */
5118
5119 static gfc_try
5120 update_ppc_arglist (gfc_expr* e)
5121 {
5122   gfc_expr* po;
5123   gfc_component *ppc;
5124   gfc_typebound_proc* tb;
5125
5126   if (!gfc_is_proc_ptr_comp (e, &ppc))
5127     return FAILURE;
5128
5129   tb = ppc->tb;
5130
5131   if (tb->error)
5132     return FAILURE;
5133   else if (tb->nopass)
5134     return SUCCESS;
5135
5136   po = extract_ppc_passed_object (e);
5137   if (!po)
5138     return FAILURE;
5139
5140   if (po->rank > 0)
5141     {
5142       gfc_error ("Passed-object at %L must be scalar", &e->where);
5143       return FAILURE;
5144     }
5145
5146   gcc_assert (tb->pass_arg_num > 0);
5147   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5148                                                   tb->pass_arg_num,
5149                                                   tb->pass_arg);
5150
5151   return SUCCESS;
5152 }
5153
5154
5155 /* Check that the object a TBP is called on is valid, i.e. it must not be
5156    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5157
5158 static gfc_try
5159 check_typebound_baseobject (gfc_expr* e)
5160 {
5161   gfc_expr* base;
5162
5163   base = extract_compcall_passed_object (e);
5164   if (!base)
5165     return FAILURE;
5166
5167   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5168
5169   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5170     {
5171       gfc_error ("Base object for type-bound procedure call at %L is of"
5172                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5173       return FAILURE;
5174     }
5175
5176   /* If the procedure called is NOPASS, the base object must be scalar.  */
5177   if (e->value.compcall.tbp->nopass && base->rank > 0)
5178     {
5179       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5180                  " be scalar", &e->where);
5181       return FAILURE;
5182     }
5183
5184   /* FIXME: Remove once PR 41177 (this problem) is fixed completely.  */
5185   if (base->rank > 0)
5186     {
5187       gfc_error ("Non-scalar base object at %L currently not implemented",
5188                  &e->where);
5189       return FAILURE;
5190     }
5191
5192   return SUCCESS;
5193 }
5194
5195
5196 /* Resolve a call to a type-bound procedure, either function or subroutine,
5197    statically from the data in an EXPR_COMPCALL expression.  The adapted
5198    arglist and the target-procedure symtree are returned.  */
5199
5200 static gfc_try
5201 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5202                           gfc_actual_arglist** actual)
5203 {
5204   gcc_assert (e->expr_type == EXPR_COMPCALL);
5205   gcc_assert (!e->value.compcall.tbp->is_generic);
5206
5207   /* Update the actual arglist for PASS.  */
5208   if (update_compcall_arglist (e) == FAILURE)
5209     return FAILURE;
5210
5211   *actual = e->value.compcall.actual;
5212   *target = e->value.compcall.tbp->u.specific;
5213
5214   gfc_free_ref_list (e->ref);
5215   e->ref = NULL;
5216   e->value.compcall.actual = NULL;
5217
5218   return SUCCESS;
5219 }
5220
5221
5222 /* Get the ultimate declared type from an expression.  In addition,
5223    return the last class/derived type reference and the copy of the
5224    reference list.  */
5225 static gfc_symbol*
5226 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5227                         gfc_expr *e)
5228 {
5229   gfc_symbol *declared;
5230   gfc_ref *ref;
5231
5232   declared = NULL;
5233   if (class_ref)
5234     *class_ref = NULL;
5235   if (new_ref)
5236     *new_ref = gfc_copy_ref (e->ref);
5237
5238   for (ref = e->ref; ref; ref = ref->next)
5239     {
5240       if (ref->type != REF_COMPONENT)
5241         continue;
5242
5243       if (ref->u.c.component->ts.type == BT_CLASS
5244             || ref->u.c.component->ts.type == BT_DERIVED)
5245         {
5246           declared = ref->u.c.component->ts.u.derived;
5247           if (class_ref)
5248             *class_ref = ref;
5249         }
5250     }
5251
5252   if (declared == NULL)
5253     declared = e->symtree->n.sym->ts.u.derived;
5254
5255   return declared;
5256 }
5257
5258
5259 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5260    which of the specific bindings (if any) matches the arglist and transform
5261    the expression into a call of that binding.  */
5262
5263 static gfc_try
5264 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5265 {
5266   gfc_typebound_proc* genproc;
5267   const char* genname;
5268   gfc_symtree *st;
5269   gfc_symbol *derived;
5270
5271   gcc_assert (e->expr_type == EXPR_COMPCALL);
5272   genname = e->value.compcall.name;
5273   genproc = e->value.compcall.tbp;
5274
5275   if (!genproc->is_generic)
5276     return SUCCESS;
5277
5278   /* Try the bindings on this type and in the inheritance hierarchy.  */
5279   for (; genproc; genproc = genproc->overridden)
5280     {
5281       gfc_tbp_generic* g;
5282
5283       gcc_assert (genproc->is_generic);
5284       for (g = genproc->u.generic; g; g = g->next)
5285         {
5286           gfc_symbol* target;
5287           gfc_actual_arglist* args;
5288           bool matches;
5289
5290           gcc_assert (g->specific);
5291
5292           if (g->specific->error)
5293             continue;
5294
5295           target = g->specific->u.specific->n.sym;
5296
5297           /* Get the right arglist by handling PASS/NOPASS.  */
5298           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5299           if (!g->specific->nopass)
5300             {
5301               gfc_expr* po;
5302               po = extract_compcall_passed_object (e);
5303               if (!po)
5304                 return FAILURE;
5305
5306               gcc_assert (g->specific->pass_arg_num > 0);
5307               gcc_assert (!g->specific->error);
5308               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5309                                           g->specific->pass_arg);
5310             }
5311           resolve_actual_arglist (args, target->attr.proc,
5312                                   is_external_proc (target) && !target->formal);
5313
5314           /* Check if this arglist matches the formal.  */
5315           matches = gfc_arglist_matches_symbol (&args, target);
5316
5317           /* Clean up and break out of the loop if we've found it.  */
5318           gfc_free_actual_arglist (args);
5319           if (matches)
5320             {
5321               e->value.compcall.tbp = g->specific;
5322               /* Pass along the name for CLASS methods, where the vtab
5323                  procedure pointer component has to be referenced.  */
5324               if (name)
5325                 *name = g->specific_st->name;
5326               goto success;
5327             }
5328         }
5329     }
5330
5331   /* Nothing matching found!  */
5332   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5333              " '%s' at %L", genname, &e->where);
5334   return FAILURE;
5335
5336 success:
5337   /* Make sure that we have the right specific instance for the name.  */
5338   genname = e->value.compcall.tbp->u.specific->name;
5339
5340   /* Is the symtree name a "unique name".  */
5341   if (*genname == '@')
5342     genname = e->value.compcall.tbp->u.specific->n.sym->name;
5343
5344   derived = get_declared_from_expr (NULL, NULL, e);
5345
5346   st = gfc_find_typebound_proc (derived, NULL, genname, false, &e->where);
5347   if (st)
5348     e->value.compcall.tbp = st->n.tb;
5349
5350   return SUCCESS;
5351 }
5352
5353
5354 /* Resolve a call to a type-bound subroutine.  */
5355
5356 static gfc_try
5357 resolve_typebound_call (gfc_code* c, const char **name)
5358 {
5359   gfc_actual_arglist* newactual;
5360   gfc_symtree* target;
5361
5362   /* Check that's really a SUBROUTINE.  */
5363   if (!c->expr1->value.compcall.tbp->subroutine)
5364     {
5365       gfc_error ("'%s' at %L should be a SUBROUTINE",
5366                  c->expr1->value.compcall.name, &c->loc);
5367       return FAILURE;
5368     }
5369
5370   if (check_typebound_baseobject (c->expr1) == FAILURE)
5371     return FAILURE;
5372
5373   /* Pass along the name for CLASS methods, where the vtab
5374      procedure pointer component has to be referenced.  */
5375   if (name)
5376     *name = c->expr1->value.compcall.name;
5377
5378   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5379     return FAILURE;
5380
5381   /* Transform into an ordinary EXEC_CALL for now.  */
5382
5383   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5384     return FAILURE;
5385
5386   c->ext.actual = newactual;
5387   c->symtree = target;
5388   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5389
5390   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5391
5392   gfc_free_expr (c->expr1);
5393   c->expr1 = gfc_get_expr ();
5394   c->expr1->expr_type = EXPR_FUNCTION;
5395   c->expr1->symtree = target;
5396   c->expr1->where = c->loc;
5397
5398   return resolve_call (c);
5399 }
5400
5401
5402 /* Resolve a component-call expression.  */
5403 static gfc_try
5404 resolve_compcall (gfc_expr* e, const char **name)
5405 {
5406   gfc_actual_arglist* newactual;
5407   gfc_symtree* target;
5408
5409   /* Check that's really a FUNCTION.  */
5410   if (!e->value.compcall.tbp->function)
5411     {
5412       gfc_error ("'%s' at %L should be a FUNCTION",
5413                  e->value.compcall.name, &e->where);
5414       return FAILURE;
5415     }
5416
5417   /* These must not be assign-calls!  */
5418   gcc_assert (!e->value.compcall.assign);
5419
5420   if (check_typebound_baseobject (e) == FAILURE)
5421     return FAILURE;
5422
5423   /* Pass along the name for CLASS methods, where the vtab
5424      procedure pointer component has to be referenced.  */
5425   if (name)
5426     *name = e->value.compcall.name;
5427
5428   if (resolve_typebound_generic_call (e, name) == FAILURE)
5429     return FAILURE;
5430   gcc_assert (!e->value.compcall.tbp->is_generic);
5431
5432   /* Take the rank from the function's symbol.  */
5433   if (e->value.compcall.tbp->u.specific->n.sym->as)
5434     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5435
5436   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5437      arglist to the TBP's binding target.  */
5438
5439   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5440     return FAILURE;
5441
5442   e->value.function.actual = newactual;
5443   e->value.function.name = NULL;
5444   e->value.function.esym = target->n.sym;
5445   e->value.function.isym = NULL;
5446   e->symtree = target;
5447   e->ts = target->n.sym->ts;
5448   e->expr_type = EXPR_FUNCTION;
5449
5450   /* Resolution is not necessary if this is a class subroutine; this
5451      function only has to identify the specific proc. Resolution of
5452      the call will be done next in resolve_typebound_call.  */
5453   return gfc_resolve_expr (e);
5454 }
5455
5456
5457
5458 /* Resolve a typebound function, or 'method'. First separate all
5459    the non-CLASS references by calling resolve_compcall directly.  */
5460
5461 static gfc_try
5462 resolve_typebound_function (gfc_expr* e)
5463 {
5464   gfc_symbol *declared;
5465   gfc_component *c;
5466   gfc_ref *new_ref;
5467   gfc_ref *class_ref;
5468   gfc_symtree *st;
5469   const char *name;
5470   const char *genname;
5471   gfc_typespec ts;
5472
5473   st = e->symtree;
5474   if (st == NULL)
5475     return resolve_compcall (e, NULL);
5476
5477   if (resolve_ref (e) == FAILURE)
5478     return FAILURE;
5479
5480   /* Get the CLASS declared type.  */
5481   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5482
5483   /* Weed out cases of the ultimate component being a derived type.  */
5484   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5485          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5486     {
5487       gfc_free_ref_list (new_ref);
5488       return resolve_compcall (e, NULL);
5489     }
5490
5491   c = gfc_find_component (declared, "$data", true, true);
5492   declared = c->ts.u.derived;
5493
5494   /* Keep the generic name so that the vtab reference can be made.  */
5495   genname = NULL; 
5496   if (e->value.compcall.tbp->is_generic)
5497     genname = e->value.compcall.name;
5498
5499   /* Treat the call as if it is a typebound procedure, in order to roll
5500      out the correct name for the specific function.  */
5501   if (resolve_compcall (e, &name) == FAILURE)
5502     return FAILURE;
5503   ts = e->ts;
5504
5505   /* Then convert the expression to a procedure pointer component call.  */
5506   e->value.function.esym = NULL;
5507   e->symtree = st;
5508
5509   if (new_ref)  
5510     e->ref = new_ref;
5511
5512   /* '$vptr' points to the vtab, which contains the procedure pointers.  */
5513   gfc_add_component_ref (e, "$vptr");
5514   if (genname)
5515     {
5516       /* A generic procedure needs the subsidiary vtabs and vtypes for
5517          the specific procedures to have been build.  */
5518       gfc_symbol *vtab;
5519       vtab = gfc_find_derived_vtab (declared, true);
5520       gcc_assert (vtab);
5521       gfc_add_component_ref (e, genname);
5522     }
5523   gfc_add_component_ref (e, name);
5524
5525   /* Recover the typespec for the expression.  This is really only
5526      necessary for generic procedures, where the additional call
5527      to gfc_add_component_ref seems to throw the collection of the
5528      correct typespec.  */
5529   e->ts = ts;
5530   return SUCCESS;
5531 }
5532
5533 /* Resolve a typebound subroutine, or 'method'. First separate all
5534    the non-CLASS references by calling resolve_typebound_call
5535    directly.  */
5536
5537 static gfc_try
5538 resolve_typebound_subroutine (gfc_code *code)
5539 {
5540   gfc_symbol *declared;
5541   gfc_component *c;
5542   gfc_ref *new_ref;
5543   gfc_ref *class_ref;
5544   gfc_symtree *st;
5545   const char *genname;
5546   const char *name;
5547   gfc_typespec ts;
5548
5549   st = code->expr1->symtree;
5550   if (st == NULL)
5551     return resolve_typebound_call (code, NULL);
5552
5553   if (resolve_ref (code->expr1) == FAILURE)
5554     return FAILURE;
5555
5556   /* Get the CLASS declared type.  */
5557   declared = get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5558
5559   /* Weed out cases of the ultimate component being a derived type.  */
5560   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5561          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5562     {
5563       gfc_free_ref_list (new_ref);
5564       return resolve_typebound_call (code, NULL);
5565     } 
5566
5567   c = gfc_find_component (declared, "$data", true, true);
5568   declared = c->ts.u.derived;
5569
5570   /* Keep the generic name so that the vtab reference can be made.  */
5571   genname = NULL; 
5572   if (code->expr1->value.compcall.tbp->is_generic)
5573     genname = code->expr1->value.compcall.name;
5574
5575   if (resolve_typebound_call (code, &name) == FAILURE)
5576     return FAILURE;
5577   ts = code->expr1->ts;
5578
5579   /* Then convert the expression to a procedure pointer component call.  */
5580   code->expr1->value.function.esym = NULL;
5581   code->expr1->symtree = st;
5582
5583   if (new_ref)
5584     code->expr1->ref = new_ref;
5585
5586   /* '$vptr' points to the vtab, which contains the procedure pointers.  */
5587   gfc_add_component_ref (code->expr1, "$vptr");
5588   if (genname)
5589     {
5590       /* A generic procedure needs the subsidiary vtabs and vtypes for
5591          the specific procedures to have been build.  */
5592       gfc_symbol *vtab;
5593       vtab = gfc_find_derived_vtab (declared, true);
5594       gcc_assert (vtab);
5595       gfc_add_component_ref (code->expr1, genname);
5596     }
5597   gfc_add_component_ref (code->expr1, name);
5598
5599   /* Recover the typespec for the expression.  This is really only
5600      necessary for generic procedures, where the additional call
5601      to gfc_add_component_ref seems to throw the collection of the
5602      correct typespec.  */
5603   code->expr1->ts = ts;
5604   return SUCCESS;
5605 }
5606
5607
5608 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5609
5610 static gfc_try
5611 resolve_ppc_call (gfc_code* c)
5612 {
5613   gfc_component *comp;
5614   bool b;
5615
5616   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5617   gcc_assert (b);
5618
5619   c->resolved_sym = c->expr1->symtree->n.sym;
5620   c->expr1->expr_type = EXPR_VARIABLE;
5621
5622   if (!comp->attr.subroutine)
5623     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5624
5625   if (resolve_ref (c->expr1) == FAILURE)
5626     return FAILURE;
5627
5628   if (update_ppc_arglist (c->expr1) == FAILURE)
5629     return FAILURE;
5630
5631   c->ext.actual = c->expr1->value.compcall.actual;
5632
5633   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5634                               comp->formal == NULL) == FAILURE)
5635     return FAILURE;
5636
5637   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
5638
5639   return SUCCESS;
5640 }
5641
5642
5643 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
5644
5645 static gfc_try
5646 resolve_expr_ppc (gfc_expr* e)
5647 {
5648   gfc_component *comp;
5649   bool b;
5650
5651   b = gfc_is_proc_ptr_comp (e, &comp);
5652   gcc_assert (b);
5653
5654   /* Convert to EXPR_FUNCTION.  */
5655   e->expr_type = EXPR_FUNCTION;
5656   e->value.function.isym = NULL;
5657   e->value.function.actual = e->value.compcall.actual;
5658   e->ts = comp->ts;
5659   if (comp->as != NULL)
5660     e->rank = comp->as->rank;
5661
5662   if (!comp->attr.function)
5663     gfc_add_function (&comp->attr, comp->name, &e->where);
5664
5665   if (resolve_ref (e) == FAILURE)
5666     return FAILURE;
5667
5668   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
5669                               comp->formal == NULL) == FAILURE)
5670     return FAILURE;
5671
5672   if (update_ppc_arglist (e) == FAILURE)
5673     return FAILURE;
5674
5675   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
5676
5677   return SUCCESS;
5678 }
5679
5680
5681 static bool
5682 gfc_is_expandable_expr (gfc_expr *e)
5683 {
5684   gfc_constructor *con;
5685
5686   if (e->expr_type == EXPR_ARRAY)
5687     {
5688       /* Traverse the constructor looking for variables that are flavor
5689          parameter.  Parameters must be expanded since they are fully used at
5690          compile time.  */
5691       con = gfc_constructor_first (e->value.constructor);
5692       for (; con; con = gfc_constructor_next (con))
5693         {
5694           if (con->expr->expr_type == EXPR_VARIABLE
5695               && con->expr->symtree
5696               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
5697               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
5698             return true;
5699           if (con->expr->expr_type == EXPR_ARRAY
5700               && gfc_is_expandable_expr (con->expr))
5701             return true;
5702         }
5703     }
5704
5705   return false;
5706 }
5707
5708 /* Resolve an expression.  That is, make sure that types of operands agree
5709    with their operators, intrinsic operators are converted to function calls
5710    for overloaded types and unresolved function references are resolved.  */
5711
5712 gfc_try
5713 gfc_resolve_expr (gfc_expr *e)
5714 {
5715   gfc_try t;
5716   bool inquiry_save;
5717
5718   if (e == NULL)
5719     return SUCCESS;
5720
5721   /* inquiry_argument only applies to variables.  */
5722   inquiry_save = inquiry_argument;
5723   if (e->expr_type != EXPR_VARIABLE)
5724     inquiry_argument = false;
5725
5726   switch (e->expr_type)
5727     {
5728     case EXPR_OP:
5729       t = resolve_operator (e);
5730       break;
5731
5732     case EXPR_FUNCTION:
5733     case EXPR_VARIABLE:
5734
5735       if (check_host_association (e))
5736         t = resolve_function (e);
5737       else
5738         {
5739           t = resolve_variable (e);
5740           if (t == SUCCESS)
5741             expression_rank (e);
5742         }
5743
5744       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
5745           && e->ref->type != REF_SUBSTRING)
5746         gfc_resolve_substring_charlen (e);
5747
5748       break;
5749
5750     case EXPR_COMPCALL:
5751       t = resolve_typebound_function (e);
5752       break;
5753
5754     case EXPR_SUBSTRING:
5755       t = resolve_ref (e);
5756       break;
5757
5758     case EXPR_CONSTANT:
5759     case EXPR_NULL:
5760       t = SUCCESS;
5761       break;
5762
5763     case EXPR_PPC:
5764       t = resolve_expr_ppc (e);
5765       break;
5766
5767     case EXPR_ARRAY:
5768       t = FAILURE;
5769       if (resolve_ref (e) == FAILURE)
5770         break;
5771
5772       t = gfc_resolve_array_constructor (e);
5773       /* Also try to expand a constructor.  */
5774       if (t == SUCCESS)
5775         {
5776           expression_rank (e);
5777           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
5778             gfc_expand_constructor (e);
5779         }
5780
5781       /* This provides the opportunity for the length of constructors with
5782          character valued function elements to propagate the string length
5783          to the expression.  */
5784       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
5785         {
5786           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
5787              here rather then add a duplicate test for it above.  */ 
5788           gfc_expand_constructor (e);
5789           t = gfc_resolve_character_array_constructor (e);
5790         }
5791
5792       break;
5793
5794     case EXPR_STRUCTURE:
5795       t = resolve_ref (e);
5796       if (t == FAILURE)
5797         break;
5798
5799       t = resolve_structure_cons (e);
5800       if (t == FAILURE)
5801         break;
5802
5803       t = gfc_simplify_expr (e, 0);
5804       break;
5805
5806     default:
5807       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
5808     }
5809
5810   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
5811     fixup_charlen (e);
5812
5813   inquiry_argument = inquiry_save;
5814
5815   return t;
5816 }
5817
5818
5819 /* Resolve an expression from an iterator.  They must be scalar and have
5820    INTEGER or (optionally) REAL type.  */
5821
5822 static gfc_try
5823 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
5824                            const char *name_msgid)
5825 {
5826   if (gfc_resolve_expr (expr) == FAILURE)
5827     return FAILURE;
5828
5829   if (expr->rank != 0)
5830     {
5831       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
5832       return FAILURE;
5833     }
5834
5835   if (expr->ts.type != BT_INTEGER)
5836     {
5837       if (expr->ts.type == BT_REAL)
5838         {
5839           if (real_ok)
5840             return gfc_notify_std (GFC_STD_F95_DEL,
5841                                    "Deleted feature: %s at %L must be integer",
5842                                    _(name_msgid), &expr->where);
5843           else
5844             {
5845               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
5846                          &expr->where);
5847               return FAILURE;
5848             }
5849         }
5850       else
5851         {
5852           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
5853           return FAILURE;
5854         }
5855     }
5856   return SUCCESS;
5857 }
5858
5859
5860 /* Resolve the expressions in an iterator structure.  If REAL_OK is
5861    false allow only INTEGER type iterators, otherwise allow REAL types.  */
5862
5863 gfc_try
5864 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
5865 {
5866   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
5867       == FAILURE)
5868     return FAILURE;
5869
5870   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
5871     {
5872       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
5873                  &iter->var->where);
5874       return FAILURE;
5875     }
5876
5877   if (gfc_resolve_iterator_expr (iter->start, real_ok,
5878                                  "Start expression in DO loop") == FAILURE)
5879     return FAILURE;
5880
5881   if (gfc_resolve_iterator_expr (iter->end, real_ok,
5882                                  "End expression in DO loop") == FAILURE)
5883     return FAILURE;
5884
5885   if (gfc_resolve_iterator_expr (iter->step, real_ok,
5886                                  "Step expression in DO loop") == FAILURE)
5887     return FAILURE;
5888
5889   if (iter->step->expr_type == EXPR_CONSTANT)
5890     {
5891       if ((iter->step->ts.type == BT_INTEGER
5892            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
5893           || (iter->step->ts.type == BT_REAL
5894               && mpfr_sgn (iter->step->value.real) == 0))
5895         {
5896           gfc_error ("Step expression in DO loop at %L cannot be zero",
5897                      &iter->step->where);
5898           return FAILURE;
5899         }
5900     }
5901
5902   /* Convert start, end, and step to the same type as var.  */
5903   if (iter->start->ts.kind != iter->var->ts.kind
5904       || iter->start->ts.type != iter->var->ts.type)
5905     gfc_convert_type (iter->start, &iter->var->ts, 2);
5906
5907   if (iter->end->ts.kind != iter->var->ts.kind
5908       || iter->end->ts.type != iter->var->ts.type)
5909     gfc_convert_type (iter->end, &iter->var->ts, 2);
5910
5911   if (iter->step->ts.kind != iter->var->ts.kind
5912       || iter->step->ts.type != iter->var->ts.type)
5913     gfc_convert_type (iter->step, &iter->var->ts, 2);
5914
5915   if (iter->start->expr_type == EXPR_CONSTANT
5916       && iter->end->expr_type == EXPR_CONSTANT
5917       && iter->step->expr_type == EXPR_CONSTANT)
5918     {
5919       int sgn, cmp;
5920       if (iter->start->ts.type == BT_INTEGER)
5921         {
5922           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
5923           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
5924         }
5925       else
5926         {
5927           sgn = mpfr_sgn (iter->step->value.real);
5928           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
5929         }
5930       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
5931         gfc_warning ("DO loop at %L will be executed zero times",
5932                      &iter->step->where);
5933     }
5934
5935   return SUCCESS;
5936 }
5937
5938
5939 /* Traversal function for find_forall_index.  f == 2 signals that
5940    that variable itself is not to be checked - only the references.  */
5941
5942 static bool
5943 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
5944 {
5945   if (expr->expr_type != EXPR_VARIABLE)
5946     return false;
5947   
5948   /* A scalar assignment  */
5949   if (!expr->ref || *f == 1)
5950     {
5951       if (expr->symtree->n.sym == sym)
5952         return true;
5953       else
5954         return false;
5955     }
5956
5957   if (*f == 2)
5958     *f = 1;
5959   return false;
5960 }
5961
5962
5963 /* Check whether the FORALL index appears in the expression or not.
5964    Returns SUCCESS if SYM is found in EXPR.  */
5965
5966 gfc_try
5967 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
5968 {
5969   if (gfc_traverse_expr (expr, sym, forall_index, f))
5970     return SUCCESS;
5971   else
5972     return FAILURE;
5973 }
5974
5975
5976 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
5977    to be a scalar INTEGER variable.  The subscripts and stride are scalar
5978    INTEGERs, and if stride is a constant it must be nonzero.
5979    Furthermore "A subscript or stride in a forall-triplet-spec shall
5980    not contain a reference to any index-name in the
5981    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
5982
5983 static void
5984 resolve_forall_iterators (gfc_forall_iterator *it)
5985 {
5986   gfc_forall_iterator *iter, *iter2;
5987
5988   for (iter = it; iter; iter = iter->next)
5989     {
5990       if (gfc_resolve_expr (iter->var) == SUCCESS
5991           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
5992         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
5993                    &iter->var->where);
5994
5995       if (gfc_resolve_expr (iter->start) == SUCCESS
5996           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
5997         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
5998                    &iter->start->where);
5999       if (iter->var->ts.kind != iter->start->ts.kind)
6000         gfc_convert_type (iter->start, &iter->var->ts, 2);
6001
6002       if (gfc_resolve_expr (iter->end) == SUCCESS
6003           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6004         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6005                    &iter->end->where);
6006       if (iter->var->ts.kind != iter->end->ts.kind)
6007         gfc_convert_type (iter->end, &iter->var->ts, 2);
6008
6009       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6010         {
6011           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6012             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6013                        &iter->stride->where, "INTEGER");
6014
6015           if (iter->stride->expr_type == EXPR_CONSTANT
6016               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6017             gfc_error ("FORALL stride expression at %L cannot be zero",
6018                        &iter->stride->where);
6019         }
6020       if (iter->var->ts.kind != iter->stride->ts.kind)
6021         gfc_convert_type (iter->stride, &iter->var->ts, 2);
6022     }
6023
6024   for (iter = it; iter; iter = iter->next)
6025     for (iter2 = iter; iter2; iter2 = iter2->next)
6026       {
6027         if (find_forall_index (iter2->start,
6028                                iter->var->symtree->n.sym, 0) == SUCCESS
6029             || find_forall_index (iter2->end,
6030                                   iter->var->symtree->n.sym, 0) == SUCCESS
6031             || find_forall_index (iter2->stride,
6032                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6033           gfc_error ("FORALL index '%s' may not appear in triplet "
6034                      "specification at %L", iter->var->symtree->name,
6035                      &iter2->start->where);
6036       }
6037 }
6038
6039
6040 /* Given a pointer to a symbol that is a derived type, see if it's
6041    inaccessible, i.e. if it's defined in another module and the components are
6042    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6043    inaccessible components are found, nonzero otherwise.  */
6044
6045 static int
6046 derived_inaccessible (gfc_symbol *sym)
6047 {
6048   gfc_component *c;
6049
6050   if (sym->attr.use_assoc && sym->attr.private_comp)
6051     return 1;
6052
6053   for (c = sym->components; c; c = c->next)
6054     {
6055         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6056           return 1;
6057     }
6058
6059   return 0;
6060 }
6061
6062
6063 /* Resolve the argument of a deallocate expression.  The expression must be
6064    a pointer or a full array.  */
6065
6066 static gfc_try
6067 resolve_deallocate_expr (gfc_expr *e)
6068 {
6069   symbol_attribute attr;
6070   int allocatable, pointer, check_intent_in;
6071   gfc_ref *ref;
6072   gfc_symbol *sym;
6073   gfc_component *c;
6074
6075   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
6076   check_intent_in = 1;
6077
6078   if (gfc_resolve_expr (e) == FAILURE)
6079     return FAILURE;
6080
6081   if (e->expr_type != EXPR_VARIABLE)
6082     goto bad;
6083
6084   sym = e->symtree->n.sym;
6085
6086   if (sym->ts.type == BT_CLASS)
6087     {
6088       allocatable = CLASS_DATA (sym)->attr.allocatable;
6089       pointer = CLASS_DATA (sym)->attr.pointer;
6090     }
6091   else
6092     {
6093       allocatable = sym->attr.allocatable;
6094       pointer = sym->attr.pointer;
6095     }
6096   for (ref = e->ref; ref; ref = ref->next)
6097     {
6098       if (pointer)
6099         check_intent_in = 0;
6100
6101       switch (ref->type)
6102         {
6103         case REF_ARRAY:
6104           if (ref->u.ar.type != AR_FULL)
6105             allocatable = 0;
6106           break;
6107
6108         case REF_COMPONENT:
6109           c = ref->u.c.component;
6110           if (c->ts.type == BT_CLASS)
6111             {
6112               allocatable = CLASS_DATA (c)->attr.allocatable;
6113               pointer = CLASS_DATA (c)->attr.pointer;
6114             }
6115           else
6116             {
6117               allocatable = c->attr.allocatable;
6118               pointer = c->attr.pointer;
6119             }
6120           break;
6121
6122         case REF_SUBSTRING:
6123           allocatable = 0;
6124           break;
6125         }
6126     }
6127
6128   attr = gfc_expr_attr (e);
6129
6130   if (allocatable == 0 && attr.pointer == 0)
6131     {
6132     bad:
6133       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6134                  &e->where);
6135       return FAILURE;
6136     }
6137
6138   if (check_intent_in && sym->attr.intent == INTENT_IN)
6139     {
6140       gfc_error ("Cannot deallocate INTENT(IN) variable '%s' at %L",
6141                  sym->name, &e->where);
6142       return FAILURE;
6143     }
6144
6145   if (e->ts.type == BT_CLASS)
6146     {
6147       /* Only deallocate the DATA component.  */
6148       gfc_add_component_ref (e, "$data");
6149     }
6150
6151   return SUCCESS;
6152 }
6153
6154
6155 /* Returns true if the expression e contains a reference to the symbol sym.  */
6156 static bool
6157 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6158 {
6159   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6160     return true;
6161
6162   return false;
6163 }
6164
6165 bool
6166 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6167 {
6168   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6169 }
6170
6171
6172 /* Given the expression node e for an allocatable/pointer of derived type to be
6173    allocated, get the expression node to be initialized afterwards (needed for
6174    derived types with default initializers, and derived types with allocatable
6175    components that need nullification.)  */
6176
6177 gfc_expr *
6178 gfc_expr_to_initialize (gfc_expr *e)
6179 {
6180   gfc_expr *result;
6181   gfc_ref *ref;
6182   int i;
6183
6184   result = gfc_copy_expr (e);
6185
6186   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6187   for (ref = result->ref; ref; ref = ref->next)
6188     if (ref->type == REF_ARRAY && ref->next == NULL)
6189       {
6190         ref->u.ar.type = AR_FULL;
6191
6192         for (i = 0; i < ref->u.ar.dimen; i++)
6193           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6194
6195         result->rank = ref->u.ar.dimen;
6196         break;
6197       }
6198
6199   return result;
6200 }
6201
6202
6203 /* Used in resolve_allocate_expr to check that a allocation-object and
6204    a source-expr are conformable.  This does not catch all possible 
6205    cases; in particular a runtime checking is needed.  */
6206
6207 static gfc_try
6208 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6209 {
6210   gfc_ref *tail;
6211   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6212   
6213   /* First compare rank.  */
6214   if (tail && e1->rank != tail->u.ar.as->rank)
6215     {
6216       gfc_error ("Source-expr at %L must be scalar or have the "
6217                  "same rank as the allocate-object at %L",
6218                  &e1->where, &e2->where);
6219       return FAILURE;
6220     }
6221
6222   if (e1->shape)
6223     {
6224       int i;
6225       mpz_t s;
6226
6227       mpz_init (s);
6228
6229       for (i = 0; i < e1->rank; i++)
6230         {
6231           if (tail->u.ar.end[i])
6232             {
6233               mpz_set (s, tail->u.ar.end[i]->value.integer);
6234               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6235               mpz_add_ui (s, s, 1);
6236             }
6237           else
6238             {
6239               mpz_set (s, tail->u.ar.start[i]->value.integer);
6240             }
6241
6242           if (mpz_cmp (e1->shape[i], s) != 0)
6243             {
6244               gfc_error ("Source-expr at %L and allocate-object at %L must "
6245                          "have the same shape", &e1->where, &e2->where);
6246               mpz_clear (s);
6247               return FAILURE;
6248             }
6249         }
6250
6251       mpz_clear (s);
6252     }
6253
6254   return SUCCESS;
6255 }
6256
6257
6258 /* Resolve the expression in an ALLOCATE statement, doing the additional
6259    checks to see whether the expression is OK or not.  The expression must
6260    have a trailing array reference that gives the size of the array.  */
6261
6262 static gfc_try
6263 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6264 {
6265   int i, pointer, allocatable, dimension, check_intent_in, is_abstract;
6266   int codimension;
6267   symbol_attribute attr;
6268   gfc_ref *ref, *ref2;
6269   gfc_array_ref *ar;
6270   gfc_symbol *sym = NULL;
6271   gfc_alloc *a;
6272   gfc_component *c;
6273
6274   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
6275   check_intent_in = 1;
6276
6277   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6278      checking of coarrays.  */
6279   for (ref = e->ref; ref; ref = ref->next)
6280     if (ref->next == NULL)
6281       break;
6282
6283   if (ref && ref->type == REF_ARRAY)
6284     ref->u.ar.in_allocate = true;
6285
6286   if (gfc_resolve_expr (e) == FAILURE)
6287     goto failure;
6288
6289   /* Make sure the expression is allocatable or a pointer.  If it is
6290      pointer, the next-to-last reference must be a pointer.  */
6291
6292   ref2 = NULL;
6293   if (e->symtree)
6294     sym = e->symtree->n.sym;
6295
6296   /* Check whether ultimate component is abstract and CLASS.  */
6297   is_abstract = 0;
6298
6299   if (e->expr_type != EXPR_VARIABLE)
6300     {
6301       allocatable = 0;
6302       attr = gfc_expr_attr (e);
6303       pointer = attr.pointer;
6304       dimension = attr.dimension;
6305       codimension = attr.codimension;
6306     }
6307   else
6308     {
6309       if (sym->ts.type == BT_CLASS)
6310         {
6311           allocatable = CLASS_DATA (sym)->attr.allocatable;
6312           pointer = CLASS_DATA (sym)->attr.pointer;
6313           dimension = CLASS_DATA (sym)->attr.dimension;
6314           codimension = CLASS_DATA (sym)->attr.codimension;
6315           is_abstract = CLASS_DATA (sym)->attr.abstract;
6316         }
6317       else
6318         {
6319           allocatable = sym->attr.allocatable;
6320           pointer = sym->attr.pointer;
6321           dimension = sym->attr.dimension;
6322           codimension = sym->attr.codimension;
6323         }
6324
6325       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6326         {
6327           if (pointer)
6328             check_intent_in = 0;
6329
6330           switch (ref->type)
6331             {
6332               case REF_ARRAY:
6333                 if (ref->next != NULL)
6334                   pointer = 0;
6335                 break;
6336
6337               case REF_COMPONENT:
6338                 /* F2008, C644.  */
6339                 if (gfc_is_coindexed (e))
6340                   {
6341                     gfc_error ("Coindexed allocatable object at %L",
6342                                &e->where);
6343                     goto failure;
6344                   }
6345
6346                 c = ref->u.c.component;
6347                 if (c->ts.type == BT_CLASS)
6348                   {
6349                     allocatable = CLASS_DATA (c)->attr.allocatable;
6350                     pointer = CLASS_DATA (c)->attr.pointer;
6351                     dimension = CLASS_DATA (c)->attr.dimension;
6352                     codimension = CLASS_DATA (c)->attr.codimension;
6353                     is_abstract = CLASS_DATA (c)->attr.abstract;
6354                   }
6355                 else
6356                   {
6357                     allocatable = c->attr.allocatable;
6358                     pointer = c->attr.pointer;
6359                     dimension = c->attr.dimension;
6360                     codimension = c->attr.codimension;
6361                     is_abstract = c->attr.abstract;
6362                   }
6363                 break;
6364
6365               case REF_SUBSTRING:
6366                 allocatable = 0;
6367                 pointer = 0;
6368                 break;
6369             }
6370         }
6371     }
6372
6373   if (allocatable == 0 && pointer == 0)
6374     {
6375       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6376                  &e->where);
6377       goto failure;
6378     }
6379
6380   /* Some checks for the SOURCE tag.  */
6381   if (code->expr3)
6382     {
6383       /* Check F03:C631.  */
6384       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6385         {
6386           gfc_error ("Type of entity at %L is type incompatible with "
6387                       "source-expr at %L", &e->where, &code->expr3->where);
6388           goto failure;
6389         }
6390
6391       /* Check F03:C632 and restriction following Note 6.18.  */
6392       if (code->expr3->rank > 0
6393           && conformable_arrays (code->expr3, e) == FAILURE)
6394         goto failure;
6395
6396       /* Check F03:C633.  */
6397       if (code->expr3->ts.kind != e->ts.kind)
6398         {
6399           gfc_error ("The allocate-object at %L and the source-expr at %L "
6400                       "shall have the same kind type parameter",
6401                       &e->where, &code->expr3->where);
6402           goto failure;
6403         }
6404     }
6405
6406   /* Check F08:C629.  */
6407   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
6408       && !code->expr3)
6409     {
6410       gcc_assert (e->ts.type == BT_CLASS);
6411       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6412                  "type-spec or source-expr", sym->name, &e->where);
6413       goto failure;
6414     }
6415
6416   if (check_intent_in && sym->attr.intent == INTENT_IN)
6417     {
6418       gfc_error ("Cannot allocate INTENT(IN) variable '%s' at %L",
6419                  sym->name, &e->where);
6420       goto failure;
6421     }
6422     
6423   if (!code->expr3 || code->expr3->mold)
6424     {
6425       /* Add default initializer for those derived types that need them.  */
6426       gfc_expr *init_e = NULL;
6427       gfc_typespec ts;
6428
6429       if (code->ext.alloc.ts.type == BT_DERIVED)
6430         ts = code->ext.alloc.ts;
6431       else if (code->expr3)
6432         ts = code->expr3->ts;
6433       else
6434         ts = e->ts;
6435
6436       if (ts.type == BT_DERIVED)
6437         init_e = gfc_default_initializer (&ts);
6438       /* FIXME: Use default init of dynamic type (cf. PR 44541).  */
6439       else if (e->ts.type == BT_CLASS)
6440         init_e = gfc_default_initializer (&ts.u.derived->components->ts);
6441
6442       if (init_e)
6443         {
6444           gfc_code *init_st = gfc_get_code ();
6445           init_st->loc = code->loc;
6446           init_st->op = EXEC_INIT_ASSIGN;
6447           init_st->expr1 = gfc_expr_to_initialize (e);
6448           init_st->expr2 = init_e;
6449           init_st->next = code->next;
6450           code->next = init_st;
6451         }
6452     }
6453
6454   if (pointer || (dimension == 0 && codimension == 0))
6455     goto success;
6456
6457   /* Make sure the next-to-last reference node is an array specification.  */
6458
6459   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
6460       || (dimension && ref2->u.ar.dimen == 0))
6461     {
6462       gfc_error ("Array specification required in ALLOCATE statement "
6463                  "at %L", &e->where);
6464       goto failure;
6465     }
6466
6467   /* Make sure that the array section reference makes sense in the
6468     context of an ALLOCATE specification.  */
6469
6470   ar = &ref2->u.ar;
6471
6472   if (codimension && ar->codimen == 0)
6473     {
6474       gfc_error ("Coarray specification required in ALLOCATE statement "
6475                  "at %L", &e->where);
6476       goto failure;
6477     }
6478
6479   for (i = 0; i < ar->dimen; i++)
6480     {
6481       if (ref2->u.ar.type == AR_ELEMENT)
6482         goto check_symbols;
6483
6484       switch (ar->dimen_type[i])
6485         {
6486         case DIMEN_ELEMENT:
6487           break;
6488
6489         case DIMEN_RANGE:
6490           if (ar->start[i] != NULL
6491               && ar->end[i] != NULL
6492               && ar->stride[i] == NULL)
6493             break;
6494
6495           /* Fall Through...  */
6496
6497         case DIMEN_UNKNOWN:
6498         case DIMEN_VECTOR:
6499         case DIMEN_STAR:
6500           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6501                      &e->where);
6502           goto failure;
6503         }
6504
6505 check_symbols:
6506       for (a = code->ext.alloc.list; a; a = a->next)
6507         {
6508           sym = a->expr->symtree->n.sym;
6509
6510           /* TODO - check derived type components.  */
6511           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6512             continue;
6513
6514           if ((ar->start[i] != NULL
6515                && gfc_find_sym_in_expr (sym, ar->start[i]))
6516               || (ar->end[i] != NULL
6517                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6518             {
6519               gfc_error ("'%s' must not appear in the array specification at "
6520                          "%L in the same ALLOCATE statement where it is "
6521                          "itself allocated", sym->name, &ar->where);
6522               goto failure;
6523             }
6524         }
6525     }
6526
6527   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
6528     {
6529       if (ar->dimen_type[i] == DIMEN_ELEMENT
6530           || ar->dimen_type[i] == DIMEN_RANGE)
6531         {
6532           if (i == (ar->dimen + ar->codimen - 1))
6533             {
6534               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
6535                          "statement at %L", &e->where);
6536               goto failure;
6537             }
6538           break;
6539         }
6540
6541       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
6542           && ar->stride[i] == NULL)
6543         break;
6544
6545       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
6546                  &e->where);
6547       goto failure;
6548     }
6549
6550   if (codimension && ar->as->rank == 0)
6551     {
6552       gfc_error ("Sorry, allocatable scalar coarrays are not yet supported "
6553                  "at %L", &e->where);
6554       goto failure;
6555     }
6556
6557 success:
6558   return SUCCESS;
6559
6560 failure:
6561   return FAILURE;
6562 }
6563
6564 static void
6565 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6566 {
6567   gfc_expr *stat, *errmsg, *pe, *qe;
6568   gfc_alloc *a, *p, *q;
6569
6570   stat = code->expr1 ? code->expr1 : NULL;
6571
6572   errmsg = code->expr2 ? code->expr2 : NULL;
6573
6574   /* Check the stat variable.  */
6575   if (stat)
6576     {
6577       if (stat->symtree->n.sym->attr.intent == INTENT_IN)
6578         gfc_error ("Stat-variable '%s' at %L cannot be INTENT(IN)",
6579                    stat->symtree->n.sym->name, &stat->where);
6580
6581       if (gfc_pure (NULL) && gfc_impure_variable (stat->symtree->n.sym))
6582         gfc_error ("Illegal stat-variable at %L for a PURE procedure",
6583                    &stat->where);
6584
6585       if ((stat->ts.type != BT_INTEGER
6586            && !(stat->ref && (stat->ref->type == REF_ARRAY
6587                               || stat->ref->type == REF_COMPONENT)))
6588           || stat->rank > 0)
6589         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6590                    "variable", &stat->where);
6591
6592       for (p = code->ext.alloc.list; p; p = p->next)
6593         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6594           {
6595             gfc_ref *ref1, *ref2;
6596             bool found = true;
6597
6598             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
6599                  ref1 = ref1->next, ref2 = ref2->next)
6600               {
6601                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
6602                   continue;
6603                 if (ref1->u.c.component->name != ref2->u.c.component->name)
6604                   {
6605                     found = false;
6606                     break;
6607                   }
6608               }
6609
6610             if (found)
6611               {
6612                 gfc_error ("Stat-variable at %L shall not be %sd within "
6613                            "the same %s statement", &stat->where, fcn, fcn);
6614                 break;
6615               }
6616           }
6617     }
6618
6619   /* Check the errmsg variable.  */
6620   if (errmsg)
6621     {
6622       if (!stat)
6623         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
6624                      &errmsg->where);
6625
6626       if (errmsg->symtree->n.sym->attr.intent == INTENT_IN)
6627         gfc_error ("Errmsg-variable '%s' at %L cannot be INTENT(IN)",
6628                    errmsg->symtree->n.sym->name, &errmsg->where);
6629
6630       if (gfc_pure (NULL) && gfc_impure_variable (errmsg->symtree->n.sym))
6631         gfc_error ("Illegal errmsg-variable at %L for a PURE procedure",
6632                    &errmsg->where);
6633
6634       if ((errmsg->ts.type != BT_CHARACTER
6635            && !(errmsg->ref
6636                 && (errmsg->ref->type == REF_ARRAY
6637                     || errmsg->ref->type == REF_COMPONENT)))
6638           || errmsg->rank > 0 )
6639         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
6640                    "variable", &errmsg->where);
6641
6642       for (p = code->ext.alloc.list; p; p = p->next)
6643         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
6644           {
6645             gfc_ref *ref1, *ref2;
6646             bool found = true;
6647
6648             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
6649                  ref1 = ref1->next, ref2 = ref2->next)
6650               {
6651                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
6652                   continue;
6653                 if (ref1->u.c.component->name != ref2->u.c.component->name)
6654                   {
6655                     found = false;
6656                     break;
6657                   }
6658               }
6659
6660             if (found)
6661               {
6662                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
6663                            "the same %s statement", &errmsg->where, fcn, fcn);
6664                 break;
6665               }
6666           }
6667     }
6668
6669   /* Check that an allocate-object appears only once in the statement.  
6670      FIXME: Checking derived types is disabled.  */
6671   for (p = code->ext.alloc.list; p; p = p->next)
6672     {
6673       pe = p->expr;
6674       if ((pe->ref && pe->ref->type != REF_COMPONENT)
6675            && (pe->symtree->n.sym->ts.type != BT_DERIVED))
6676         {
6677           for (q = p->next; q; q = q->next)
6678             {
6679               qe = q->expr;
6680               if ((qe->ref && qe->ref->type != REF_COMPONENT)
6681                   && (qe->symtree->n.sym->ts.type != BT_DERIVED)
6682                   && (pe->symtree->n.sym->name == qe->symtree->n.sym->name))
6683                 gfc_error ("Allocate-object at %L also appears at %L",
6684                            &pe->where, &qe->where);
6685             }
6686         }
6687     }
6688
6689   if (strcmp (fcn, "ALLOCATE") == 0)
6690     {
6691       for (a = code->ext.alloc.list; a; a = a->next)
6692         resolve_allocate_expr (a->expr, code);
6693     }
6694   else
6695     {
6696       for (a = code->ext.alloc.list; a; a = a->next)
6697         resolve_deallocate_expr (a->expr);
6698     }
6699 }
6700
6701
6702 /************ SELECT CASE resolution subroutines ************/
6703
6704 /* Callback function for our mergesort variant.  Determines interval
6705    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
6706    op1 > op2.  Assumes we're not dealing with the default case.  
6707    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
6708    There are nine situations to check.  */
6709
6710 static int
6711 compare_cases (const gfc_case *op1, const gfc_case *op2)
6712 {
6713   int retval;
6714
6715   if (op1->low == NULL) /* op1 = (:L)  */
6716     {
6717       /* op2 = (:N), so overlap.  */
6718       retval = 0;
6719       /* op2 = (M:) or (M:N),  L < M  */
6720       if (op2->low != NULL
6721           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6722         retval = -1;
6723     }
6724   else if (op1->high == NULL) /* op1 = (K:)  */
6725     {
6726       /* op2 = (M:), so overlap.  */
6727       retval = 0;
6728       /* op2 = (:N) or (M:N), K > N  */
6729       if (op2->high != NULL
6730           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6731         retval = 1;
6732     }
6733   else /* op1 = (K:L)  */
6734     {
6735       if (op2->low == NULL)       /* op2 = (:N), K > N  */
6736         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6737                  ? 1 : 0;
6738       else if (op2->high == NULL) /* op2 = (M:), L < M  */
6739         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6740                  ? -1 : 0;
6741       else                      /* op2 = (M:N)  */
6742         {
6743           retval =  0;
6744           /* L < M  */
6745           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6746             retval =  -1;
6747           /* K > N  */
6748           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6749             retval =  1;
6750         }
6751     }
6752
6753   return retval;
6754 }
6755
6756
6757 /* Merge-sort a double linked case list, detecting overlap in the
6758    process.  LIST is the head of the double linked case list before it
6759    is sorted.  Returns the head of the sorted list if we don't see any
6760    overlap, or NULL otherwise.  */
6761
6762 static gfc_case *
6763 check_case_overlap (gfc_case *list)
6764 {
6765   gfc_case *p, *q, *e, *tail;
6766   int insize, nmerges, psize, qsize, cmp, overlap_seen;
6767
6768   /* If the passed list was empty, return immediately.  */
6769   if (!list)
6770     return NULL;
6771
6772   overlap_seen = 0;
6773   insize = 1;
6774
6775   /* Loop unconditionally.  The only exit from this loop is a return
6776      statement, when we've finished sorting the case list.  */
6777   for (;;)
6778     {
6779       p = list;
6780       list = NULL;
6781       tail = NULL;
6782
6783       /* Count the number of merges we do in this pass.  */
6784       nmerges = 0;
6785
6786       /* Loop while there exists a merge to be done.  */
6787       while (p)
6788         {
6789           int i;
6790
6791           /* Count this merge.  */
6792           nmerges++;
6793
6794           /* Cut the list in two pieces by stepping INSIZE places
6795              forward in the list, starting from P.  */
6796           psize = 0;
6797           q = p;
6798           for (i = 0; i < insize; i++)
6799             {
6800               psize++;
6801               q = q->right;
6802               if (!q)
6803                 break;
6804             }
6805           qsize = insize;
6806
6807           /* Now we have two lists.  Merge them!  */
6808           while (psize > 0 || (qsize > 0 && q != NULL))
6809             {
6810               /* See from which the next case to merge comes from.  */
6811               if (psize == 0)
6812                 {
6813                   /* P is empty so the next case must come from Q.  */
6814                   e = q;
6815                   q = q->right;
6816                   qsize--;
6817                 }
6818               else if (qsize == 0 || q == NULL)
6819                 {
6820                   /* Q is empty.  */
6821                   e = p;
6822                   p = p->right;
6823                   psize--;
6824                 }
6825               else
6826                 {
6827                   cmp = compare_cases (p, q);
6828                   if (cmp < 0)
6829                     {
6830                       /* The whole case range for P is less than the
6831                          one for Q.  */
6832                       e = p;
6833                       p = p->right;
6834                       psize--;
6835                     }
6836                   else if (cmp > 0)
6837                     {
6838                       /* The whole case range for Q is greater than
6839                          the case range for P.  */
6840                       e = q;
6841                       q = q->right;
6842                       qsize--;
6843                     }
6844                   else
6845                     {
6846                       /* The cases overlap, or they are the same
6847                          element in the list.  Either way, we must
6848                          issue an error and get the next case from P.  */
6849                       /* FIXME: Sort P and Q by line number.  */
6850                       gfc_error ("CASE label at %L overlaps with CASE "
6851                                  "label at %L", &p->where, &q->where);
6852                       overlap_seen = 1;
6853                       e = p;
6854                       p = p->right;
6855                       psize--;
6856                     }
6857                 }
6858
6859                 /* Add the next element to the merged list.  */
6860               if (tail)
6861                 tail->right = e;
6862               else
6863                 list = e;
6864               e->left = tail;
6865               tail = e;
6866             }
6867
6868           /* P has now stepped INSIZE places along, and so has Q.  So
6869              they're the same.  */
6870           p = q;
6871         }
6872       tail->right = NULL;
6873
6874       /* If we have done only one merge or none at all, we've
6875          finished sorting the cases.  */
6876       if (nmerges <= 1)
6877         {
6878           if (!overlap_seen)
6879             return list;
6880           else
6881             return NULL;
6882         }
6883
6884       /* Otherwise repeat, merging lists twice the size.  */
6885       insize *= 2;
6886     }
6887 }
6888
6889
6890 /* Check to see if an expression is suitable for use in a CASE statement.
6891    Makes sure that all case expressions are scalar constants of the same
6892    type.  Return FAILURE if anything is wrong.  */
6893
6894 static gfc_try
6895 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
6896 {
6897   if (e == NULL) return SUCCESS;
6898
6899   if (e->ts.type != case_expr->ts.type)
6900     {
6901       gfc_error ("Expression in CASE statement at %L must be of type %s",
6902                  &e->where, gfc_basic_typename (case_expr->ts.type));
6903       return FAILURE;
6904     }
6905
6906   /* C805 (R808) For a given case-construct, each case-value shall be of
6907      the same type as case-expr.  For character type, length differences
6908      are allowed, but the kind type parameters shall be the same.  */
6909
6910   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
6911     {
6912       gfc_error ("Expression in CASE statement at %L must be of kind %d",
6913                  &e->where, case_expr->ts.kind);
6914       return FAILURE;
6915     }
6916
6917   /* Convert the case value kind to that of case expression kind,
6918      if needed */
6919
6920   if (e->ts.kind != case_expr->ts.kind)
6921     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
6922
6923   if (e->rank != 0)
6924     {
6925       gfc_error ("Expression in CASE statement at %L must be scalar",
6926                  &e->where);
6927       return FAILURE;
6928     }
6929
6930   return SUCCESS;
6931 }
6932
6933
6934 /* Given a completely parsed select statement, we:
6935
6936      - Validate all expressions and code within the SELECT.
6937      - Make sure that the selection expression is not of the wrong type.
6938      - Make sure that no case ranges overlap.
6939      - Eliminate unreachable cases and unreachable code resulting from
6940        removing case labels.
6941
6942    The standard does allow unreachable cases, e.g. CASE (5:3).  But
6943    they are a hassle for code generation, and to prevent that, we just
6944    cut them out here.  This is not necessary for overlapping cases
6945    because they are illegal and we never even try to generate code.
6946
6947    We have the additional caveat that a SELECT construct could have
6948    been a computed GOTO in the source code. Fortunately we can fairly
6949    easily work around that here: The case_expr for a "real" SELECT CASE
6950    is in code->expr1, but for a computed GOTO it is in code->expr2. All
6951    we have to do is make sure that the case_expr is a scalar integer
6952    expression.  */
6953
6954 static void
6955 resolve_select (gfc_code *code)
6956 {
6957   gfc_code *body;
6958   gfc_expr *case_expr;
6959   gfc_case *cp, *default_case, *tail, *head;
6960   int seen_unreachable;
6961   int seen_logical;
6962   int ncases;
6963   bt type;
6964   gfc_try t;
6965
6966   if (code->expr1 == NULL)
6967     {
6968       /* This was actually a computed GOTO statement.  */
6969       case_expr = code->expr2;
6970       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
6971         gfc_error ("Selection expression in computed GOTO statement "
6972                    "at %L must be a scalar integer expression",
6973                    &case_expr->where);
6974
6975       /* Further checking is not necessary because this SELECT was built
6976          by the compiler, so it should always be OK.  Just move the
6977          case_expr from expr2 to expr so that we can handle computed
6978          GOTOs as normal SELECTs from here on.  */
6979       code->expr1 = code->expr2;
6980       code->expr2 = NULL;
6981       return;
6982     }
6983
6984   case_expr = code->expr1;
6985
6986   type = case_expr->ts.type;
6987   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
6988     {
6989       gfc_error ("Argument of SELECT statement at %L cannot be %s",
6990                  &case_expr->where, gfc_typename (&case_expr->ts));
6991
6992       /* Punt. Going on here just produce more garbage error messages.  */
6993       return;
6994     }
6995
6996   if (case_expr->rank != 0)
6997     {
6998       gfc_error ("Argument of SELECT statement at %L must be a scalar "
6999                  "expression", &case_expr->where);
7000
7001       /* Punt.  */
7002       return;
7003     }
7004
7005
7006   /* Raise a warning if an INTEGER case value exceeds the range of
7007      the case-expr. Later, all expressions will be promoted to the
7008      largest kind of all case-labels.  */
7009
7010   if (type == BT_INTEGER)
7011     for (body = code->block; body; body = body->block)
7012       for (cp = body->ext.case_list; cp; cp = cp->next)
7013         {
7014           if (cp->low
7015               && gfc_check_integer_range (cp->low->value.integer,
7016                                           case_expr->ts.kind) != ARITH_OK)
7017             gfc_warning ("Expression in CASE statement at %L is "
7018                          "not in the range of %s", &cp->low->where,
7019                          gfc_typename (&case_expr->ts));
7020
7021           if (cp->high
7022               && cp->low != cp->high
7023               && gfc_check_integer_range (cp->high->value.integer,
7024                                           case_expr->ts.kind) != ARITH_OK)
7025             gfc_warning ("Expression in CASE statement at %L is "
7026                          "not in the range of %s", &cp->high->where,
7027                          gfc_typename (&case_expr->ts));
7028         }
7029
7030   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7031      of the SELECT CASE expression and its CASE values.  Walk the lists
7032      of case values, and if we find a mismatch, promote case_expr to
7033      the appropriate kind.  */
7034
7035   if (type == BT_LOGICAL || type == BT_INTEGER)
7036     {
7037       for (body = code->block; body; body = body->block)
7038         {
7039           /* Walk the case label list.  */
7040           for (cp = body->ext.case_list; cp; cp = cp->next)
7041             {
7042               /* Intercept the DEFAULT case.  It does not have a kind.  */
7043               if (cp->low == NULL && cp->high == NULL)
7044                 continue;
7045
7046               /* Unreachable case ranges are discarded, so ignore.  */
7047               if (cp->low != NULL && cp->high != NULL
7048                   && cp->low != cp->high
7049                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7050                 continue;
7051
7052               if (cp->low != NULL
7053                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7054                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7055
7056               if (cp->high != NULL
7057                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7058                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7059             }
7060          }
7061     }
7062
7063   /* Assume there is no DEFAULT case.  */
7064   default_case = NULL;
7065   head = tail = NULL;
7066   ncases = 0;
7067   seen_logical = 0;
7068
7069   for (body = code->block; body; body = body->block)
7070     {
7071       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7072       t = SUCCESS;
7073       seen_unreachable = 0;
7074
7075       /* Walk the case label list, making sure that all case labels
7076          are legal.  */
7077       for (cp = body->ext.case_list; cp; cp = cp->next)
7078         {
7079           /* Count the number of cases in the whole construct.  */
7080           ncases++;
7081
7082           /* Intercept the DEFAULT case.  */
7083           if (cp->low == NULL && cp->high == NULL)
7084             {
7085               if (default_case != NULL)
7086                 {
7087                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7088                              "by a second DEFAULT CASE at %L",
7089                              &default_case->where, &cp->where);
7090                   t = FAILURE;
7091                   break;
7092                 }
7093               else
7094                 {
7095                   default_case = cp;
7096                   continue;
7097                 }
7098             }
7099
7100           /* Deal with single value cases and case ranges.  Errors are
7101              issued from the validation function.  */
7102           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7103               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7104             {
7105               t = FAILURE;
7106               break;
7107             }
7108
7109           if (type == BT_LOGICAL
7110               && ((cp->low == NULL || cp->high == NULL)
7111                   || cp->low != cp->high))
7112             {
7113               gfc_error ("Logical range in CASE statement at %L is not "
7114                          "allowed", &cp->low->where);
7115               t = FAILURE;
7116               break;
7117             }
7118
7119           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7120             {
7121               int value;
7122               value = cp->low->value.logical == 0 ? 2 : 1;
7123               if (value & seen_logical)
7124                 {
7125                   gfc_error ("Constant logical value in CASE statement "
7126                              "is repeated at %L",
7127                              &cp->low->where);
7128                   t = FAILURE;
7129                   break;
7130                 }
7131               seen_logical |= value;
7132             }
7133
7134           if (cp->low != NULL && cp->high != NULL
7135               && cp->low != cp->high
7136               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7137             {
7138               if (gfc_option.warn_surprising)
7139                 gfc_warning ("Range specification at %L can never "
7140                              "be matched", &cp->where);
7141
7142               cp->unreachable = 1;
7143               seen_unreachable = 1;
7144             }
7145           else
7146             {
7147               /* If the case range can be matched, it can also overlap with
7148                  other cases.  To make sure it does not, we put it in a
7149                  double linked list here.  We sort that with a merge sort
7150                  later on to detect any overlapping cases.  */
7151               if (!head)
7152                 {
7153                   head = tail = cp;
7154                   head->right = head->left = NULL;
7155                 }
7156               else
7157                 {
7158                   tail->right = cp;
7159                   tail->right->left = tail;
7160                   tail = tail->right;
7161                   tail->right = NULL;
7162                 }
7163             }
7164         }
7165
7166       /* It there was a failure in the previous case label, give up
7167          for this case label list.  Continue with the next block.  */
7168       if (t == FAILURE)
7169         continue;
7170
7171       /* See if any case labels that are unreachable have been seen.
7172          If so, we eliminate them.  This is a bit of a kludge because
7173          the case lists for a single case statement (label) is a
7174          single forward linked lists.  */
7175       if (seen_unreachable)
7176       {
7177         /* Advance until the first case in the list is reachable.  */
7178         while (body->ext.case_list != NULL
7179                && body->ext.case_list->unreachable)
7180           {
7181             gfc_case *n = body->ext.case_list;
7182             body->ext.case_list = body->ext.case_list->next;
7183             n->next = NULL;
7184             gfc_free_case_list (n);
7185           }
7186
7187         /* Strip all other unreachable cases.  */
7188         if (body->ext.case_list)
7189           {
7190             for (cp = body->ext.case_list; cp->next; cp = cp->next)
7191               {
7192                 if (cp->next->unreachable)
7193                   {
7194                     gfc_case *n = cp->next;
7195                     cp->next = cp->next->next;
7196                     n->next = NULL;
7197                     gfc_free_case_list (n);
7198                   }
7199               }
7200           }
7201       }
7202     }
7203
7204   /* See if there were overlapping cases.  If the check returns NULL,
7205      there was overlap.  In that case we don't do anything.  If head
7206      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7207      then used during code generation for SELECT CASE constructs with
7208      a case expression of a CHARACTER type.  */
7209   if (head)
7210     {
7211       head = check_case_overlap (head);
7212
7213       /* Prepend the default_case if it is there.  */
7214       if (head != NULL && default_case)
7215         {
7216           default_case->left = NULL;
7217           default_case->right = head;
7218           head->left = default_case;
7219         }
7220     }
7221
7222   /* Eliminate dead blocks that may be the result if we've seen
7223      unreachable case labels for a block.  */
7224   for (body = code; body && body->block; body = body->block)
7225     {
7226       if (body->block->ext.case_list == NULL)
7227         {
7228           /* Cut the unreachable block from the code chain.  */
7229           gfc_code *c = body->block;
7230           body->block = c->block;
7231
7232           /* Kill the dead block, but not the blocks below it.  */
7233           c->block = NULL;
7234           gfc_free_statements (c);
7235         }
7236     }
7237
7238   /* More than two cases is legal but insane for logical selects.
7239      Issue a warning for it.  */
7240   if (gfc_option.warn_surprising && type == BT_LOGICAL
7241       && ncases > 2)
7242     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7243                  &code->loc);
7244 }
7245
7246
7247 /* Check if a derived type is extensible.  */
7248
7249 bool
7250 gfc_type_is_extensible (gfc_symbol *sym)
7251 {
7252   return !(sym->attr.is_bind_c || sym->attr.sequence);
7253 }
7254
7255
7256 /* Resolve a SELECT TYPE statement.  */
7257
7258 static void
7259 resolve_select_type (gfc_code *code)
7260 {
7261   gfc_symbol *selector_type;
7262   gfc_code *body, *new_st, *if_st, *tail;
7263   gfc_code *class_is = NULL, *default_case = NULL;
7264   gfc_case *c;
7265   gfc_symtree *st;
7266   char name[GFC_MAX_SYMBOL_LEN];
7267   gfc_namespace *ns;
7268   int error = 0;
7269
7270   ns = code->ext.block.ns;
7271   gfc_resolve (ns);
7272
7273   /* Check for F03:C813.  */
7274   if (code->expr1->ts.type != BT_CLASS
7275       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
7276     {
7277       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
7278                  "at %L", &code->loc);
7279       return;
7280     }
7281
7282   if (code->expr2)
7283     {
7284       if (code->expr1->symtree->n.sym->attr.untyped)
7285         code->expr1->symtree->n.sym->ts = code->expr2->ts;
7286       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
7287     }
7288   else
7289     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
7290
7291   /* Loop over TYPE IS / CLASS IS cases.  */
7292   for (body = code->block; body; body = body->block)
7293     {
7294       c = body->ext.case_list;
7295
7296       /* Check F03:C815.  */
7297       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7298           && !gfc_type_is_extensible (c->ts.u.derived))
7299         {
7300           gfc_error ("Derived type '%s' at %L must be extensible",
7301                      c->ts.u.derived->name, &c->where);
7302           error++;
7303           continue;
7304         }
7305
7306       /* Check F03:C816.  */
7307       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7308           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
7309         {
7310           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
7311                      c->ts.u.derived->name, &c->where, selector_type->name);
7312           error++;
7313           continue;
7314         }
7315
7316       /* Intercept the DEFAULT case.  */
7317       if (c->ts.type == BT_UNKNOWN)
7318         {
7319           /* Check F03:C818.  */
7320           if (default_case)
7321             {
7322               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7323                          "by a second DEFAULT CASE at %L",
7324                          &default_case->ext.case_list->where, &c->where);
7325               error++;
7326               continue;
7327             }
7328           else
7329             default_case = body;
7330         }
7331     }
7332     
7333   if (error>0)
7334     return;
7335
7336   if (code->expr2)
7337     {
7338       /* Insert assignment for selector variable.  */
7339       new_st = gfc_get_code ();
7340       new_st->op = EXEC_ASSIGN;
7341       new_st->expr1 = gfc_copy_expr (code->expr1);
7342       new_st->expr2 = gfc_copy_expr (code->expr2);
7343       ns->code = new_st;
7344     }
7345
7346   /* Put SELECT TYPE statement inside a BLOCK.  */
7347   new_st = gfc_get_code ();
7348   new_st->op = code->op;
7349   new_st->expr1 = code->expr1;
7350   new_st->expr2 = code->expr2;
7351   new_st->block = code->block;
7352   if (!ns->code)
7353     ns->code = new_st;
7354   else
7355     ns->code->next = new_st;
7356   code->op = EXEC_BLOCK;
7357   code->ext.block.assoc = NULL;
7358   code->expr1 = code->expr2 =  NULL;
7359   code->block = NULL;
7360
7361   code = new_st;
7362
7363   /* Transform to EXEC_SELECT.  */
7364   code->op = EXEC_SELECT;
7365   gfc_add_component_ref (code->expr1, "$vptr");
7366   gfc_add_component_ref (code->expr1, "$hash");
7367
7368   /* Loop over TYPE IS / CLASS IS cases.  */
7369   for (body = code->block; body; body = body->block)
7370     {
7371       c = body->ext.case_list;
7372
7373       if (c->ts.type == BT_DERIVED)
7374         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
7375                                              c->ts.u.derived->hash_value);
7376
7377       else if (c->ts.type == BT_UNKNOWN)
7378         continue;
7379
7380       /* Assign temporary to selector.  */
7381       if (c->ts.type == BT_CLASS)
7382         sprintf (name, "tmp$class$%s", c->ts.u.derived->name);
7383       else
7384         sprintf (name, "tmp$type$%s", c->ts.u.derived->name);
7385       st = gfc_find_symtree (ns->sym_root, name);
7386       new_st = gfc_get_code ();
7387       new_st->expr1 = gfc_get_variable_expr (st);
7388       new_st->expr2 = gfc_get_variable_expr (code->expr1->symtree);
7389       if (c->ts.type == BT_DERIVED)
7390         {
7391           new_st->op = EXEC_POINTER_ASSIGN;
7392           gfc_add_component_ref (new_st->expr2, "$data");
7393         }
7394       else
7395         new_st->op = EXEC_POINTER_ASSIGN;
7396       new_st->next = body->next;
7397       body->next = new_st;
7398     }
7399     
7400   /* Take out CLASS IS cases for separate treatment.  */
7401   body = code;
7402   while (body && body->block)
7403     {
7404       if (body->block->ext.case_list->ts.type == BT_CLASS)
7405         {
7406           /* Add to class_is list.  */
7407           if (class_is == NULL)
7408             { 
7409               class_is = body->block;
7410               tail = class_is;
7411             }
7412           else
7413             {
7414               for (tail = class_is; tail->block; tail = tail->block) ;
7415               tail->block = body->block;
7416               tail = tail->block;
7417             }
7418           /* Remove from EXEC_SELECT list.  */
7419           body->block = body->block->block;
7420           tail->block = NULL;
7421         }
7422       else
7423         body = body->block;
7424     }
7425
7426   if (class_is)
7427     {
7428       gfc_symbol *vtab;
7429       
7430       if (!default_case)
7431         {
7432           /* Add a default case to hold the CLASS IS cases.  */
7433           for (tail = code; tail->block; tail = tail->block) ;
7434           tail->block = gfc_get_code ();
7435           tail = tail->block;
7436           tail->op = EXEC_SELECT_TYPE;
7437           tail->ext.case_list = gfc_get_case ();
7438           tail->ext.case_list->ts.type = BT_UNKNOWN;
7439           tail->next = NULL;
7440           default_case = tail;
7441         }
7442
7443       /* More than one CLASS IS block?  */
7444       if (class_is->block)
7445         {
7446           gfc_code **c1,*c2;
7447           bool swapped;
7448           /* Sort CLASS IS blocks by extension level.  */
7449           do
7450             {
7451               swapped = false;
7452               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
7453                 {
7454                   c2 = (*c1)->block;
7455                   /* F03:C817 (check for doubles).  */
7456                   if ((*c1)->ext.case_list->ts.u.derived->hash_value
7457                       == c2->ext.case_list->ts.u.derived->hash_value)
7458                     {
7459                       gfc_error ("Double CLASS IS block in SELECT TYPE "
7460                                  "statement at %L", &c2->ext.case_list->where);
7461                       return;
7462                     }
7463                   if ((*c1)->ext.case_list->ts.u.derived->attr.extension
7464                       < c2->ext.case_list->ts.u.derived->attr.extension)
7465                     {
7466                       /* Swap.  */
7467                       (*c1)->block = c2->block;
7468                       c2->block = *c1;
7469                       *c1 = c2;
7470                       swapped = true;
7471                     }
7472                 }
7473             }
7474           while (swapped);
7475         }
7476         
7477       /* Generate IF chain.  */
7478       if_st = gfc_get_code ();
7479       if_st->op = EXEC_IF;
7480       new_st = if_st;
7481       for (body = class_is; body; body = body->block)
7482         {
7483           new_st->block = gfc_get_code ();
7484           new_st = new_st->block;
7485           new_st->op = EXEC_IF;
7486           /* Set up IF condition: Call _gfortran_is_extension_of.  */
7487           new_st->expr1 = gfc_get_expr ();
7488           new_st->expr1->expr_type = EXPR_FUNCTION;
7489           new_st->expr1->ts.type = BT_LOGICAL;
7490           new_st->expr1->ts.kind = 4;
7491           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
7492           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
7493           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
7494           /* Set up arguments.  */
7495           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
7496           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
7497           gfc_add_component_ref (new_st->expr1->value.function.actual->expr, "$vptr");
7498           vtab = gfc_find_derived_vtab (body->ext.case_list->ts.u.derived, true);
7499           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
7500           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
7501           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
7502           new_st->next = body->next;
7503         }
7504         if (default_case->next)
7505           {
7506             new_st->block = gfc_get_code ();
7507             new_st = new_st->block;
7508             new_st->op = EXEC_IF;
7509             new_st->next = default_case->next;
7510           }
7511           
7512         /* Replace CLASS DEFAULT code by the IF chain.  */
7513         default_case->next = if_st;
7514     }
7515
7516   resolve_select (code);
7517
7518 }
7519
7520
7521 /* Resolve a transfer statement. This is making sure that:
7522    -- a derived type being transferred has only non-pointer components
7523    -- a derived type being transferred doesn't have private components, unless 
7524       it's being transferred from the module where the type was defined
7525    -- we're not trying to transfer a whole assumed size array.  */
7526
7527 static void
7528 resolve_transfer (gfc_code *code)
7529 {
7530   gfc_typespec *ts;
7531   gfc_symbol *sym;
7532   gfc_ref *ref;
7533   gfc_expr *exp;
7534
7535   exp = code->expr1;
7536
7537   if (exp->expr_type != EXPR_VARIABLE && exp->expr_type != EXPR_FUNCTION)
7538     return;
7539
7540   sym = exp->symtree->n.sym;
7541   ts = &sym->ts;
7542
7543   /* Go to actual component transferred.  */
7544   for (ref = code->expr1->ref; ref; ref = ref->next)
7545     if (ref->type == REF_COMPONENT)
7546       ts = &ref->u.c.component->ts;
7547
7548   if (ts->type == BT_DERIVED)
7549     {
7550       /* Check that transferred derived type doesn't contain POINTER
7551          components.  */
7552       if (ts->u.derived->attr.pointer_comp)
7553         {
7554           gfc_error ("Data transfer element at %L cannot have "
7555                      "POINTER components", &code->loc);
7556           return;
7557         }
7558
7559       if (ts->u.derived->attr.alloc_comp)
7560         {
7561           gfc_error ("Data transfer element at %L cannot have "
7562                      "ALLOCATABLE components", &code->loc);
7563           return;
7564         }
7565
7566       if (derived_inaccessible (ts->u.derived))
7567         {
7568           gfc_error ("Data transfer element at %L cannot have "
7569                      "PRIVATE components",&code->loc);
7570           return;
7571         }
7572     }
7573
7574   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
7575       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
7576     {
7577       gfc_error ("Data transfer element at %L cannot be a full reference to "
7578                  "an assumed-size array", &code->loc);
7579       return;
7580     }
7581 }
7582
7583
7584 /*********** Toplevel code resolution subroutines ***********/
7585
7586 /* Find the set of labels that are reachable from this block.  We also
7587    record the last statement in each block.  */
7588      
7589 static void
7590 find_reachable_labels (gfc_code *block)
7591 {
7592   gfc_code *c;
7593
7594   if (!block)
7595     return;
7596
7597   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
7598
7599   /* Collect labels in this block.  We don't keep those corresponding
7600      to END {IF|SELECT}, these are checked in resolve_branch by going
7601      up through the code_stack.  */
7602   for (c = block; c; c = c->next)
7603     {
7604       if (c->here && c->op != EXEC_END_BLOCK)
7605         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
7606     }
7607
7608   /* Merge with labels from parent block.  */
7609   if (cs_base->prev)
7610     {
7611       gcc_assert (cs_base->prev->reachable_labels);
7612       bitmap_ior_into (cs_base->reachable_labels,
7613                        cs_base->prev->reachable_labels);
7614     }
7615 }
7616
7617
7618 static void
7619 resolve_sync (gfc_code *code)
7620 {
7621   /* Check imageset. The * case matches expr1 == NULL.  */
7622   if (code->expr1)
7623     {
7624       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
7625         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
7626                    "INTEGER expression", &code->expr1->where);
7627       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
7628           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
7629         gfc_error ("Imageset argument at %L must between 1 and num_images()",
7630                    &code->expr1->where);
7631       else if (code->expr1->expr_type == EXPR_ARRAY
7632                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
7633         {
7634            gfc_constructor *cons;
7635            cons = gfc_constructor_first (code->expr1->value.constructor);
7636            for (; cons; cons = gfc_constructor_next (cons))
7637              if (cons->expr->expr_type == EXPR_CONSTANT
7638                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
7639                gfc_error ("Imageset argument at %L must between 1 and "
7640                           "num_images()", &cons->expr->where);
7641         }
7642     }
7643
7644   /* Check STAT.  */
7645   if (code->expr2
7646       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
7647           || code->expr2->expr_type != EXPR_VARIABLE))
7648     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
7649                &code->expr2->where);
7650
7651   /* Check ERRMSG.  */
7652   if (code->expr3
7653       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
7654           || code->expr3->expr_type != EXPR_VARIABLE))
7655     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
7656                &code->expr3->where);
7657 }
7658
7659
7660 /* Given a branch to a label, see if the branch is conforming.
7661    The code node describes where the branch is located.  */
7662
7663 static void
7664 resolve_branch (gfc_st_label *label, gfc_code *code)
7665 {
7666   code_stack *stack;
7667
7668   if (label == NULL)
7669     return;
7670
7671   /* Step one: is this a valid branching target?  */
7672
7673   if (label->defined == ST_LABEL_UNKNOWN)
7674     {
7675       gfc_error ("Label %d referenced at %L is never defined", label->value,
7676                  &label->where);
7677       return;
7678     }
7679
7680   if (label->defined != ST_LABEL_TARGET)
7681     {
7682       gfc_error ("Statement at %L is not a valid branch target statement "
7683                  "for the branch statement at %L", &label->where, &code->loc);
7684       return;
7685     }
7686
7687   /* Step two: make sure this branch is not a branch to itself ;-)  */
7688
7689   if (code->here == label)
7690     {
7691       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
7692       return;
7693     }
7694
7695   /* Step three:  See if the label is in the same block as the
7696      branching statement.  The hard work has been done by setting up
7697      the bitmap reachable_labels.  */
7698
7699   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
7700     {
7701       /* Check now whether there is a CRITICAL construct; if so, check
7702          whether the label is still visible outside of the CRITICAL block,
7703          which is invalid.  */
7704       for (stack = cs_base; stack; stack = stack->prev)
7705         if (stack->current->op == EXEC_CRITICAL
7706             && bitmap_bit_p (stack->reachable_labels, label->value))
7707           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
7708                       " at %L", &code->loc, &label->where);
7709
7710       return;
7711     }
7712
7713   /* Step four:  If we haven't found the label in the bitmap, it may
7714     still be the label of the END of the enclosing block, in which
7715     case we find it by going up the code_stack.  */
7716
7717   for (stack = cs_base; stack; stack = stack->prev)
7718     {
7719       if (stack->current->next && stack->current->next->here == label)
7720         break;
7721       if (stack->current->op == EXEC_CRITICAL)
7722         {
7723           /* Note: A label at END CRITICAL does not leave the CRITICAL
7724              construct as END CRITICAL is still part of it.  */
7725           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
7726                       " at %L", &code->loc, &label->where);
7727           return;
7728         }
7729     }
7730
7731   if (stack)
7732     {
7733       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
7734       return;
7735     }
7736
7737   /* The label is not in an enclosing block, so illegal.  This was
7738      allowed in Fortran 66, so we allow it as extension.  No
7739      further checks are necessary in this case.  */
7740   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
7741                   "as the GOTO statement at %L", &label->where,
7742                   &code->loc);
7743   return;
7744 }
7745
7746
7747 /* Check whether EXPR1 has the same shape as EXPR2.  */
7748
7749 static gfc_try
7750 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
7751 {
7752   mpz_t shape[GFC_MAX_DIMENSIONS];
7753   mpz_t shape2[GFC_MAX_DIMENSIONS];
7754   gfc_try result = FAILURE;
7755   int i;
7756
7757   /* Compare the rank.  */
7758   if (expr1->rank != expr2->rank)
7759     return result;
7760
7761   /* Compare the size of each dimension.  */
7762   for (i=0; i<expr1->rank; i++)
7763     {
7764       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
7765         goto ignore;
7766
7767       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
7768         goto ignore;
7769
7770       if (mpz_cmp (shape[i], shape2[i]))
7771         goto over;
7772     }
7773
7774   /* When either of the two expression is an assumed size array, we
7775      ignore the comparison of dimension sizes.  */
7776 ignore:
7777   result = SUCCESS;
7778
7779 over:
7780   for (i--; i >= 0; i--)
7781     {
7782       mpz_clear (shape[i]);
7783       mpz_clear (shape2[i]);
7784     }
7785   return result;
7786 }
7787
7788
7789 /* Check whether a WHERE assignment target or a WHERE mask expression
7790    has the same shape as the outmost WHERE mask expression.  */
7791
7792 static void
7793 resolve_where (gfc_code *code, gfc_expr *mask)
7794 {
7795   gfc_code *cblock;
7796   gfc_code *cnext;
7797   gfc_expr *e = NULL;
7798
7799   cblock = code->block;
7800
7801   /* Store the first WHERE mask-expr of the WHERE statement or construct.
7802      In case of nested WHERE, only the outmost one is stored.  */
7803   if (mask == NULL) /* outmost WHERE */
7804     e = cblock->expr1;
7805   else /* inner WHERE */
7806     e = mask;
7807
7808   while (cblock)
7809     {
7810       if (cblock->expr1)
7811         {
7812           /* Check if the mask-expr has a consistent shape with the
7813              outmost WHERE mask-expr.  */
7814           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
7815             gfc_error ("WHERE mask at %L has inconsistent shape",
7816                        &cblock->expr1->where);
7817          }
7818
7819       /* the assignment statement of a WHERE statement, or the first
7820          statement in where-body-construct of a WHERE construct */
7821       cnext = cblock->next;
7822       while (cnext)
7823         {
7824           switch (cnext->op)
7825             {
7826             /* WHERE assignment statement */
7827             case EXEC_ASSIGN:
7828
7829               /* Check shape consistent for WHERE assignment target.  */
7830               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
7831                gfc_error ("WHERE assignment target at %L has "
7832                           "inconsistent shape", &cnext->expr1->where);
7833               break;
7834
7835   
7836             case EXEC_ASSIGN_CALL:
7837               resolve_call (cnext);
7838               if (!cnext->resolved_sym->attr.elemental)
7839                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7840                           &cnext->ext.actual->expr->where);
7841               break;
7842
7843             /* WHERE or WHERE construct is part of a where-body-construct */
7844             case EXEC_WHERE:
7845               resolve_where (cnext, e);
7846               break;
7847
7848             default:
7849               gfc_error ("Unsupported statement inside WHERE at %L",
7850                          &cnext->loc);
7851             }
7852          /* the next statement within the same where-body-construct */
7853          cnext = cnext->next;
7854        }
7855     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7856     cblock = cblock->block;
7857   }
7858 }
7859
7860
7861 /* Resolve assignment in FORALL construct.
7862    NVAR is the number of FORALL index variables, and VAR_EXPR records the
7863    FORALL index variables.  */
7864
7865 static void
7866 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
7867 {
7868   int n;
7869
7870   for (n = 0; n < nvar; n++)
7871     {
7872       gfc_symbol *forall_index;
7873
7874       forall_index = var_expr[n]->symtree->n.sym;
7875
7876       /* Check whether the assignment target is one of the FORALL index
7877          variable.  */
7878       if ((code->expr1->expr_type == EXPR_VARIABLE)
7879           && (code->expr1->symtree->n.sym == forall_index))
7880         gfc_error ("Assignment to a FORALL index variable at %L",
7881                    &code->expr1->where);
7882       else
7883         {
7884           /* If one of the FORALL index variables doesn't appear in the
7885              assignment variable, then there could be a many-to-one
7886              assignment.  Emit a warning rather than an error because the
7887              mask could be resolving this problem.  */
7888           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
7889             gfc_warning ("The FORALL with index '%s' is not used on the "
7890                          "left side of the assignment at %L and so might "
7891                          "cause multiple assignment to this object",
7892                          var_expr[n]->symtree->name, &code->expr1->where);
7893         }
7894     }
7895 }
7896
7897
7898 /* Resolve WHERE statement in FORALL construct.  */
7899
7900 static void
7901 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
7902                                   gfc_expr **var_expr)
7903 {
7904   gfc_code *cblock;
7905   gfc_code *cnext;
7906
7907   cblock = code->block;
7908   while (cblock)
7909     {
7910       /* the assignment statement of a WHERE statement, or the first
7911          statement in where-body-construct of a WHERE construct */
7912       cnext = cblock->next;
7913       while (cnext)
7914         {
7915           switch (cnext->op)
7916             {
7917             /* WHERE assignment statement */
7918             case EXEC_ASSIGN:
7919               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
7920               break;
7921   
7922             /* WHERE operator assignment statement */
7923             case EXEC_ASSIGN_CALL:
7924               resolve_call (cnext);
7925               if (!cnext->resolved_sym->attr.elemental)
7926                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7927                           &cnext->ext.actual->expr->where);
7928               break;
7929
7930             /* WHERE or WHERE construct is part of a where-body-construct */
7931             case EXEC_WHERE:
7932               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
7933               break;
7934
7935             default:
7936               gfc_error ("Unsupported statement inside WHERE at %L",
7937                          &cnext->loc);
7938             }
7939           /* the next statement within the same where-body-construct */
7940           cnext = cnext->next;
7941         }
7942       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7943       cblock = cblock->block;
7944     }
7945 }
7946
7947
7948 /* Traverse the FORALL body to check whether the following errors exist:
7949    1. For assignment, check if a many-to-one assignment happens.
7950    2. For WHERE statement, check the WHERE body to see if there is any
7951       many-to-one assignment.  */
7952
7953 static void
7954 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
7955 {
7956   gfc_code *c;
7957
7958   c = code->block->next;
7959   while (c)
7960     {
7961       switch (c->op)
7962         {
7963         case EXEC_ASSIGN:
7964         case EXEC_POINTER_ASSIGN:
7965           gfc_resolve_assign_in_forall (c, nvar, var_expr);
7966           break;
7967
7968         case EXEC_ASSIGN_CALL:
7969           resolve_call (c);
7970           break;
7971
7972         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
7973            there is no need to handle it here.  */
7974         case EXEC_FORALL:
7975           break;
7976         case EXEC_WHERE:
7977           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
7978           break;
7979         default:
7980           break;
7981         }
7982       /* The next statement in the FORALL body.  */
7983       c = c->next;
7984     }
7985 }
7986
7987
7988 /* Counts the number of iterators needed inside a forall construct, including
7989    nested forall constructs. This is used to allocate the needed memory 
7990    in gfc_resolve_forall.  */
7991
7992 static int 
7993 gfc_count_forall_iterators (gfc_code *code)
7994 {
7995   int max_iters, sub_iters, current_iters;
7996   gfc_forall_iterator *fa;
7997
7998   gcc_assert(code->op == EXEC_FORALL);
7999   max_iters = 0;
8000   current_iters = 0;
8001
8002   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8003     current_iters ++;
8004   
8005   code = code->block->next;
8006
8007   while (code)
8008     {          
8009       if (code->op == EXEC_FORALL)
8010         {
8011           sub_iters = gfc_count_forall_iterators (code);
8012           if (sub_iters > max_iters)
8013             max_iters = sub_iters;
8014         }
8015       code = code->next;
8016     }
8017
8018   return current_iters + max_iters;
8019 }
8020
8021
8022 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8023    gfc_resolve_forall_body to resolve the FORALL body.  */
8024
8025 static void
8026 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8027 {
8028   static gfc_expr **var_expr;
8029   static int total_var = 0;
8030   static int nvar = 0;
8031   int old_nvar, tmp;
8032   gfc_forall_iterator *fa;
8033   int i;
8034
8035   old_nvar = nvar;
8036
8037   /* Start to resolve a FORALL construct   */
8038   if (forall_save == 0)
8039     {
8040       /* Count the total number of FORALL index in the nested FORALL
8041          construct in order to allocate the VAR_EXPR with proper size.  */
8042       total_var = gfc_count_forall_iterators (code);
8043
8044       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8045       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
8046     }
8047
8048   /* The information about FORALL iterator, including FORALL index start, end
8049      and stride. The FORALL index can not appear in start, end or stride.  */
8050   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8051     {
8052       /* Check if any outer FORALL index name is the same as the current
8053          one.  */
8054       for (i = 0; i < nvar; i++)
8055         {
8056           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8057             {
8058               gfc_error ("An outer FORALL construct already has an index "
8059                          "with this name %L", &fa->var->where);
8060             }
8061         }
8062
8063       /* Record the current FORALL index.  */
8064       var_expr[nvar] = gfc_copy_expr (fa->var);
8065
8066       nvar++;
8067
8068       /* No memory leak.  */
8069       gcc_assert (nvar <= total_var);
8070     }
8071
8072   /* Resolve the FORALL body.  */
8073   gfc_resolve_forall_body (code, nvar, var_expr);
8074
8075   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8076   gfc_resolve_blocks (code->block, ns);
8077
8078   tmp = nvar;
8079   nvar = old_nvar;
8080   /* Free only the VAR_EXPRs allocated in this frame.  */
8081   for (i = nvar; i < tmp; i++)
8082      gfc_free_expr (var_expr[i]);
8083
8084   if (nvar == 0)
8085     {
8086       /* We are in the outermost FORALL construct.  */
8087       gcc_assert (forall_save == 0);
8088
8089       /* VAR_EXPR is not needed any more.  */
8090       gfc_free (var_expr);
8091       total_var = 0;
8092     }
8093 }
8094
8095
8096 /* Resolve a BLOCK construct statement.  */
8097
8098 static void
8099 resolve_block_construct (gfc_code* code)
8100 {
8101   /* For an ASSOCIATE block, the associations (and their targets) are already
8102      resolved during gfc_resolve_symbol.  */
8103
8104   /* Resolve the BLOCK's namespace.  */
8105   gfc_resolve (code->ext.block.ns);
8106 }
8107
8108
8109 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
8110    DO code nodes.  */
8111
8112 static void resolve_code (gfc_code *, gfc_namespace *);
8113
8114 void
8115 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8116 {
8117   gfc_try t;
8118
8119   for (; b; b = b->block)
8120     {
8121       t = gfc_resolve_expr (b->expr1);
8122       if (gfc_resolve_expr (b->expr2) == FAILURE)
8123         t = FAILURE;
8124
8125       switch (b->op)
8126         {
8127         case EXEC_IF:
8128           if (t == SUCCESS && b->expr1 != NULL
8129               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8130             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8131                        &b->expr1->where);
8132           break;
8133
8134         case EXEC_WHERE:
8135           if (t == SUCCESS
8136               && b->expr1 != NULL
8137               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8138             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8139                        &b->expr1->where);
8140           break;
8141
8142         case EXEC_GOTO:
8143           resolve_branch (b->label1, b);
8144           break;
8145
8146         case EXEC_BLOCK:
8147           resolve_block_construct (b);
8148           break;
8149
8150         case EXEC_SELECT:
8151         case EXEC_SELECT_TYPE:
8152         case EXEC_FORALL:
8153         case EXEC_DO:
8154         case EXEC_DO_WHILE:
8155         case EXEC_CRITICAL:
8156         case EXEC_READ:
8157         case EXEC_WRITE:
8158         case EXEC_IOLENGTH:
8159         case EXEC_WAIT:
8160           break;
8161
8162         case EXEC_OMP_ATOMIC:
8163         case EXEC_OMP_CRITICAL:
8164         case EXEC_OMP_DO:
8165         case EXEC_OMP_MASTER:
8166         case EXEC_OMP_ORDERED:
8167         case EXEC_OMP_PARALLEL:
8168         case EXEC_OMP_PARALLEL_DO:
8169         case EXEC_OMP_PARALLEL_SECTIONS:
8170         case EXEC_OMP_PARALLEL_WORKSHARE:
8171         case EXEC_OMP_SECTIONS:
8172         case EXEC_OMP_SINGLE:
8173         case EXEC_OMP_TASK:
8174         case EXEC_OMP_TASKWAIT:
8175         case EXEC_OMP_WORKSHARE:
8176           break;
8177
8178         default:
8179           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
8180         }
8181
8182       resolve_code (b->next, ns);
8183     }
8184 }
8185
8186
8187 /* Does everything to resolve an ordinary assignment.  Returns true
8188    if this is an interface assignment.  */
8189 static bool
8190 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
8191 {
8192   bool rval = false;
8193   gfc_expr *lhs;
8194   gfc_expr *rhs;
8195   int llen = 0;
8196   int rlen = 0;
8197   int n;
8198   gfc_ref *ref;
8199
8200   if (gfc_extend_assign (code, ns) == SUCCESS)
8201     {
8202       gfc_expr** rhsptr;
8203
8204       if (code->op == EXEC_ASSIGN_CALL)
8205         {
8206           lhs = code->ext.actual->expr;
8207           rhsptr = &code->ext.actual->next->expr;
8208         }
8209       else
8210         {
8211           gfc_actual_arglist* args;
8212           gfc_typebound_proc* tbp;
8213
8214           gcc_assert (code->op == EXEC_COMPCALL);
8215
8216           args = code->expr1->value.compcall.actual;
8217           lhs = args->expr;
8218           rhsptr = &args->next->expr;
8219
8220           tbp = code->expr1->value.compcall.tbp;
8221           gcc_assert (!tbp->is_generic);
8222         }
8223
8224       /* Make a temporary rhs when there is a default initializer
8225          and rhs is the same symbol as the lhs.  */
8226       if ((*rhsptr)->expr_type == EXPR_VARIABLE
8227             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
8228             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
8229             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
8230         *rhsptr = gfc_get_parentheses (*rhsptr);
8231
8232       return true;
8233     }
8234
8235   lhs = code->expr1;
8236   rhs = code->expr2;
8237
8238   if (rhs->is_boz
8239       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
8240                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
8241                          &code->loc) == FAILURE)
8242     return false;
8243
8244   /* Handle the case of a BOZ literal on the RHS.  */
8245   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
8246     {
8247       int rc;
8248       if (gfc_option.warn_surprising)
8249         gfc_warning ("BOZ literal at %L is bitwise transferred "
8250                      "non-integer symbol '%s'", &code->loc,
8251                      lhs->symtree->n.sym->name);
8252
8253       if (!gfc_convert_boz (rhs, &lhs->ts))
8254         return false;
8255       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
8256         {
8257           if (rc == ARITH_UNDERFLOW)
8258             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
8259                        ". This check can be disabled with the option "
8260                        "-fno-range-check", &rhs->where);
8261           else if (rc == ARITH_OVERFLOW)
8262             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
8263                        ". This check can be disabled with the option "
8264                        "-fno-range-check", &rhs->where);
8265           else if (rc == ARITH_NAN)
8266             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
8267                        ". This check can be disabled with the option "
8268                        "-fno-range-check", &rhs->where);
8269           return false;
8270         }
8271     }
8272
8273
8274   if (lhs->ts.type == BT_CHARACTER
8275         && gfc_option.warn_character_truncation)
8276     {
8277       if (lhs->ts.u.cl != NULL
8278             && lhs->ts.u.cl->length != NULL
8279             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8280         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
8281
8282       if (rhs->expr_type == EXPR_CONSTANT)
8283         rlen = rhs->value.character.length;
8284
8285       else if (rhs->ts.u.cl != NULL
8286                  && rhs->ts.u.cl->length != NULL
8287                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8288         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
8289
8290       if (rlen && llen && rlen > llen)
8291         gfc_warning_now ("CHARACTER expression will be truncated "
8292                          "in assignment (%d/%d) at %L",
8293                          llen, rlen, &code->loc);
8294     }
8295
8296   /* Ensure that a vector index expression for the lvalue is evaluated
8297      to a temporary if the lvalue symbol is referenced in it.  */
8298   if (lhs->rank)
8299     {
8300       for (ref = lhs->ref; ref; ref= ref->next)
8301         if (ref->type == REF_ARRAY)
8302           {
8303             for (n = 0; n < ref->u.ar.dimen; n++)
8304               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
8305                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
8306                                            ref->u.ar.start[n]))
8307                 ref->u.ar.start[n]
8308                         = gfc_get_parentheses (ref->u.ar.start[n]);
8309           }
8310     }
8311
8312   if (gfc_pure (NULL))
8313     {
8314       if (gfc_impure_variable (lhs->symtree->n.sym))
8315         {
8316           gfc_error ("Cannot assign to variable '%s' in PURE "
8317                      "procedure at %L",
8318                       lhs->symtree->n.sym->name,
8319                       &lhs->where);
8320           return rval;
8321         }
8322
8323       if (lhs->ts.type == BT_DERIVED
8324             && lhs->expr_type == EXPR_VARIABLE
8325             && lhs->ts.u.derived->attr.pointer_comp
8326             && rhs->expr_type == EXPR_VARIABLE
8327             && (gfc_impure_variable (rhs->symtree->n.sym)
8328                 || gfc_is_coindexed (rhs)))
8329         {
8330           /* F2008, C1283.  */
8331           if (gfc_is_coindexed (rhs))
8332             gfc_error ("Coindexed expression at %L is assigned to "
8333                         "a derived type variable with a POINTER "
8334                         "component in a PURE procedure",
8335                         &rhs->where);
8336           else
8337             gfc_error ("The impure variable at %L is assigned to "
8338                         "a derived type variable with a POINTER "
8339                         "component in a PURE procedure (12.6)",
8340                         &rhs->where);
8341           return rval;
8342         }
8343
8344       /* Fortran 2008, C1283.  */
8345       if (gfc_is_coindexed (lhs))
8346         {
8347           gfc_error ("Assignment to coindexed variable at %L in a PURE "
8348                      "procedure", &rhs->where);
8349           return rval;
8350         }
8351     }
8352
8353   /* F03:7.4.1.2.  */
8354   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
8355      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
8356   if (lhs->ts.type == BT_CLASS)
8357     {
8358       gfc_error ("Variable must not be polymorphic in assignment at %L",
8359                  &lhs->where);
8360       return false;
8361     }
8362
8363   /* F2008, Section 7.2.1.2.  */
8364   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
8365     {
8366       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
8367                  "component in assignment at %L", &lhs->where);
8368       return false;
8369     }
8370
8371   gfc_check_assign (lhs, rhs, 1);
8372   return false;
8373 }
8374
8375
8376 /* Given a block of code, recursively resolve everything pointed to by this
8377    code block.  */
8378
8379 static void
8380 resolve_code (gfc_code *code, gfc_namespace *ns)
8381 {
8382   int omp_workshare_save;
8383   int forall_save;
8384   code_stack frame;
8385   gfc_try t;
8386
8387   frame.prev = cs_base;
8388   frame.head = code;
8389   cs_base = &frame;
8390
8391   find_reachable_labels (code);
8392
8393   for (; code; code = code->next)
8394     {
8395       frame.current = code;
8396       forall_save = forall_flag;
8397
8398       if (code->op == EXEC_FORALL)
8399         {
8400           forall_flag = 1;
8401           gfc_resolve_forall (code, ns, forall_save);
8402           forall_flag = 2;
8403         }
8404       else if (code->block)
8405         {
8406           omp_workshare_save = -1;
8407           switch (code->op)
8408             {
8409             case EXEC_OMP_PARALLEL_WORKSHARE:
8410               omp_workshare_save = omp_workshare_flag;
8411               omp_workshare_flag = 1;
8412               gfc_resolve_omp_parallel_blocks (code, ns);
8413               break;
8414             case EXEC_OMP_PARALLEL:
8415             case EXEC_OMP_PARALLEL_DO:
8416             case EXEC_OMP_PARALLEL_SECTIONS:
8417             case EXEC_OMP_TASK:
8418               omp_workshare_save = omp_workshare_flag;
8419               omp_workshare_flag = 0;
8420               gfc_resolve_omp_parallel_blocks (code, ns);
8421               break;
8422             case EXEC_OMP_DO:
8423               gfc_resolve_omp_do_blocks (code, ns);
8424               break;
8425             case EXEC_SELECT_TYPE:
8426               gfc_current_ns = code->ext.block.ns;
8427               gfc_resolve_blocks (code->block, gfc_current_ns);
8428               gfc_current_ns = ns;
8429               break;
8430             case EXEC_OMP_WORKSHARE:
8431               omp_workshare_save = omp_workshare_flag;
8432               omp_workshare_flag = 1;
8433               /* FALLTHROUGH */
8434             default:
8435               gfc_resolve_blocks (code->block, ns);
8436               break;
8437             }
8438
8439           if (omp_workshare_save != -1)
8440             omp_workshare_flag = omp_workshare_save;
8441         }
8442
8443       t = SUCCESS;
8444       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
8445         t = gfc_resolve_expr (code->expr1);
8446       forall_flag = forall_save;
8447
8448       if (gfc_resolve_expr (code->expr2) == FAILURE)
8449         t = FAILURE;
8450
8451       if (code->op == EXEC_ALLOCATE
8452           && gfc_resolve_expr (code->expr3) == FAILURE)
8453         t = FAILURE;
8454
8455       switch (code->op)
8456         {
8457         case EXEC_NOP:
8458         case EXEC_END_BLOCK:
8459         case EXEC_CYCLE:
8460         case EXEC_PAUSE:
8461         case EXEC_STOP:
8462         case EXEC_ERROR_STOP:
8463         case EXEC_EXIT:
8464         case EXEC_CONTINUE:
8465         case EXEC_DT_END:
8466         case EXEC_ASSIGN_CALL:
8467         case EXEC_CRITICAL:
8468           break;
8469
8470         case EXEC_SYNC_ALL:
8471         case EXEC_SYNC_IMAGES:
8472         case EXEC_SYNC_MEMORY:
8473           resolve_sync (code);
8474           break;
8475
8476         case EXEC_ENTRY:
8477           /* Keep track of which entry we are up to.  */
8478           current_entry_id = code->ext.entry->id;
8479           break;
8480
8481         case EXEC_WHERE:
8482           resolve_where (code, NULL);
8483           break;
8484
8485         case EXEC_GOTO:
8486           if (code->expr1 != NULL)
8487             {
8488               if (code->expr1->ts.type != BT_INTEGER)
8489                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
8490                            "INTEGER variable", &code->expr1->where);
8491               else if (code->expr1->symtree->n.sym->attr.assign != 1)
8492                 gfc_error ("Variable '%s' has not been assigned a target "
8493                            "label at %L", code->expr1->symtree->n.sym->name,
8494                            &code->expr1->where);
8495             }
8496           else
8497             resolve_branch (code->label1, code);
8498           break;
8499
8500         case EXEC_RETURN:
8501           if (code->expr1 != NULL
8502                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
8503             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
8504                        "INTEGER return specifier", &code->expr1->where);
8505           break;
8506
8507         case EXEC_INIT_ASSIGN:
8508         case EXEC_END_PROCEDURE:
8509           break;
8510
8511         case EXEC_ASSIGN:
8512           if (t == FAILURE)
8513             break;
8514
8515           if (resolve_ordinary_assign (code, ns))
8516             {
8517               if (code->op == EXEC_COMPCALL)
8518                 goto compcall;
8519               else
8520                 goto call;
8521             }
8522           break;
8523
8524         case EXEC_LABEL_ASSIGN:
8525           if (code->label1->defined == ST_LABEL_UNKNOWN)
8526             gfc_error ("Label %d referenced at %L is never defined",
8527                        code->label1->value, &code->label1->where);
8528           if (t == SUCCESS
8529               && (code->expr1->expr_type != EXPR_VARIABLE
8530                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
8531                   || code->expr1->symtree->n.sym->ts.kind
8532                      != gfc_default_integer_kind
8533                   || code->expr1->symtree->n.sym->as != NULL))
8534             gfc_error ("ASSIGN statement at %L requires a scalar "
8535                        "default INTEGER variable", &code->expr1->where);
8536           break;
8537
8538         case EXEC_POINTER_ASSIGN:
8539           if (t == FAILURE)
8540             break;
8541
8542           gfc_check_pointer_assign (code->expr1, code->expr2);
8543           break;
8544
8545         case EXEC_ARITHMETIC_IF:
8546           if (t == SUCCESS
8547               && code->expr1->ts.type != BT_INTEGER
8548               && code->expr1->ts.type != BT_REAL)
8549             gfc_error ("Arithmetic IF statement at %L requires a numeric "
8550                        "expression", &code->expr1->where);
8551
8552           resolve_branch (code->label1, code);
8553           resolve_branch (code->label2, code);
8554           resolve_branch (code->label3, code);
8555           break;
8556
8557         case EXEC_IF:
8558           if (t == SUCCESS && code->expr1 != NULL
8559               && (code->expr1->ts.type != BT_LOGICAL
8560                   || code->expr1->rank != 0))
8561             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8562                        &code->expr1->where);
8563           break;
8564
8565         case EXEC_CALL:
8566         call:
8567           resolve_call (code);
8568           break;
8569
8570         case EXEC_COMPCALL:
8571         compcall:
8572           resolve_typebound_subroutine (code);
8573           break;
8574
8575         case EXEC_CALL_PPC:
8576           resolve_ppc_call (code);
8577           break;
8578
8579         case EXEC_SELECT:
8580           /* Select is complicated. Also, a SELECT construct could be
8581              a transformed computed GOTO.  */
8582           resolve_select (code);
8583           break;
8584
8585         case EXEC_SELECT_TYPE:
8586           resolve_select_type (code);
8587           break;
8588
8589         case EXEC_BLOCK:
8590           gfc_resolve (code->ext.block.ns);
8591           break;
8592
8593         case EXEC_DO:
8594           if (code->ext.iterator != NULL)
8595             {
8596               gfc_iterator *iter = code->ext.iterator;
8597               if (gfc_resolve_iterator (iter, true) != FAILURE)
8598                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
8599             }
8600           break;
8601
8602         case EXEC_DO_WHILE:
8603           if (code->expr1 == NULL)
8604             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
8605           if (t == SUCCESS
8606               && (code->expr1->rank != 0
8607                   || code->expr1->ts.type != BT_LOGICAL))
8608             gfc_error ("Exit condition of DO WHILE loop at %L must be "
8609                        "a scalar LOGICAL expression", &code->expr1->where);
8610           break;
8611
8612         case EXEC_ALLOCATE:
8613           if (t == SUCCESS)
8614             resolve_allocate_deallocate (code, "ALLOCATE");
8615
8616           break;
8617
8618         case EXEC_DEALLOCATE:
8619           if (t == SUCCESS)
8620             resolve_allocate_deallocate (code, "DEALLOCATE");
8621
8622           break;
8623
8624         case EXEC_OPEN:
8625           if (gfc_resolve_open (code->ext.open) == FAILURE)
8626             break;
8627
8628           resolve_branch (code->ext.open->err, code);
8629           break;
8630
8631         case EXEC_CLOSE:
8632           if (gfc_resolve_close (code->ext.close) == FAILURE)
8633             break;
8634
8635           resolve_branch (code->ext.close->err, code);
8636           break;
8637
8638         case EXEC_BACKSPACE:
8639         case EXEC_ENDFILE:
8640         case EXEC_REWIND:
8641         case EXEC_FLUSH:
8642           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
8643             break;
8644
8645           resolve_branch (code->ext.filepos->err, code);
8646           break;
8647
8648         case EXEC_INQUIRE:
8649           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8650               break;
8651
8652           resolve_branch (code->ext.inquire->err, code);
8653           break;
8654
8655         case EXEC_IOLENGTH:
8656           gcc_assert (code->ext.inquire != NULL);
8657           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8658             break;
8659
8660           resolve_branch (code->ext.inquire->err, code);
8661           break;
8662
8663         case EXEC_WAIT:
8664           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
8665             break;
8666
8667           resolve_branch (code->ext.wait->err, code);
8668           resolve_branch (code->ext.wait->end, code);
8669           resolve_branch (code->ext.wait->eor, code);
8670           break;
8671
8672         case EXEC_READ:
8673         case EXEC_WRITE:
8674           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
8675             break;
8676
8677           resolve_branch (code->ext.dt->err, code);
8678           resolve_branch (code->ext.dt->end, code);
8679           resolve_branch (code->ext.dt->eor, code);
8680           break;
8681
8682         case EXEC_TRANSFER:
8683           resolve_transfer (code);
8684           break;
8685
8686         case EXEC_FORALL:
8687           resolve_forall_iterators (code->ext.forall_iterator);
8688
8689           if (code->expr1 != NULL && code->expr1->ts.type != BT_LOGICAL)
8690             gfc_error ("FORALL mask clause at %L requires a LOGICAL "
8691                        "expression", &code->expr1->where);
8692           break;
8693
8694         case EXEC_OMP_ATOMIC:
8695         case EXEC_OMP_BARRIER:
8696         case EXEC_OMP_CRITICAL:
8697         case EXEC_OMP_FLUSH:
8698         case EXEC_OMP_DO:
8699         case EXEC_OMP_MASTER:
8700         case EXEC_OMP_ORDERED:
8701         case EXEC_OMP_SECTIONS:
8702         case EXEC_OMP_SINGLE:
8703         case EXEC_OMP_TASKWAIT:
8704         case EXEC_OMP_WORKSHARE:
8705           gfc_resolve_omp_directive (code, ns);
8706           break;
8707
8708         case EXEC_OMP_PARALLEL:
8709         case EXEC_OMP_PARALLEL_DO:
8710         case EXEC_OMP_PARALLEL_SECTIONS:
8711         case EXEC_OMP_PARALLEL_WORKSHARE:
8712         case EXEC_OMP_TASK:
8713           omp_workshare_save = omp_workshare_flag;
8714           omp_workshare_flag = 0;
8715           gfc_resolve_omp_directive (code, ns);
8716           omp_workshare_flag = omp_workshare_save;
8717           break;
8718
8719         default:
8720           gfc_internal_error ("resolve_code(): Bad statement code");
8721         }
8722     }
8723
8724   cs_base = frame.prev;
8725 }
8726
8727
8728 /* Resolve initial values and make sure they are compatible with
8729    the variable.  */
8730
8731 static void
8732 resolve_values (gfc_symbol *sym)
8733 {
8734   if (sym->value == NULL)
8735     return;
8736
8737   if (gfc_resolve_expr (sym->value) == FAILURE)
8738     return;
8739
8740   gfc_check_assign_symbol (sym, sym->value);
8741 }
8742
8743
8744 /* Verify the binding labels for common blocks that are BIND(C).  The label
8745    for a BIND(C) common block must be identical in all scoping units in which
8746    the common block is declared.  Further, the binding label can not collide
8747    with any other global entity in the program.  */
8748
8749 static void
8750 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
8751 {
8752   if (comm_block_tree->n.common->is_bind_c == 1)
8753     {
8754       gfc_gsymbol *binding_label_gsym;
8755       gfc_gsymbol *comm_name_gsym;
8756
8757       /* See if a global symbol exists by the common block's name.  It may
8758          be NULL if the common block is use-associated.  */
8759       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
8760                                          comm_block_tree->n.common->name);
8761       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
8762         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
8763                    "with the global entity '%s' at %L",
8764                    comm_block_tree->n.common->binding_label,
8765                    comm_block_tree->n.common->name,
8766                    &(comm_block_tree->n.common->where),
8767                    comm_name_gsym->name, &(comm_name_gsym->where));
8768       else if (comm_name_gsym != NULL
8769                && strcmp (comm_name_gsym->name,
8770                           comm_block_tree->n.common->name) == 0)
8771         {
8772           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
8773              as expected.  */
8774           if (comm_name_gsym->binding_label == NULL)
8775             /* No binding label for common block stored yet; save this one.  */
8776             comm_name_gsym->binding_label =
8777               comm_block_tree->n.common->binding_label;
8778           else
8779             if (strcmp (comm_name_gsym->binding_label,
8780                         comm_block_tree->n.common->binding_label) != 0)
8781               {
8782                 /* Common block names match but binding labels do not.  */
8783                 gfc_error ("Binding label '%s' for common block '%s' at %L "
8784                            "does not match the binding label '%s' for common "
8785                            "block '%s' at %L",
8786                            comm_block_tree->n.common->binding_label,
8787                            comm_block_tree->n.common->name,
8788                            &(comm_block_tree->n.common->where),
8789                            comm_name_gsym->binding_label,
8790                            comm_name_gsym->name,
8791                            &(comm_name_gsym->where));
8792                 return;
8793               }
8794         }
8795
8796       /* There is no binding label (NAME="") so we have nothing further to
8797          check and nothing to add as a global symbol for the label.  */
8798       if (comm_block_tree->n.common->binding_label[0] == '\0' )
8799         return;
8800       
8801       binding_label_gsym =
8802         gfc_find_gsymbol (gfc_gsym_root,
8803                           comm_block_tree->n.common->binding_label);
8804       if (binding_label_gsym == NULL)
8805         {
8806           /* Need to make a global symbol for the binding label to prevent
8807              it from colliding with another.  */
8808           binding_label_gsym =
8809             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
8810           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
8811           binding_label_gsym->type = GSYM_COMMON;
8812         }
8813       else
8814         {
8815           /* If comm_name_gsym is NULL, the name common block is use
8816              associated and the name could be colliding.  */
8817           if (binding_label_gsym->type != GSYM_COMMON)
8818             gfc_error ("Binding label '%s' for common block '%s' at %L "
8819                        "collides with the global entity '%s' at %L",
8820                        comm_block_tree->n.common->binding_label,
8821                        comm_block_tree->n.common->name,
8822                        &(comm_block_tree->n.common->where),
8823                        binding_label_gsym->name,
8824                        &(binding_label_gsym->where));
8825           else if (comm_name_gsym != NULL
8826                    && (strcmp (binding_label_gsym->name,
8827                                comm_name_gsym->binding_label) != 0)
8828                    && (strcmp (binding_label_gsym->sym_name,
8829                                comm_name_gsym->name) != 0))
8830             gfc_error ("Binding label '%s' for common block '%s' at %L "
8831                        "collides with global entity '%s' at %L",
8832                        binding_label_gsym->name, binding_label_gsym->sym_name,
8833                        &(comm_block_tree->n.common->where),
8834                        comm_name_gsym->name, &(comm_name_gsym->where));
8835         }
8836     }
8837   
8838   return;
8839 }
8840
8841
8842 /* Verify any BIND(C) derived types in the namespace so we can report errors
8843    for them once, rather than for each variable declared of that type.  */
8844
8845 static void
8846 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
8847 {
8848   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
8849       && derived_sym->attr.is_bind_c == 1)
8850     verify_bind_c_derived_type (derived_sym);
8851   
8852   return;
8853 }
8854
8855
8856 /* Verify that any binding labels used in a given namespace do not collide 
8857    with the names or binding labels of any global symbols.  */
8858
8859 static void
8860 gfc_verify_binding_labels (gfc_symbol *sym)
8861 {
8862   int has_error = 0;
8863   
8864   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
8865       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
8866     {
8867       gfc_gsymbol *bind_c_sym;
8868
8869       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
8870       if (bind_c_sym != NULL 
8871           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
8872         {
8873           if (sym->attr.if_source == IFSRC_DECL 
8874               && (bind_c_sym->type != GSYM_SUBROUTINE 
8875                   && bind_c_sym->type != GSYM_FUNCTION) 
8876               && ((sym->attr.contained == 1 
8877                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
8878                   || (sym->attr.use_assoc == 1 
8879                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
8880             {
8881               /* Make sure global procedures don't collide with anything.  */
8882               gfc_error ("Binding label '%s' at %L collides with the global "
8883                          "entity '%s' at %L", sym->binding_label,
8884                          &(sym->declared_at), bind_c_sym->name,
8885                          &(bind_c_sym->where));
8886               has_error = 1;
8887             }
8888           else if (sym->attr.contained == 0 
8889                    && (sym->attr.if_source == IFSRC_IFBODY 
8890                        && sym->attr.flavor == FL_PROCEDURE) 
8891                    && (bind_c_sym->sym_name != NULL 
8892                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
8893             {
8894               /* Make sure procedures in interface bodies don't collide.  */
8895               gfc_error ("Binding label '%s' in interface body at %L collides "
8896                          "with the global entity '%s' at %L",
8897                          sym->binding_label,
8898                          &(sym->declared_at), bind_c_sym->name,
8899                          &(bind_c_sym->where));
8900               has_error = 1;
8901             }
8902           else if (sym->attr.contained == 0 
8903                    && sym->attr.if_source == IFSRC_UNKNOWN)
8904             if ((sym->attr.use_assoc && bind_c_sym->mod_name
8905                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
8906                 || sym->attr.use_assoc == 0)
8907               {
8908                 gfc_error ("Binding label '%s' at %L collides with global "
8909                            "entity '%s' at %L", sym->binding_label,
8910                            &(sym->declared_at), bind_c_sym->name,
8911                            &(bind_c_sym->where));
8912                 has_error = 1;
8913               }
8914
8915           if (has_error != 0)
8916             /* Clear the binding label to prevent checking multiple times.  */
8917             sym->binding_label[0] = '\0';
8918         }
8919       else if (bind_c_sym == NULL)
8920         {
8921           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
8922           bind_c_sym->where = sym->declared_at;
8923           bind_c_sym->sym_name = sym->name;
8924
8925           if (sym->attr.use_assoc == 1)
8926             bind_c_sym->mod_name = sym->module;
8927           else
8928             if (sym->ns->proc_name != NULL)
8929               bind_c_sym->mod_name = sym->ns->proc_name->name;
8930
8931           if (sym->attr.contained == 0)
8932             {
8933               if (sym->attr.subroutine)
8934                 bind_c_sym->type = GSYM_SUBROUTINE;
8935               else if (sym->attr.function)
8936                 bind_c_sym->type = GSYM_FUNCTION;
8937             }
8938         }
8939     }
8940   return;
8941 }
8942
8943
8944 /* Resolve an index expression.  */
8945
8946 static gfc_try
8947 resolve_index_expr (gfc_expr *e)
8948 {
8949   if (gfc_resolve_expr (e) == FAILURE)
8950     return FAILURE;
8951
8952   if (gfc_simplify_expr (e, 0) == FAILURE)
8953     return FAILURE;
8954
8955   if (gfc_specification_expr (e) == FAILURE)
8956     return FAILURE;
8957
8958   return SUCCESS;
8959 }
8960
8961 /* Resolve a charlen structure.  */
8962
8963 static gfc_try
8964 resolve_charlen (gfc_charlen *cl)
8965 {
8966   int i, k;
8967
8968   if (cl->resolved)
8969     return SUCCESS;
8970
8971   cl->resolved = 1;
8972
8973   specification_expr = 1;
8974
8975   if (resolve_index_expr (cl->length) == FAILURE)
8976     {
8977       specification_expr = 0;
8978       return FAILURE;
8979     }
8980
8981   /* "If the character length parameter value evaluates to a negative
8982      value, the length of character entities declared is zero."  */
8983   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
8984     {
8985       if (gfc_option.warn_surprising)
8986         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
8987                          " the length has been set to zero",
8988                          &cl->length->where, i);
8989       gfc_replace_expr (cl->length,
8990                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
8991     }
8992
8993   /* Check that the character length is not too large.  */
8994   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
8995   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
8996       && cl->length->ts.type == BT_INTEGER
8997       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
8998     {
8999       gfc_error ("String length at %L is too large", &cl->length->where);
9000       return FAILURE;
9001     }
9002
9003   return SUCCESS;
9004 }
9005
9006
9007 /* Test for non-constant shape arrays.  */
9008
9009 static bool
9010 is_non_constant_shape_array (gfc_symbol *sym)
9011 {
9012   gfc_expr *e;
9013   int i;
9014   bool not_constant;
9015
9016   not_constant = false;
9017   if (sym->as != NULL)
9018     {
9019       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
9020          has not been simplified; parameter array references.  Do the
9021          simplification now.  */
9022       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
9023         {
9024           e = sym->as->lower[i];
9025           if (e && (resolve_index_expr (e) == FAILURE
9026                     || !gfc_is_constant_expr (e)))
9027             not_constant = true;
9028           e = sym->as->upper[i];
9029           if (e && (resolve_index_expr (e) == FAILURE
9030                     || !gfc_is_constant_expr (e)))
9031             not_constant = true;
9032         }
9033     }
9034   return not_constant;
9035 }
9036
9037 /* Given a symbol and an initialization expression, add code to initialize
9038    the symbol to the function entry.  */
9039 static void
9040 build_init_assign (gfc_symbol *sym, gfc_expr *init)
9041 {
9042   gfc_expr *lval;
9043   gfc_code *init_st;
9044   gfc_namespace *ns = sym->ns;
9045
9046   /* Search for the function namespace if this is a contained
9047      function without an explicit result.  */
9048   if (sym->attr.function && sym == sym->result
9049       && sym->name != sym->ns->proc_name->name)
9050     {
9051       ns = ns->contained;
9052       for (;ns; ns = ns->sibling)
9053         if (strcmp (ns->proc_name->name, sym->name) == 0)
9054           break;
9055     }
9056
9057   if (ns == NULL)
9058     {
9059       gfc_free_expr (init);
9060       return;
9061     }
9062
9063   /* Build an l-value expression for the result.  */
9064   lval = gfc_lval_expr_from_sym (sym);
9065
9066   /* Add the code at scope entry.  */
9067   init_st = gfc_get_code ();
9068   init_st->next = ns->code;
9069   ns->code = init_st;
9070
9071   /* Assign the default initializer to the l-value.  */
9072   init_st->loc = sym->declared_at;
9073   init_st->op = EXEC_INIT_ASSIGN;
9074   init_st->expr1 = lval;
9075   init_st->expr2 = init;
9076 }
9077
9078 /* Assign the default initializer to a derived type variable or result.  */
9079
9080 static void
9081 apply_default_init (gfc_symbol *sym)
9082 {
9083   gfc_expr *init = NULL;
9084
9085   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9086     return;
9087
9088   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
9089     init = gfc_default_initializer (&sym->ts);
9090
9091   if (init == NULL)
9092     return;
9093
9094   build_init_assign (sym, init);
9095 }
9096
9097 /* Build an initializer for a local integer, real, complex, logical, or
9098    character variable, based on the command line flags finit-local-zero,
9099    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
9100    null if the symbol should not have a default initialization.  */
9101 static gfc_expr *
9102 build_default_init_expr (gfc_symbol *sym)
9103 {
9104   int char_len;
9105   gfc_expr *init_expr;
9106   int i;
9107
9108   /* These symbols should never have a default initialization.  */
9109   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
9110       || sym->attr.external
9111       || sym->attr.dummy
9112       || sym->attr.pointer
9113       || sym->attr.in_equivalence
9114       || sym->attr.in_common
9115       || sym->attr.data
9116       || sym->module
9117       || sym->attr.cray_pointee
9118       || sym->attr.cray_pointer)
9119     return NULL;
9120
9121   /* Now we'll try to build an initializer expression.  */
9122   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
9123                                      &sym->declared_at);
9124
9125   /* We will only initialize integers, reals, complex, logicals, and
9126      characters, and only if the corresponding command-line flags
9127      were set.  Otherwise, we free init_expr and return null.  */
9128   switch (sym->ts.type)
9129     {    
9130     case BT_INTEGER:
9131       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
9132         mpz_init_set_si (init_expr->value.integer, 
9133                          gfc_option.flag_init_integer_value);
9134       else
9135         {
9136           gfc_free_expr (init_expr);
9137           init_expr = NULL;
9138         }
9139       break;
9140
9141     case BT_REAL:
9142       mpfr_init (init_expr->value.real);
9143       switch (gfc_option.flag_init_real)
9144         {
9145         case GFC_INIT_REAL_SNAN:
9146           init_expr->is_snan = 1;
9147           /* Fall through.  */
9148         case GFC_INIT_REAL_NAN:
9149           mpfr_set_nan (init_expr->value.real);
9150           break;
9151
9152         case GFC_INIT_REAL_INF:
9153           mpfr_set_inf (init_expr->value.real, 1);
9154           break;
9155
9156         case GFC_INIT_REAL_NEG_INF:
9157           mpfr_set_inf (init_expr->value.real, -1);
9158           break;
9159
9160         case GFC_INIT_REAL_ZERO:
9161           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
9162           break;
9163
9164         default:
9165           gfc_free_expr (init_expr);
9166           init_expr = NULL;
9167           break;
9168         }
9169       break;
9170           
9171     case BT_COMPLEX:
9172       mpc_init2 (init_expr->value.complex, mpfr_get_default_prec());
9173       switch (gfc_option.flag_init_real)
9174         {
9175         case GFC_INIT_REAL_SNAN:
9176           init_expr->is_snan = 1;
9177           /* Fall through.  */
9178         case GFC_INIT_REAL_NAN:
9179           mpfr_set_nan (mpc_realref (init_expr->value.complex));
9180           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
9181           break;
9182
9183         case GFC_INIT_REAL_INF:
9184           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
9185           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
9186           break;
9187
9188         case GFC_INIT_REAL_NEG_INF:
9189           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
9190           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
9191           break;
9192
9193         case GFC_INIT_REAL_ZERO:
9194           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
9195           break;
9196
9197         default:
9198           gfc_free_expr (init_expr);
9199           init_expr = NULL;
9200           break;
9201         }
9202       break;
9203           
9204     case BT_LOGICAL:
9205       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
9206         init_expr->value.logical = 0;
9207       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
9208         init_expr->value.logical = 1;
9209       else
9210         {
9211           gfc_free_expr (init_expr);
9212           init_expr = NULL;
9213         }
9214       break;
9215           
9216     case BT_CHARACTER:
9217       /* For characters, the length must be constant in order to 
9218          create a default initializer.  */
9219       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
9220           && sym->ts.u.cl->length
9221           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9222         {
9223           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
9224           init_expr->value.character.length = char_len;
9225           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
9226           for (i = 0; i < char_len; i++)
9227             init_expr->value.character.string[i]
9228               = (unsigned char) gfc_option.flag_init_character_value;
9229         }
9230       else
9231         {
9232           gfc_free_expr (init_expr);
9233           init_expr = NULL;
9234         }
9235       break;
9236           
9237     default:
9238      gfc_free_expr (init_expr);
9239      init_expr = NULL;
9240     }
9241   return init_expr;
9242 }
9243
9244 /* Add an initialization expression to a local variable.  */
9245 static void
9246 apply_default_init_local (gfc_symbol *sym)
9247 {
9248   gfc_expr *init = NULL;
9249
9250   /* The symbol should be a variable or a function return value.  */
9251   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9252       || (sym->attr.function && sym->result != sym))
9253     return;
9254
9255   /* Try to build the initializer expression.  If we can't initialize
9256      this symbol, then init will be NULL.  */
9257   init = build_default_init_expr (sym);
9258   if (init == NULL)
9259     return;
9260
9261   /* For saved variables, we don't want to add an initializer at 
9262      function entry, so we just add a static initializer.  */
9263   if (sym->attr.save || sym->ns->save_all 
9264       || gfc_option.flag_max_stack_var_size == 0)
9265     {
9266       /* Don't clobber an existing initializer!  */
9267       gcc_assert (sym->value == NULL);
9268       sym->value = init;
9269       return;
9270     }
9271
9272   build_init_assign (sym, init);
9273 }
9274
9275 /* Resolution of common features of flavors variable and procedure.  */
9276
9277 static gfc_try
9278 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
9279 {
9280   /* Constraints on deferred shape variable.  */
9281   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
9282     {
9283       if (sym->attr.allocatable)
9284         {
9285           if (sym->attr.dimension)
9286             {
9287               gfc_error ("Allocatable array '%s' at %L must have "
9288                          "a deferred shape", sym->name, &sym->declared_at);
9289               return FAILURE;
9290             }
9291           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
9292                                    "may not be ALLOCATABLE", sym->name,
9293                                    &sym->declared_at) == FAILURE)
9294             return FAILURE;
9295         }
9296
9297       if (sym->attr.pointer && sym->attr.dimension)
9298         {
9299           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
9300                      sym->name, &sym->declared_at);
9301           return FAILURE;
9302         }
9303
9304     }
9305   else
9306     {
9307       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
9308           && !sym->attr.dummy && sym->ts.type != BT_CLASS)
9309         {
9310           gfc_error ("Array '%s' at %L cannot have a deferred shape",
9311                      sym->name, &sym->declared_at);
9312           return FAILURE;
9313          }
9314     }
9315
9316   /* Constraints on polymorphic variables.  */
9317   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
9318     {
9319       /* F03:C502.  */
9320       if (!gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
9321         {
9322           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
9323                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
9324                      &sym->declared_at);
9325           return FAILURE;
9326         }
9327
9328       /* F03:C509.  */
9329       /* Assume that use associated symbols were checked in the module ns.  */ 
9330       if (!sym->attr.class_ok && !sym->attr.use_assoc)
9331         {
9332           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
9333                      "or pointer", sym->name, &sym->declared_at);
9334           return FAILURE;
9335         }
9336     }
9337     
9338   return SUCCESS;
9339 }
9340
9341
9342 /* Additional checks for symbols with flavor variable and derived
9343    type.  To be called from resolve_fl_variable.  */
9344
9345 static gfc_try
9346 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
9347 {
9348   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
9349
9350   /* Check to see if a derived type is blocked from being host
9351      associated by the presence of another class I symbol in the same
9352      namespace.  14.6.1.3 of the standard and the discussion on
9353      comp.lang.fortran.  */
9354   if (sym->ns != sym->ts.u.derived->ns
9355       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
9356     {
9357       gfc_symbol *s;
9358       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
9359       if (s && s->attr.flavor != FL_DERIVED)
9360         {
9361           gfc_error ("The type '%s' cannot be host associated at %L "
9362                      "because it is blocked by an incompatible object "
9363                      "of the same name declared at %L",
9364                      sym->ts.u.derived->name, &sym->declared_at,
9365                      &s->declared_at);
9366           return FAILURE;
9367         }
9368     }
9369
9370   /* 4th constraint in section 11.3: "If an object of a type for which
9371      component-initialization is specified (R429) appears in the
9372      specification-part of a module and does not have the ALLOCATABLE
9373      or POINTER attribute, the object shall have the SAVE attribute."
9374
9375      The check for initializers is performed with
9376      gfc_has_default_initializer because gfc_default_initializer generates
9377      a hidden default for allocatable components.  */
9378   if (!(sym->value || no_init_flag) && sym->ns->proc_name
9379       && sym->ns->proc_name->attr.flavor == FL_MODULE
9380       && !sym->ns->save_all && !sym->attr.save
9381       && !sym->attr.pointer && !sym->attr.allocatable
9382       && gfc_has_default_initializer (sym->ts.u.derived)
9383       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
9384                          "module variable '%s' at %L, needed due to "
9385                          "the default initialization", sym->name,
9386                          &sym->declared_at) == FAILURE)
9387     return FAILURE;
9388
9389   /* Assign default initializer.  */
9390   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
9391       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
9392     {
9393       sym->value = gfc_default_initializer (&sym->ts);
9394     }
9395
9396   return SUCCESS;
9397 }
9398
9399
9400 /* Resolve symbols with flavor variable.  */
9401
9402 static gfc_try
9403 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
9404 {
9405   int no_init_flag, automatic_flag;
9406   gfc_expr *e;
9407   const char *auto_save_msg;
9408
9409   auto_save_msg = "Automatic object '%s' at %L cannot have the "
9410                   "SAVE attribute";
9411
9412   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9413     return FAILURE;
9414
9415   /* Set this flag to check that variables are parameters of all entries.
9416      This check is effected by the call to gfc_resolve_expr through
9417      is_non_constant_shape_array.  */
9418   specification_expr = 1;
9419
9420   if (sym->ns->proc_name
9421       && (sym->ns->proc_name->attr.flavor == FL_MODULE
9422           || sym->ns->proc_name->attr.is_main_program)
9423       && !sym->attr.use_assoc
9424       && !sym->attr.allocatable
9425       && !sym->attr.pointer
9426       && is_non_constant_shape_array (sym))
9427     {
9428       /* The shape of a main program or module array needs to be
9429          constant.  */
9430       gfc_error ("The module or main program array '%s' at %L must "
9431                  "have constant shape", sym->name, &sym->declared_at);
9432       specification_expr = 0;
9433       return FAILURE;
9434     }
9435
9436   if (sym->ts.type == BT_CHARACTER)
9437     {
9438       /* Make sure that character string variables with assumed length are
9439          dummy arguments.  */
9440       e = sym->ts.u.cl->length;
9441       if (e == NULL && !sym->attr.dummy && !sym->attr.result)
9442         {
9443           gfc_error ("Entity with assumed character length at %L must be a "
9444                      "dummy argument or a PARAMETER", &sym->declared_at);
9445           return FAILURE;
9446         }
9447
9448       if (e && sym->attr.save && !gfc_is_constant_expr (e))
9449         {
9450           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9451           return FAILURE;
9452         }
9453
9454       if (!gfc_is_constant_expr (e)
9455           && !(e->expr_type == EXPR_VARIABLE
9456                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
9457           && sym->ns->proc_name
9458           && (sym->ns->proc_name->attr.flavor == FL_MODULE
9459               || sym->ns->proc_name->attr.is_main_program)
9460           && !sym->attr.use_assoc)
9461         {
9462           gfc_error ("'%s' at %L must have constant character length "
9463                      "in this context", sym->name, &sym->declared_at);
9464           return FAILURE;
9465         }
9466     }
9467
9468   if (sym->value == NULL && sym->attr.referenced)
9469     apply_default_init_local (sym); /* Try to apply a default initialization.  */
9470
9471   /* Determine if the symbol may not have an initializer.  */
9472   no_init_flag = automatic_flag = 0;
9473   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
9474       || sym->attr.intrinsic || sym->attr.result)
9475     no_init_flag = 1;
9476   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
9477            && is_non_constant_shape_array (sym))
9478     {
9479       no_init_flag = automatic_flag = 1;
9480
9481       /* Also, they must not have the SAVE attribute.
9482          SAVE_IMPLICIT is checked below.  */
9483       if (sym->attr.save == SAVE_EXPLICIT)
9484         {
9485           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9486           return FAILURE;
9487         }
9488     }
9489
9490   /* Ensure that any initializer is simplified.  */
9491   if (sym->value)
9492     gfc_simplify_expr (sym->value, 1);
9493
9494   /* Reject illegal initializers.  */
9495   if (!sym->mark && sym->value)
9496     {
9497       if (sym->attr.allocatable)
9498         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
9499                    sym->name, &sym->declared_at);
9500       else if (sym->attr.external)
9501         gfc_error ("External '%s' at %L cannot have an initializer",
9502                    sym->name, &sym->declared_at);
9503       else if (sym->attr.dummy
9504         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
9505         gfc_error ("Dummy '%s' at %L cannot have an initializer",
9506                    sym->name, &sym->declared_at);
9507       else if (sym->attr.intrinsic)
9508         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
9509                    sym->name, &sym->declared_at);
9510       else if (sym->attr.result)
9511         gfc_error ("Function result '%s' at %L cannot have an initializer",
9512                    sym->name, &sym->declared_at);
9513       else if (automatic_flag)
9514         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
9515                    sym->name, &sym->declared_at);
9516       else
9517         goto no_init_error;
9518       return FAILURE;
9519     }
9520
9521 no_init_error:
9522   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
9523     return resolve_fl_variable_derived (sym, no_init_flag);
9524
9525   return SUCCESS;
9526 }
9527
9528
9529 /* Resolve a procedure.  */
9530
9531 static gfc_try
9532 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
9533 {
9534   gfc_formal_arglist *arg;
9535
9536   if (sym->attr.function
9537       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9538     return FAILURE;
9539
9540   if (sym->ts.type == BT_CHARACTER)
9541     {
9542       gfc_charlen *cl = sym->ts.u.cl;
9543
9544       if (cl && cl->length && gfc_is_constant_expr (cl->length)
9545              && resolve_charlen (cl) == FAILURE)
9546         return FAILURE;
9547
9548       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
9549           && sym->attr.proc == PROC_ST_FUNCTION)
9550         {
9551           gfc_error ("Character-valued statement function '%s' at %L must "
9552                      "have constant length", sym->name, &sym->declared_at);
9553           return FAILURE;
9554         }
9555     }
9556
9557   /* Ensure that derived type for are not of a private type.  Internal
9558      module procedures are excluded by 2.2.3.3 - i.e., they are not
9559      externally accessible and can access all the objects accessible in
9560      the host.  */
9561   if (!(sym->ns->parent
9562         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
9563       && gfc_check_access(sym->attr.access, sym->ns->default_access))
9564     {
9565       gfc_interface *iface;
9566
9567       for (arg = sym->formal; arg; arg = arg->next)
9568         {
9569           if (arg->sym
9570               && arg->sym->ts.type == BT_DERIVED
9571               && !arg->sym->ts.u.derived->attr.use_assoc
9572               && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9573                                     arg->sym->ts.u.derived->ns->default_access)
9574               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
9575                                  "PRIVATE type and cannot be a dummy argument"
9576                                  " of '%s', which is PUBLIC at %L",
9577                                  arg->sym->name, sym->name, &sym->declared_at)
9578                  == FAILURE)
9579             {
9580               /* Stop this message from recurring.  */
9581               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9582               return FAILURE;
9583             }
9584         }
9585
9586       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9587          PRIVATE to the containing module.  */
9588       for (iface = sym->generic; iface; iface = iface->next)
9589         {
9590           for (arg = iface->sym->formal; arg; arg = arg->next)
9591             {
9592               if (arg->sym
9593                   && arg->sym->ts.type == BT_DERIVED
9594                   && !arg->sym->ts.u.derived->attr.use_assoc
9595                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9596                                         arg->sym->ts.u.derived->ns->default_access)
9597                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9598                                      "'%s' in PUBLIC interface '%s' at %L "
9599                                      "takes dummy arguments of '%s' which is "
9600                                      "PRIVATE", iface->sym->name, sym->name,
9601                                      &iface->sym->declared_at,
9602                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9603                 {
9604                   /* Stop this message from recurring.  */
9605                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9606                   return FAILURE;
9607                 }
9608              }
9609         }
9610
9611       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9612          PRIVATE to the containing module.  */
9613       for (iface = sym->generic; iface; iface = iface->next)
9614         {
9615           for (arg = iface->sym->formal; arg; arg = arg->next)
9616             {
9617               if (arg->sym
9618                   && arg->sym->ts.type == BT_DERIVED
9619                   && !arg->sym->ts.u.derived->attr.use_assoc
9620                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9621                                         arg->sym->ts.u.derived->ns->default_access)
9622                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9623                                      "'%s' in PUBLIC interface '%s' at %L "
9624                                      "takes dummy arguments of '%s' which is "
9625                                      "PRIVATE", iface->sym->name, sym->name,
9626                                      &iface->sym->declared_at,
9627                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9628                 {
9629                   /* Stop this message from recurring.  */
9630                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9631                   return FAILURE;
9632                 }
9633              }
9634         }
9635     }
9636
9637   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
9638       && !sym->attr.proc_pointer)
9639     {
9640       gfc_error ("Function '%s' at %L cannot have an initializer",
9641                  sym->name, &sym->declared_at);
9642       return FAILURE;
9643     }
9644
9645   /* An external symbol may not have an initializer because it is taken to be
9646      a procedure. Exception: Procedure Pointers.  */
9647   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
9648     {
9649       gfc_error ("External object '%s' at %L may not have an initializer",
9650                  sym->name, &sym->declared_at);
9651       return FAILURE;
9652     }
9653
9654   /* An elemental function is required to return a scalar 12.7.1  */
9655   if (sym->attr.elemental && sym->attr.function && sym->as)
9656     {
9657       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
9658                  "result", sym->name, &sym->declared_at);
9659       /* Reset so that the error only occurs once.  */
9660       sym->attr.elemental = 0;
9661       return FAILURE;
9662     }
9663
9664   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
9665      char-len-param shall not be array-valued, pointer-valued, recursive
9666      or pure.  ....snip... A character value of * may only be used in the
9667      following ways: (i) Dummy arg of procedure - dummy associates with
9668      actual length; (ii) To declare a named constant; or (iii) External
9669      function - but length must be declared in calling scoping unit.  */
9670   if (sym->attr.function
9671       && sym->ts.type == BT_CHARACTER
9672       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
9673     {
9674       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
9675           || (sym->attr.recursive) || (sym->attr.pure))
9676         {
9677           if (sym->as && sym->as->rank)
9678             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9679                        "array-valued", sym->name, &sym->declared_at);
9680
9681           if (sym->attr.pointer)
9682             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9683                        "pointer-valued", sym->name, &sym->declared_at);
9684
9685           if (sym->attr.pure)
9686             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9687                        "pure", sym->name, &sym->declared_at);
9688
9689           if (sym->attr.recursive)
9690             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9691                        "recursive", sym->name, &sym->declared_at);
9692
9693           return FAILURE;
9694         }
9695
9696       /* Appendix B.2 of the standard.  Contained functions give an
9697          error anyway.  Fixed-form is likely to be F77/legacy.  */
9698       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
9699         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
9700                         "CHARACTER(*) function '%s' at %L",
9701                         sym->name, &sym->declared_at);
9702     }
9703
9704   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
9705     {
9706       gfc_formal_arglist *curr_arg;
9707       int has_non_interop_arg = 0;
9708
9709       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
9710                              sym->common_block) == FAILURE)
9711         {
9712           /* Clear these to prevent looking at them again if there was an
9713              error.  */
9714           sym->attr.is_bind_c = 0;
9715           sym->attr.is_c_interop = 0;
9716           sym->ts.is_c_interop = 0;
9717         }
9718       else
9719         {
9720           /* So far, no errors have been found.  */
9721           sym->attr.is_c_interop = 1;
9722           sym->ts.is_c_interop = 1;
9723         }
9724       
9725       curr_arg = sym->formal;
9726       while (curr_arg != NULL)
9727         {
9728           /* Skip implicitly typed dummy args here.  */
9729           if (curr_arg->sym->attr.implicit_type == 0)
9730             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
9731               /* If something is found to fail, record the fact so we
9732                  can mark the symbol for the procedure as not being
9733                  BIND(C) to try and prevent multiple errors being
9734                  reported.  */
9735               has_non_interop_arg = 1;
9736           
9737           curr_arg = curr_arg->next;
9738         }
9739
9740       /* See if any of the arguments were not interoperable and if so, clear
9741          the procedure symbol to prevent duplicate error messages.  */
9742       if (has_non_interop_arg != 0)
9743         {
9744           sym->attr.is_c_interop = 0;
9745           sym->ts.is_c_interop = 0;
9746           sym->attr.is_bind_c = 0;
9747         }
9748     }
9749   
9750   if (!sym->attr.proc_pointer)
9751     {
9752       if (sym->attr.save == SAVE_EXPLICIT)
9753         {
9754           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
9755                      "in '%s' at %L", sym->name, &sym->declared_at);
9756           return FAILURE;
9757         }
9758       if (sym->attr.intent)
9759         {
9760           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
9761                      "in '%s' at %L", sym->name, &sym->declared_at);
9762           return FAILURE;
9763         }
9764       if (sym->attr.subroutine && sym->attr.result)
9765         {
9766           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
9767                      "in '%s' at %L", sym->name, &sym->declared_at);
9768           return FAILURE;
9769         }
9770       if (sym->attr.external && sym->attr.function
9771           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
9772               || sym->attr.contained))
9773         {
9774           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
9775                      "in '%s' at %L", sym->name, &sym->declared_at);
9776           return FAILURE;
9777         }
9778       if (strcmp ("ppr@", sym->name) == 0)
9779         {
9780           gfc_error ("Procedure pointer result '%s' at %L "
9781                      "is missing the pointer attribute",
9782                      sym->ns->proc_name->name, &sym->declared_at);
9783           return FAILURE;
9784         }
9785     }
9786
9787   return SUCCESS;
9788 }
9789
9790
9791 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
9792    been defined and we now know their defined arguments, check that they fulfill
9793    the requirements of the standard for procedures used as finalizers.  */
9794
9795 static gfc_try
9796 gfc_resolve_finalizers (gfc_symbol* derived)
9797 {
9798   gfc_finalizer* list;
9799   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
9800   gfc_try result = SUCCESS;
9801   bool seen_scalar = false;
9802
9803   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
9804     return SUCCESS;
9805
9806   /* Walk over the list of finalizer-procedures, check them, and if any one
9807      does not fit in with the standard's definition, print an error and remove
9808      it from the list.  */
9809   prev_link = &derived->f2k_derived->finalizers;
9810   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
9811     {
9812       gfc_symbol* arg;
9813       gfc_finalizer* i;
9814       int my_rank;
9815
9816       /* Skip this finalizer if we already resolved it.  */
9817       if (list->proc_tree)
9818         {
9819           prev_link = &(list->next);
9820           continue;
9821         }
9822
9823       /* Check this exists and is a SUBROUTINE.  */
9824       if (!list->proc_sym->attr.subroutine)
9825         {
9826           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
9827                      list->proc_sym->name, &list->where);
9828           goto error;
9829         }
9830
9831       /* We should have exactly one argument.  */
9832       if (!list->proc_sym->formal || list->proc_sym->formal->next)
9833         {
9834           gfc_error ("FINAL procedure at %L must have exactly one argument",
9835                      &list->where);
9836           goto error;
9837         }
9838       arg = list->proc_sym->formal->sym;
9839
9840       /* This argument must be of our type.  */
9841       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
9842         {
9843           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
9844                      &arg->declared_at, derived->name);
9845           goto error;
9846         }
9847
9848       /* It must neither be a pointer nor allocatable nor optional.  */
9849       if (arg->attr.pointer)
9850         {
9851           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
9852                      &arg->declared_at);
9853           goto error;
9854         }
9855       if (arg->attr.allocatable)
9856         {
9857           gfc_error ("Argument of FINAL procedure at %L must not be"
9858                      " ALLOCATABLE", &arg->declared_at);
9859           goto error;
9860         }
9861       if (arg->attr.optional)
9862         {
9863           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
9864                      &arg->declared_at);
9865           goto error;
9866         }
9867
9868       /* It must not be INTENT(OUT).  */
9869       if (arg->attr.intent == INTENT_OUT)
9870         {
9871           gfc_error ("Argument of FINAL procedure at %L must not be"
9872                      " INTENT(OUT)", &arg->declared_at);
9873           goto error;
9874         }
9875
9876       /* Warn if the procedure is non-scalar and not assumed shape.  */
9877       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
9878           && arg->as->type != AS_ASSUMED_SHAPE)
9879         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
9880                      " shape argument", &arg->declared_at);
9881
9882       /* Check that it does not match in kind and rank with a FINAL procedure
9883          defined earlier.  To really loop over the *earlier* declarations,
9884          we need to walk the tail of the list as new ones were pushed at the
9885          front.  */
9886       /* TODO: Handle kind parameters once they are implemented.  */
9887       my_rank = (arg->as ? arg->as->rank : 0);
9888       for (i = list->next; i; i = i->next)
9889         {
9890           /* Argument list might be empty; that is an error signalled earlier,
9891              but we nevertheless continued resolving.  */
9892           if (i->proc_sym->formal)
9893             {
9894               gfc_symbol* i_arg = i->proc_sym->formal->sym;
9895               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
9896               if (i_rank == my_rank)
9897                 {
9898                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
9899                              " rank (%d) as '%s'",
9900                              list->proc_sym->name, &list->where, my_rank, 
9901                              i->proc_sym->name);
9902                   goto error;
9903                 }
9904             }
9905         }
9906
9907         /* Is this the/a scalar finalizer procedure?  */
9908         if (!arg->as || arg->as->rank == 0)
9909           seen_scalar = true;
9910
9911         /* Find the symtree for this procedure.  */
9912         gcc_assert (!list->proc_tree);
9913         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
9914
9915         prev_link = &list->next;
9916         continue;
9917
9918         /* Remove wrong nodes immediately from the list so we don't risk any
9919            troubles in the future when they might fail later expectations.  */
9920 error:
9921         result = FAILURE;
9922         i = list;
9923         *prev_link = list->next;
9924         gfc_free_finalizer (i);
9925     }
9926
9927   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
9928      were nodes in the list, must have been for arrays.  It is surely a good
9929      idea to have a scalar version there if there's something to finalize.  */
9930   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
9931     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
9932                  " defined at %L, suggest also scalar one",
9933                  derived->name, &derived->declared_at);
9934
9935   /* TODO:  Remove this error when finalization is finished.  */
9936   gfc_error ("Finalization at %L is not yet implemented",
9937              &derived->declared_at);
9938
9939   return result;
9940 }
9941
9942
9943 /* Check that it is ok for the typebound procedure proc to override the
9944    procedure old.  */
9945
9946 static gfc_try
9947 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
9948 {
9949   locus where;
9950   const gfc_symbol* proc_target;
9951   const gfc_symbol* old_target;
9952   unsigned proc_pass_arg, old_pass_arg, argpos;
9953   gfc_formal_arglist* proc_formal;
9954   gfc_formal_arglist* old_formal;
9955
9956   /* This procedure should only be called for non-GENERIC proc.  */
9957   gcc_assert (!proc->n.tb->is_generic);
9958
9959   /* If the overwritten procedure is GENERIC, this is an error.  */
9960   if (old->n.tb->is_generic)
9961     {
9962       gfc_error ("Can't overwrite GENERIC '%s' at %L",
9963                  old->name, &proc->n.tb->where);
9964       return FAILURE;
9965     }
9966
9967   where = proc->n.tb->where;
9968   proc_target = proc->n.tb->u.specific->n.sym;
9969   old_target = old->n.tb->u.specific->n.sym;
9970
9971   /* Check that overridden binding is not NON_OVERRIDABLE.  */
9972   if (old->n.tb->non_overridable)
9973     {
9974       gfc_error ("'%s' at %L overrides a procedure binding declared"
9975                  " NON_OVERRIDABLE", proc->name, &where);
9976       return FAILURE;
9977     }
9978
9979   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
9980   if (!old->n.tb->deferred && proc->n.tb->deferred)
9981     {
9982       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
9983                  " non-DEFERRED binding", proc->name, &where);
9984       return FAILURE;
9985     }
9986
9987   /* If the overridden binding is PURE, the overriding must be, too.  */
9988   if (old_target->attr.pure && !proc_target->attr.pure)
9989     {
9990       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
9991                  proc->name, &where);
9992       return FAILURE;
9993     }
9994
9995   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
9996      is not, the overriding must not be either.  */
9997   if (old_target->attr.elemental && !proc_target->attr.elemental)
9998     {
9999       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
10000                  " ELEMENTAL", proc->name, &where);
10001       return FAILURE;
10002     }
10003   if (!old_target->attr.elemental && proc_target->attr.elemental)
10004     {
10005       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
10006                  " be ELEMENTAL, either", proc->name, &where);
10007       return FAILURE;
10008     }
10009
10010   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
10011      SUBROUTINE.  */
10012   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
10013     {
10014       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
10015                  " SUBROUTINE", proc->name, &where);
10016       return FAILURE;
10017     }
10018
10019   /* If the overridden binding is a FUNCTION, the overriding must also be a
10020      FUNCTION and have the same characteristics.  */
10021   if (old_target->attr.function)
10022     {
10023       if (!proc_target->attr.function)
10024         {
10025           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
10026                      " FUNCTION", proc->name, &where);
10027           return FAILURE;
10028         }
10029
10030       /* FIXME:  Do more comprehensive checking (including, for instance, the
10031          rank and array-shape).  */
10032       gcc_assert (proc_target->result && old_target->result);
10033       if (!gfc_compare_types (&proc_target->result->ts,
10034                               &old_target->result->ts))
10035         {
10036           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
10037                      " matching result types", proc->name, &where);
10038           return FAILURE;
10039         }
10040     }
10041
10042   /* If the overridden binding is PUBLIC, the overriding one must not be
10043      PRIVATE.  */
10044   if (old->n.tb->access == ACCESS_PUBLIC
10045       && proc->n.tb->access == ACCESS_PRIVATE)
10046     {
10047       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
10048                  " PRIVATE", proc->name, &where);
10049       return FAILURE;
10050     }
10051
10052   /* Compare the formal argument lists of both procedures.  This is also abused
10053      to find the position of the passed-object dummy arguments of both
10054      bindings as at least the overridden one might not yet be resolved and we
10055      need those positions in the check below.  */
10056   proc_pass_arg = old_pass_arg = 0;
10057   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
10058     proc_pass_arg = 1;
10059   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
10060     old_pass_arg = 1;
10061   argpos = 1;
10062   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
10063        proc_formal && old_formal;
10064        proc_formal = proc_formal->next, old_formal = old_formal->next)
10065     {
10066       if (proc->n.tb->pass_arg
10067           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
10068         proc_pass_arg = argpos;
10069       if (old->n.tb->pass_arg
10070           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
10071         old_pass_arg = argpos;
10072
10073       /* Check that the names correspond.  */
10074       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
10075         {
10076           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
10077                      " to match the corresponding argument of the overridden"
10078                      " procedure", proc_formal->sym->name, proc->name, &where,
10079                      old_formal->sym->name);
10080           return FAILURE;
10081         }
10082
10083       /* Check that the types correspond if neither is the passed-object
10084          argument.  */
10085       /* FIXME:  Do more comprehensive testing here.  */
10086       if (proc_pass_arg != argpos && old_pass_arg != argpos
10087           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
10088         {
10089           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L "
10090                      "in respect to the overridden procedure",
10091                      proc_formal->sym->name, proc->name, &where);
10092           return FAILURE;
10093         }
10094
10095       ++argpos;
10096     }
10097   if (proc_formal || old_formal)
10098     {
10099       gfc_error ("'%s' at %L must have the same number of formal arguments as"
10100                  " the overridden procedure", proc->name, &where);
10101       return FAILURE;
10102     }
10103
10104   /* If the overridden binding is NOPASS, the overriding one must also be
10105      NOPASS.  */
10106   if (old->n.tb->nopass && !proc->n.tb->nopass)
10107     {
10108       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
10109                  " NOPASS", proc->name, &where);
10110       return FAILURE;
10111     }
10112
10113   /* If the overridden binding is PASS(x), the overriding one must also be
10114      PASS and the passed-object dummy arguments must correspond.  */
10115   if (!old->n.tb->nopass)
10116     {
10117       if (proc->n.tb->nopass)
10118         {
10119           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
10120                      " PASS", proc->name, &where);
10121           return FAILURE;
10122         }
10123
10124       if (proc_pass_arg != old_pass_arg)
10125         {
10126           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
10127                      " the same position as the passed-object dummy argument of"
10128                      " the overridden procedure", proc->name, &where);
10129           return FAILURE;
10130         }
10131     }
10132
10133   return SUCCESS;
10134 }
10135
10136
10137 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10138
10139 static gfc_try
10140 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10141                              const char* generic_name, locus where)
10142 {
10143   gfc_symbol* sym1;
10144   gfc_symbol* sym2;
10145
10146   gcc_assert (t1->specific && t2->specific);
10147   gcc_assert (!t1->specific->is_generic);
10148   gcc_assert (!t2->specific->is_generic);
10149
10150   sym1 = t1->specific->u.specific->n.sym;
10151   sym2 = t2->specific->u.specific->n.sym;
10152
10153   if (sym1 == sym2)
10154     return SUCCESS;
10155
10156   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10157   if (sym1->attr.subroutine != sym2->attr.subroutine
10158       || sym1->attr.function != sym2->attr.function)
10159     {
10160       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10161                  " GENERIC '%s' at %L",
10162                  sym1->name, sym2->name, generic_name, &where);
10163       return FAILURE;
10164     }
10165
10166   /* Compare the interfaces.  */
10167   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10168     {
10169       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10170                  sym1->name, sym2->name, generic_name, &where);
10171       return FAILURE;
10172     }
10173
10174   return SUCCESS;
10175 }
10176
10177
10178 /* Worker function for resolving a generic procedure binding; this is used to
10179    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10180
10181    The difference between those cases is finding possible inherited bindings
10182    that are overridden, as one has to look for them in tb_sym_root,
10183    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10184    the super-type and set p->overridden correctly.  */
10185
10186 static gfc_try
10187 resolve_tb_generic_targets (gfc_symbol* super_type,
10188                             gfc_typebound_proc* p, const char* name)
10189 {
10190   gfc_tbp_generic* target;
10191   gfc_symtree* first_target;
10192   gfc_symtree* inherited;
10193
10194   gcc_assert (p && p->is_generic);
10195
10196   /* Try to find the specific bindings for the symtrees in our target-list.  */
10197   gcc_assert (p->u.generic);
10198   for (target = p->u.generic; target; target = target->next)
10199     if (!target->specific)
10200       {
10201         gfc_typebound_proc* overridden_tbp;
10202         gfc_tbp_generic* g;
10203         const char* target_name;
10204
10205         target_name = target->specific_st->name;
10206
10207         /* Defined for this type directly.  */
10208         if (target->specific_st->n.tb)
10209           {
10210             target->specific = target->specific_st->n.tb;
10211             goto specific_found;
10212           }
10213
10214         /* Look for an inherited specific binding.  */
10215         if (super_type)
10216           {
10217             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10218                                                  true, NULL);
10219
10220             if (inherited)
10221               {
10222                 gcc_assert (inherited->n.tb);
10223                 target->specific = inherited->n.tb;
10224                 goto specific_found;
10225               }
10226           }
10227
10228         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10229                    " at %L", target_name, name, &p->where);
10230         return FAILURE;
10231
10232         /* Once we've found the specific binding, check it is not ambiguous with
10233            other specifics already found or inherited for the same GENERIC.  */
10234 specific_found:
10235         gcc_assert (target->specific);
10236
10237         /* This must really be a specific binding!  */
10238         if (target->specific->is_generic)
10239           {
10240             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
10241                        " '%s' is GENERIC, too", name, &p->where, target_name);
10242             return FAILURE;
10243           }
10244
10245         /* Check those already resolved on this type directly.  */
10246         for (g = p->u.generic; g; g = g->next)
10247           if (g != target && g->specific
10248               && check_generic_tbp_ambiguity (target, g, name, p->where)
10249                   == FAILURE)
10250             return FAILURE;
10251
10252         /* Check for ambiguity with inherited specific targets.  */
10253         for (overridden_tbp = p->overridden; overridden_tbp;
10254              overridden_tbp = overridden_tbp->overridden)
10255           if (overridden_tbp->is_generic)
10256             {
10257               for (g = overridden_tbp->u.generic; g; g = g->next)
10258                 {
10259                   gcc_assert (g->specific);
10260                   if (check_generic_tbp_ambiguity (target, g,
10261                                                    name, p->where) == FAILURE)
10262                     return FAILURE;
10263                 }
10264             }
10265       }
10266
10267   /* If we attempt to "overwrite" a specific binding, this is an error.  */
10268   if (p->overridden && !p->overridden->is_generic)
10269     {
10270       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
10271                  " the same name", name, &p->where);
10272       return FAILURE;
10273     }
10274
10275   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
10276      all must have the same attributes here.  */
10277   first_target = p->u.generic->specific->u.specific;
10278   gcc_assert (first_target);
10279   p->subroutine = first_target->n.sym->attr.subroutine;
10280   p->function = first_target->n.sym->attr.function;
10281
10282   return SUCCESS;
10283 }
10284
10285
10286 /* Resolve a GENERIC procedure binding for a derived type.  */
10287
10288 static gfc_try
10289 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
10290 {
10291   gfc_symbol* super_type;
10292
10293   /* Find the overridden binding if any.  */
10294   st->n.tb->overridden = NULL;
10295   super_type = gfc_get_derived_super_type (derived);
10296   if (super_type)
10297     {
10298       gfc_symtree* overridden;
10299       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
10300                                             true, NULL);
10301
10302       if (overridden && overridden->n.tb)
10303         st->n.tb->overridden = overridden->n.tb;
10304     }
10305
10306   /* Resolve using worker function.  */
10307   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
10308 }
10309
10310
10311 /* Retrieve the target-procedure of an operator binding and do some checks in
10312    common for intrinsic and user-defined type-bound operators.  */
10313
10314 static gfc_symbol*
10315 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
10316 {
10317   gfc_symbol* target_proc;
10318
10319   gcc_assert (target->specific && !target->specific->is_generic);
10320   target_proc = target->specific->u.specific->n.sym;
10321   gcc_assert (target_proc);
10322
10323   /* All operator bindings must have a passed-object dummy argument.  */
10324   if (target->specific->nopass)
10325     {
10326       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
10327       return NULL;
10328     }
10329
10330   return target_proc;
10331 }
10332
10333
10334 /* Resolve a type-bound intrinsic operator.  */
10335
10336 static gfc_try
10337 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
10338                                 gfc_typebound_proc* p)
10339 {
10340   gfc_symbol* super_type;
10341   gfc_tbp_generic* target;
10342   
10343   /* If there's already an error here, do nothing (but don't fail again).  */
10344   if (p->error)
10345     return SUCCESS;
10346
10347   /* Operators should always be GENERIC bindings.  */
10348   gcc_assert (p->is_generic);
10349
10350   /* Look for an overridden binding.  */
10351   super_type = gfc_get_derived_super_type (derived);
10352   if (super_type && super_type->f2k_derived)
10353     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
10354                                                      op, true, NULL);
10355   else
10356     p->overridden = NULL;
10357
10358   /* Resolve general GENERIC properties using worker function.  */
10359   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
10360     goto error;
10361
10362   /* Check the targets to be procedures of correct interface.  */
10363   for (target = p->u.generic; target; target = target->next)
10364     {
10365       gfc_symbol* target_proc;
10366
10367       target_proc = get_checked_tb_operator_target (target, p->where);
10368       if (!target_proc)
10369         goto error;
10370
10371       if (!gfc_check_operator_interface (target_proc, op, p->where))
10372         goto error;
10373     }
10374
10375   return SUCCESS;
10376
10377 error:
10378   p->error = 1;
10379   return FAILURE;
10380 }
10381
10382
10383 /* Resolve a type-bound user operator (tree-walker callback).  */
10384
10385 static gfc_symbol* resolve_bindings_derived;
10386 static gfc_try resolve_bindings_result;
10387
10388 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
10389
10390 static void
10391 resolve_typebound_user_op (gfc_symtree* stree)
10392 {
10393   gfc_symbol* super_type;
10394   gfc_tbp_generic* target;
10395
10396   gcc_assert (stree && stree->n.tb);
10397
10398   if (stree->n.tb->error)
10399     return;
10400
10401   /* Operators should always be GENERIC bindings.  */
10402   gcc_assert (stree->n.tb->is_generic);
10403
10404   /* Find overridden procedure, if any.  */
10405   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10406   if (super_type && super_type->f2k_derived)
10407     {
10408       gfc_symtree* overridden;
10409       overridden = gfc_find_typebound_user_op (super_type, NULL,
10410                                                stree->name, true, NULL);
10411
10412       if (overridden && overridden->n.tb)
10413         stree->n.tb->overridden = overridden->n.tb;
10414     }
10415   else
10416     stree->n.tb->overridden = NULL;
10417
10418   /* Resolve basically using worker function.  */
10419   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
10420         == FAILURE)
10421     goto error;
10422
10423   /* Check the targets to be functions of correct interface.  */
10424   for (target = stree->n.tb->u.generic; target; target = target->next)
10425     {
10426       gfc_symbol* target_proc;
10427
10428       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
10429       if (!target_proc)
10430         goto error;
10431
10432       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
10433         goto error;
10434     }
10435
10436   return;
10437
10438 error:
10439   resolve_bindings_result = FAILURE;
10440   stree->n.tb->error = 1;
10441 }
10442
10443
10444 /* Resolve the type-bound procedures for a derived type.  */
10445
10446 static void
10447 resolve_typebound_procedure (gfc_symtree* stree)
10448 {
10449   gfc_symbol* proc;
10450   locus where;
10451   gfc_symbol* me_arg;
10452   gfc_symbol* super_type;
10453   gfc_component* comp;
10454
10455   gcc_assert (stree);
10456
10457   /* Undefined specific symbol from GENERIC target definition.  */
10458   if (!stree->n.tb)
10459     return;
10460
10461   if (stree->n.tb->error)
10462     return;
10463
10464   /* If this is a GENERIC binding, use that routine.  */
10465   if (stree->n.tb->is_generic)
10466     {
10467       if (resolve_typebound_generic (resolve_bindings_derived, stree)
10468             == FAILURE)
10469         goto error;
10470       return;
10471     }
10472
10473   /* Get the target-procedure to check it.  */
10474   gcc_assert (!stree->n.tb->is_generic);
10475   gcc_assert (stree->n.tb->u.specific);
10476   proc = stree->n.tb->u.specific->n.sym;
10477   where = stree->n.tb->where;
10478
10479   /* Default access should already be resolved from the parser.  */
10480   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
10481
10482   /* It should be a module procedure or an external procedure with explicit
10483      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
10484   if ((!proc->attr.subroutine && !proc->attr.function)
10485       || (proc->attr.proc != PROC_MODULE
10486           && proc->attr.if_source != IFSRC_IFBODY)
10487       || (proc->attr.abstract && !stree->n.tb->deferred))
10488     {
10489       gfc_error ("'%s' must be a module procedure or an external procedure with"
10490                  " an explicit interface at %L", proc->name, &where);
10491       goto error;
10492     }
10493   stree->n.tb->subroutine = proc->attr.subroutine;
10494   stree->n.tb->function = proc->attr.function;
10495
10496   /* Find the super-type of the current derived type.  We could do this once and
10497      store in a global if speed is needed, but as long as not I believe this is
10498      more readable and clearer.  */
10499   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10500
10501   /* If PASS, resolve and check arguments if not already resolved / loaded
10502      from a .mod file.  */
10503   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
10504     {
10505       if (stree->n.tb->pass_arg)
10506         {
10507           gfc_formal_arglist* i;
10508
10509           /* If an explicit passing argument name is given, walk the arg-list
10510              and look for it.  */
10511
10512           me_arg = NULL;
10513           stree->n.tb->pass_arg_num = 1;
10514           for (i = proc->formal; i; i = i->next)
10515             {
10516               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
10517                 {
10518                   me_arg = i->sym;
10519                   break;
10520                 }
10521               ++stree->n.tb->pass_arg_num;
10522             }
10523
10524           if (!me_arg)
10525             {
10526               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
10527                          " argument '%s'",
10528                          proc->name, stree->n.tb->pass_arg, &where,
10529                          stree->n.tb->pass_arg);
10530               goto error;
10531             }
10532         }
10533       else
10534         {
10535           /* Otherwise, take the first one; there should in fact be at least
10536              one.  */
10537           stree->n.tb->pass_arg_num = 1;
10538           if (!proc->formal)
10539             {
10540               gfc_error ("Procedure '%s' with PASS at %L must have at"
10541                          " least one argument", proc->name, &where);
10542               goto error;
10543             }
10544           me_arg = proc->formal->sym;
10545         }
10546
10547       /* Now check that the argument-type matches and the passed-object
10548          dummy argument is generally fine.  */
10549
10550       gcc_assert (me_arg);
10551
10552       if (me_arg->ts.type != BT_CLASS)
10553         {
10554           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10555                      " at %L", proc->name, &where);
10556           goto error;
10557         }
10558
10559       if (CLASS_DATA (me_arg)->ts.u.derived
10560           != resolve_bindings_derived)
10561         {
10562           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10563                      " the derived-type '%s'", me_arg->name, proc->name,
10564                      me_arg->name, &where, resolve_bindings_derived->name);
10565           goto error;
10566         }
10567   
10568       gcc_assert (me_arg->ts.type == BT_CLASS);
10569       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
10570         {
10571           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
10572                      " scalar", proc->name, &where);
10573           goto error;
10574         }
10575       if (CLASS_DATA (me_arg)->attr.allocatable)
10576         {
10577           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10578                      " be ALLOCATABLE", proc->name, &where);
10579           goto error;
10580         }
10581       if (CLASS_DATA (me_arg)->attr.class_pointer)
10582         {
10583           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10584                      " be POINTER", proc->name, &where);
10585           goto error;
10586         }
10587     }
10588
10589   /* If we are extending some type, check that we don't override a procedure
10590      flagged NON_OVERRIDABLE.  */
10591   stree->n.tb->overridden = NULL;
10592   if (super_type)
10593     {
10594       gfc_symtree* overridden;
10595       overridden = gfc_find_typebound_proc (super_type, NULL,
10596                                             stree->name, true, NULL);
10597
10598       if (overridden && overridden->n.tb)
10599         stree->n.tb->overridden = overridden->n.tb;
10600
10601       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
10602         goto error;
10603     }
10604
10605   /* See if there's a name collision with a component directly in this type.  */
10606   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
10607     if (!strcmp (comp->name, stree->name))
10608       {
10609         gfc_error ("Procedure '%s' at %L has the same name as a component of"
10610                    " '%s'",
10611                    stree->name, &where, resolve_bindings_derived->name);
10612         goto error;
10613       }
10614
10615   /* Try to find a name collision with an inherited component.  */
10616   if (super_type && gfc_find_component (super_type, stree->name, true, true))
10617     {
10618       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
10619                  " component of '%s'",
10620                  stree->name, &where, resolve_bindings_derived->name);
10621       goto error;
10622     }
10623
10624   stree->n.tb->error = 0;
10625   return;
10626
10627 error:
10628   resolve_bindings_result = FAILURE;
10629   stree->n.tb->error = 1;
10630 }
10631
10632 static gfc_try
10633 resolve_typebound_procedures (gfc_symbol* derived)
10634 {
10635   int op;
10636
10637   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
10638     return SUCCESS;
10639
10640   resolve_bindings_derived = derived;
10641   resolve_bindings_result = SUCCESS;
10642
10643   if (derived->f2k_derived->tb_sym_root)
10644     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
10645                           &resolve_typebound_procedure);
10646
10647   if (derived->f2k_derived->tb_uop_root)
10648     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
10649                           &resolve_typebound_user_op);
10650
10651   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
10652     {
10653       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
10654       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
10655                                                p) == FAILURE)
10656         resolve_bindings_result = FAILURE;
10657     }
10658
10659   return resolve_bindings_result;
10660 }
10661
10662
10663 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
10664    to give all identical derived types the same backend_decl.  */
10665 static void
10666 add_dt_to_dt_list (gfc_symbol *derived)
10667 {
10668   gfc_dt_list *dt_list;
10669
10670   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
10671     if (derived == dt_list->derived)
10672       break;
10673
10674   if (dt_list == NULL)
10675     {
10676       dt_list = gfc_get_dt_list ();
10677       dt_list->next = gfc_derived_types;
10678       dt_list->derived = derived;
10679       gfc_derived_types = dt_list;
10680     }
10681 }
10682
10683
10684 /* Ensure that a derived-type is really not abstract, meaning that every
10685    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
10686
10687 static gfc_try
10688 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
10689 {
10690   if (!st)
10691     return SUCCESS;
10692
10693   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
10694     return FAILURE;
10695   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
10696     return FAILURE;
10697
10698   if (st->n.tb && st->n.tb->deferred)
10699     {
10700       gfc_symtree* overriding;
10701       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
10702       if (!overriding)
10703         return FAILURE;
10704       gcc_assert (overriding->n.tb);
10705       if (overriding->n.tb->deferred)
10706         {
10707           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
10708                      " '%s' is DEFERRED and not overridden",
10709                      sub->name, &sub->declared_at, st->name);
10710           return FAILURE;
10711         }
10712     }
10713
10714   return SUCCESS;
10715 }
10716
10717 static gfc_try
10718 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
10719 {
10720   /* The algorithm used here is to recursively travel up the ancestry of sub
10721      and for each ancestor-type, check all bindings.  If any of them is
10722      DEFERRED, look it up starting from sub and see if the found (overriding)
10723      binding is not DEFERRED.
10724      This is not the most efficient way to do this, but it should be ok and is
10725      clearer than something sophisticated.  */
10726
10727   gcc_assert (ancestor && !sub->attr.abstract);
10728   
10729   if (!ancestor->attr.abstract)
10730     return SUCCESS;
10731
10732   /* Walk bindings of this ancestor.  */
10733   if (ancestor->f2k_derived)
10734     {
10735       gfc_try t;
10736       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
10737       if (t == FAILURE)
10738         return FAILURE;
10739     }
10740
10741   /* Find next ancestor type and recurse on it.  */
10742   ancestor = gfc_get_derived_super_type (ancestor);
10743   if (ancestor)
10744     return ensure_not_abstract (sub, ancestor);
10745
10746   return SUCCESS;
10747 }
10748
10749
10750 static void resolve_symbol (gfc_symbol *sym);
10751
10752
10753 /* Resolve the components of a derived type.  */
10754
10755 static gfc_try
10756 resolve_fl_derived (gfc_symbol *sym)
10757 {
10758   gfc_symbol* super_type;
10759   gfc_component *c;
10760   int i;
10761
10762   super_type = gfc_get_derived_super_type (sym);
10763   
10764   if (sym->attr.is_class && sym->ts.u.derived == NULL)
10765     {
10766       /* Fix up incomplete CLASS symbols.  */
10767       gfc_component *data = gfc_find_component (sym, "$data", true, true);
10768       gfc_component *vptr = gfc_find_component (sym, "$vptr", true, true);
10769       if (vptr->ts.u.derived == NULL)
10770         {
10771           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived, false);
10772           gcc_assert (vtab);
10773           vptr->ts.u.derived = vtab->ts.u.derived;
10774         }
10775     }
10776
10777   /* F2008, C432. */
10778   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
10779     {
10780       gfc_error ("As extending type '%s' at %L has a coarray component, "
10781                  "parent type '%s' shall also have one", sym->name,
10782                  &sym->declared_at, super_type->name);
10783       return FAILURE;
10784     }
10785
10786   /* Ensure the extended type gets resolved before we do.  */
10787   if (super_type && resolve_fl_derived (super_type) == FAILURE)
10788     return FAILURE;
10789
10790   /* An ABSTRACT type must be extensible.  */
10791   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
10792     {
10793       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
10794                  sym->name, &sym->declared_at);
10795       return FAILURE;
10796     }
10797
10798   for (c = sym->components; c != NULL; c = c->next)
10799     {
10800       /* F2008, C442.  */
10801       if (c->attr.codimension /* FIXME: c->as check due to PR 43412.  */
10802           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
10803         {
10804           gfc_error ("Coarray component '%s' at %L must be allocatable with "
10805                      "deferred shape", c->name, &c->loc);
10806           return FAILURE;
10807         }
10808
10809       /* F2008, C443.  */
10810       if (c->attr.codimension && c->ts.type == BT_DERIVED
10811           && c->ts.u.derived->ts.is_iso_c)
10812         {
10813           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
10814                      "shall not be a coarray", c->name, &c->loc);
10815           return FAILURE;
10816         }
10817
10818       /* F2008, C444.  */
10819       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
10820           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
10821               || c->attr.allocatable))
10822         {
10823           gfc_error ("Component '%s' at %L with coarray component "
10824                      "shall be a nonpointer, nonallocatable scalar",
10825                      c->name, &c->loc);
10826           return FAILURE;
10827         }
10828
10829       /* F2008, C448.  */
10830       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
10831         {
10832           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
10833                      "is not an array pointer", c->name, &c->loc);
10834           return FAILURE;
10835         }
10836
10837       if (c->attr.proc_pointer && c->ts.interface)
10838         {
10839           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
10840             gfc_error ("Interface '%s', used by procedure pointer component "
10841                        "'%s' at %L, is declared in a later PROCEDURE statement",
10842                        c->ts.interface->name, c->name, &c->loc);
10843
10844           /* Get the attributes from the interface (now resolved).  */
10845           if (c->ts.interface->attr.if_source
10846               || c->ts.interface->attr.intrinsic)
10847             {
10848               gfc_symbol *ifc = c->ts.interface;
10849
10850               if (ifc->formal && !ifc->formal_ns)
10851                 resolve_symbol (ifc);
10852
10853               if (ifc->attr.intrinsic)
10854                 resolve_intrinsic (ifc, &ifc->declared_at);
10855
10856               if (ifc->result)
10857                 {
10858                   c->ts = ifc->result->ts;
10859                   c->attr.allocatable = ifc->result->attr.allocatable;
10860                   c->attr.pointer = ifc->result->attr.pointer;
10861                   c->attr.dimension = ifc->result->attr.dimension;
10862                   c->as = gfc_copy_array_spec (ifc->result->as);
10863                 }
10864               else
10865                 {   
10866                   c->ts = ifc->ts;
10867                   c->attr.allocatable = ifc->attr.allocatable;
10868                   c->attr.pointer = ifc->attr.pointer;
10869                   c->attr.dimension = ifc->attr.dimension;
10870                   c->as = gfc_copy_array_spec (ifc->as);
10871                 }
10872               c->ts.interface = ifc;
10873               c->attr.function = ifc->attr.function;
10874               c->attr.subroutine = ifc->attr.subroutine;
10875               gfc_copy_formal_args_ppc (c, ifc);
10876
10877               c->attr.pure = ifc->attr.pure;
10878               c->attr.elemental = ifc->attr.elemental;
10879               c->attr.recursive = ifc->attr.recursive;
10880               c->attr.always_explicit = ifc->attr.always_explicit;
10881               c->attr.ext_attr |= ifc->attr.ext_attr;
10882               /* Replace symbols in array spec.  */
10883               if (c->as)
10884                 {
10885                   int i;
10886                   for (i = 0; i < c->as->rank; i++)
10887                     {
10888                       gfc_expr_replace_comp (c->as->lower[i], c);
10889                       gfc_expr_replace_comp (c->as->upper[i], c);
10890                     }
10891                 }
10892               /* Copy char length.  */
10893               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
10894                 {
10895                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
10896                   gfc_expr_replace_comp (cl->length, c);
10897                   if (cl->length && !cl->resolved
10898                         && gfc_resolve_expr (cl->length) == FAILURE)
10899                     return FAILURE;
10900                   c->ts.u.cl = cl;
10901                 }
10902             }
10903           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
10904             {
10905               gfc_error ("Interface '%s' of procedure pointer component "
10906                          "'%s' at %L must be explicit", c->ts.interface->name,
10907                          c->name, &c->loc);
10908               return FAILURE;
10909             }
10910         }
10911       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
10912         {
10913           /* Since PPCs are not implicitly typed, a PPC without an explicit
10914              interface must be a subroutine.  */
10915           gfc_add_subroutine (&c->attr, c->name, &c->loc);
10916         }
10917
10918       /* Procedure pointer components: Check PASS arg.  */
10919       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
10920           && !sym->attr.vtype)
10921         {
10922           gfc_symbol* me_arg;
10923
10924           if (c->tb->pass_arg)
10925             {
10926               gfc_formal_arglist* i;
10927
10928               /* If an explicit passing argument name is given, walk the arg-list
10929                 and look for it.  */
10930
10931               me_arg = NULL;
10932               c->tb->pass_arg_num = 1;
10933               for (i = c->formal; i; i = i->next)
10934                 {
10935                   if (!strcmp (i->sym->name, c->tb->pass_arg))
10936                     {
10937                       me_arg = i->sym;
10938                       break;
10939                     }
10940                   c->tb->pass_arg_num++;
10941                 }
10942
10943               if (!me_arg)
10944                 {
10945                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
10946                              "at %L has no argument '%s'", c->name,
10947                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
10948                   c->tb->error = 1;
10949                   return FAILURE;
10950                 }
10951             }
10952           else
10953             {
10954               /* Otherwise, take the first one; there should in fact be at least
10955                 one.  */
10956               c->tb->pass_arg_num = 1;
10957               if (!c->formal)
10958                 {
10959                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
10960                              "must have at least one argument",
10961                              c->name, &c->loc);
10962                   c->tb->error = 1;
10963                   return FAILURE;
10964                 }
10965               me_arg = c->formal->sym;
10966             }
10967
10968           /* Now check that the argument-type matches.  */
10969           gcc_assert (me_arg);
10970           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
10971               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
10972               || (me_arg->ts.type == BT_CLASS
10973                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
10974             {
10975               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10976                          " the derived type '%s'", me_arg->name, c->name,
10977                          me_arg->name, &c->loc, sym->name);
10978               c->tb->error = 1;
10979               return FAILURE;
10980             }
10981
10982           /* Check for C453.  */
10983           if (me_arg->attr.dimension)
10984             {
10985               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10986                          "must be scalar", me_arg->name, c->name, me_arg->name,
10987                          &c->loc);
10988               c->tb->error = 1;
10989               return FAILURE;
10990             }
10991
10992           if (me_arg->attr.pointer)
10993             {
10994               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10995                          "may not have the POINTER attribute", me_arg->name,
10996                          c->name, me_arg->name, &c->loc);
10997               c->tb->error = 1;
10998               return FAILURE;
10999             }
11000
11001           if (me_arg->attr.allocatable)
11002             {
11003               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11004                          "may not be ALLOCATABLE", me_arg->name, c->name,
11005                          me_arg->name, &c->loc);
11006               c->tb->error = 1;
11007               return FAILURE;
11008             }
11009
11010           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11011             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11012                        " at %L", c->name, &c->loc);
11013
11014         }
11015
11016       /* Check type-spec if this is not the parent-type component.  */
11017       if ((!sym->attr.extension || c != sym->components)
11018           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11019         return FAILURE;
11020
11021       /* If this type is an extension, set the accessibility of the parent
11022          component.  */
11023       if (super_type && c == sym->components
11024           && strcmp (super_type->name, c->name) == 0)
11025         c->attr.access = super_type->attr.access;
11026       
11027       /* If this type is an extension, see if this component has the same name
11028          as an inherited type-bound procedure.  */
11029       if (super_type && !sym->attr.is_class
11030           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11031         {
11032           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11033                      " inherited type-bound procedure",
11034                      c->name, sym->name, &c->loc);
11035           return FAILURE;
11036         }
11037
11038       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer)
11039         {
11040          if (c->ts.u.cl->length == NULL
11041              || (resolve_charlen (c->ts.u.cl) == FAILURE)
11042              || !gfc_is_constant_expr (c->ts.u.cl->length))
11043            {
11044              gfc_error ("Character length of component '%s' needs to "
11045                         "be a constant specification expression at %L",
11046                         c->name,
11047                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
11048              return FAILURE;
11049            }
11050         }
11051
11052       if (c->ts.type == BT_DERIVED
11053           && sym->component_access != ACCESS_PRIVATE
11054           && gfc_check_access (sym->attr.access, sym->ns->default_access)
11055           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11056           && !c->ts.u.derived->attr.use_assoc
11057           && !gfc_check_access (c->ts.u.derived->attr.access,
11058                                 c->ts.u.derived->ns->default_access)
11059           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11060                              "is a PRIVATE type and cannot be a component of "
11061                              "'%s', which is PUBLIC at %L", c->name,
11062                              sym->name, &sym->declared_at) == FAILURE)
11063         return FAILURE;
11064
11065       if (sym->attr.sequence)
11066         {
11067           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
11068             {
11069               gfc_error ("Component %s of SEQUENCE type declared at %L does "
11070                          "not have the SEQUENCE attribute",
11071                          c->ts.u.derived->name, &sym->declared_at);
11072               return FAILURE;
11073             }
11074         }
11075
11076       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && c->attr.pointer
11077           && c->ts.u.derived->components == NULL
11078           && !c->ts.u.derived->attr.zero_comp)
11079         {
11080           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11081                      "that has not been declared", c->name, sym->name,
11082                      &c->loc);
11083           return FAILURE;
11084         }
11085
11086       if (c->ts.type == BT_CLASS && CLASS_DATA (c)->attr.pointer
11087           && CLASS_DATA (c)->ts.u.derived->components == NULL
11088           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
11089         {
11090           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11091                      "that has not been declared", c->name, sym->name,
11092                      &c->loc);
11093           return FAILURE;
11094         }
11095
11096       /* C437.  */
11097       if (c->ts.type == BT_CLASS
11098           && !(CLASS_DATA (c)->attr.pointer || CLASS_DATA (c)->attr.allocatable))
11099         {
11100           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
11101                      "or pointer", c->name, &c->loc);
11102           return FAILURE;
11103         }
11104
11105       /* Ensure that all the derived type components are put on the
11106          derived type list; even in formal namespaces, where derived type
11107          pointer components might not have been declared.  */
11108       if (c->ts.type == BT_DERIVED
11109             && c->ts.u.derived
11110             && c->ts.u.derived->components
11111             && c->attr.pointer
11112             && sym != c->ts.u.derived)
11113         add_dt_to_dt_list (c->ts.u.derived);
11114
11115       if (c->attr.pointer || c->attr.proc_pointer || c->attr.allocatable
11116           || c->as == NULL)
11117         continue;
11118
11119       for (i = 0; i < c->as->rank; i++)
11120         {
11121           if (c->as->lower[i] == NULL
11122               || (resolve_index_expr (c->as->lower[i]) == FAILURE)
11123               || !gfc_is_constant_expr (c->as->lower[i])
11124               || c->as->upper[i] == NULL
11125               || (resolve_index_expr (c->as->upper[i]) == FAILURE)
11126               || !gfc_is_constant_expr (c->as->upper[i]))
11127             {
11128               gfc_error ("Component '%s' of '%s' at %L must have "
11129                          "constant array bounds",
11130                          c->name, sym->name, &c->loc);
11131               return FAILURE;
11132             }
11133         }
11134     }
11135
11136   /* Resolve the type-bound procedures.  */
11137   if (resolve_typebound_procedures (sym) == FAILURE)
11138     return FAILURE;
11139
11140   /* Resolve the finalizer procedures.  */
11141   if (gfc_resolve_finalizers (sym) == FAILURE)
11142     return FAILURE;
11143
11144   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11145      all DEFERRED bindings are overridden.  */
11146   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11147       && !sym->attr.is_class
11148       && ensure_not_abstract (sym, super_type) == FAILURE)
11149     return FAILURE;
11150
11151   /* Add derived type to the derived type list.  */
11152   add_dt_to_dt_list (sym);
11153
11154   return SUCCESS;
11155 }
11156
11157
11158 static gfc_try
11159 resolve_fl_namelist (gfc_symbol *sym)
11160 {
11161   gfc_namelist *nl;
11162   gfc_symbol *nlsym;
11163
11164   /* Reject PRIVATE objects in a PUBLIC namelist.  */
11165   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
11166     {
11167       for (nl = sym->namelist; nl; nl = nl->next)
11168         {
11169           if (!nl->sym->attr.use_assoc
11170               && !is_sym_host_assoc (nl->sym, sym->ns)
11171               && !gfc_check_access(nl->sym->attr.access,
11172                                 nl->sym->ns->default_access))
11173             {
11174               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
11175                          "cannot be member of PUBLIC namelist '%s' at %L",
11176                          nl->sym->name, sym->name, &sym->declared_at);
11177               return FAILURE;
11178             }
11179
11180           /* Types with private components that came here by USE-association.  */
11181           if (nl->sym->ts.type == BT_DERIVED
11182               && derived_inaccessible (nl->sym->ts.u.derived))
11183             {
11184               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
11185                          "components and cannot be member of namelist '%s' at %L",
11186                          nl->sym->name, sym->name, &sym->declared_at);
11187               return FAILURE;
11188             }
11189
11190           /* Types with private components that are defined in the same module.  */
11191           if (nl->sym->ts.type == BT_DERIVED
11192               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
11193               && !gfc_check_access (nl->sym->ts.u.derived->attr.private_comp
11194                                         ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
11195                                         nl->sym->ns->default_access))
11196             {
11197               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
11198                          "cannot be a member of PUBLIC namelist '%s' at %L",
11199                          nl->sym->name, sym->name, &sym->declared_at);
11200               return FAILURE;
11201             }
11202         }
11203     }
11204
11205   for (nl = sym->namelist; nl; nl = nl->next)
11206     {
11207       /* Reject namelist arrays of assumed shape.  */
11208       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
11209           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
11210                              "must not have assumed shape in namelist "
11211                              "'%s' at %L", nl->sym->name, sym->name,
11212                              &sym->declared_at) == FAILURE)
11213             return FAILURE;
11214
11215       /* Reject namelist arrays that are not constant shape.  */
11216       if (is_non_constant_shape_array (nl->sym))
11217         {
11218           gfc_error ("NAMELIST array object '%s' must have constant "
11219                      "shape in namelist '%s' at %L", nl->sym->name,
11220                      sym->name, &sym->declared_at);
11221           return FAILURE;
11222         }
11223
11224       /* Namelist objects cannot have allocatable or pointer components.  */
11225       if (nl->sym->ts.type != BT_DERIVED)
11226         continue;
11227
11228       if (nl->sym->ts.u.derived->attr.alloc_comp)
11229         {
11230           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11231                      "have ALLOCATABLE components",
11232                      nl->sym->name, sym->name, &sym->declared_at);
11233           return FAILURE;
11234         }
11235
11236       if (nl->sym->ts.u.derived->attr.pointer_comp)
11237         {
11238           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11239                      "have POINTER components", 
11240                      nl->sym->name, sym->name, &sym->declared_at);
11241           return FAILURE;
11242         }
11243     }
11244
11245
11246   /* 14.1.2 A module or internal procedure represent local entities
11247      of the same type as a namelist member and so are not allowed.  */
11248   for (nl = sym->namelist; nl; nl = nl->next)
11249     {
11250       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
11251         continue;
11252
11253       if (nl->sym->attr.function && nl->sym == nl->sym->result)
11254         if ((nl->sym == sym->ns->proc_name)
11255                ||
11256             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
11257           continue;
11258
11259       nlsym = NULL;
11260       if (nl->sym && nl->sym->name)
11261         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
11262       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
11263         {
11264           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
11265                      "attribute in '%s' at %L", nlsym->name,
11266                      &sym->declared_at);
11267           return FAILURE;
11268         }
11269     }
11270
11271   return SUCCESS;
11272 }
11273
11274
11275 static gfc_try
11276 resolve_fl_parameter (gfc_symbol *sym)
11277 {
11278   /* A parameter array's shape needs to be constant.  */
11279   if (sym->as != NULL 
11280       && (sym->as->type == AS_DEFERRED
11281           || is_non_constant_shape_array (sym)))
11282     {
11283       gfc_error ("Parameter array '%s' at %L cannot be automatic "
11284                  "or of deferred shape", sym->name, &sym->declared_at);
11285       return FAILURE;
11286     }
11287
11288   /* Make sure a parameter that has been implicitly typed still
11289      matches the implicit type, since PARAMETER statements can precede
11290      IMPLICIT statements.  */
11291   if (sym->attr.implicit_type
11292       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
11293                                                              sym->ns)))
11294     {
11295       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
11296                  "later IMPLICIT type", sym->name, &sym->declared_at);
11297       return FAILURE;
11298     }
11299
11300   /* Make sure the types of derived parameters are consistent.  This
11301      type checking is deferred until resolution because the type may
11302      refer to a derived type from the host.  */
11303   if (sym->ts.type == BT_DERIVED
11304       && !gfc_compare_types (&sym->ts, &sym->value->ts))
11305     {
11306       gfc_error ("Incompatible derived type in PARAMETER at %L",
11307                  &sym->value->where);
11308       return FAILURE;
11309     }
11310   return SUCCESS;
11311 }
11312
11313
11314 /* Do anything necessary to resolve a symbol.  Right now, we just
11315    assume that an otherwise unknown symbol is a variable.  This sort
11316    of thing commonly happens for symbols in module.  */
11317
11318 static void
11319 resolve_symbol (gfc_symbol *sym)
11320 {
11321   int check_constant, mp_flag;
11322   gfc_symtree *symtree;
11323   gfc_symtree *this_symtree;
11324   gfc_namespace *ns;
11325   gfc_component *c;
11326
11327   /* Avoid double resolution of function result symbols.  */
11328   if ((sym->result || sym->attr.result) && (sym->ns != gfc_current_ns))
11329     return;
11330   
11331   if (sym->attr.flavor == FL_UNKNOWN)
11332     {
11333
11334     /* If we find that a flavorless symbol is an interface in one of the
11335        parent namespaces, find its symtree in this namespace, free the
11336        symbol and set the symtree to point to the interface symbol.  */
11337       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
11338         {
11339           symtree = gfc_find_symtree (ns->sym_root, sym->name);
11340           if (symtree && symtree->n.sym->generic)
11341             {
11342               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
11343                                                sym->name);
11344               sym->refs--;
11345               if (!sym->refs)
11346                 gfc_free_symbol (sym);
11347               symtree->n.sym->refs++;
11348               this_symtree->n.sym = symtree->n.sym;
11349               return;
11350             }
11351         }
11352
11353       /* Otherwise give it a flavor according to such attributes as
11354          it has.  */
11355       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
11356         sym->attr.flavor = FL_VARIABLE;
11357       else
11358         {
11359           sym->attr.flavor = FL_PROCEDURE;
11360           if (sym->attr.dimension)
11361             sym->attr.function = 1;
11362         }
11363     }
11364
11365   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
11366     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
11367
11368   if (sym->attr.procedure && sym->ts.interface
11369       && sym->attr.if_source != IFSRC_DECL)
11370     {
11371       if (sym->ts.interface == sym)
11372         {
11373           gfc_error ("PROCEDURE '%s' at %L may not be used as its own "
11374                      "interface", sym->name, &sym->declared_at);
11375           return;
11376         }
11377       if (sym->ts.interface->attr.procedure)
11378         {
11379           gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared"
11380                      " in a later PROCEDURE statement", sym->ts.interface->name,
11381                      sym->name,&sym->declared_at);
11382           return;
11383         }
11384
11385       /* Get the attributes from the interface (now resolved).  */
11386       if (sym->ts.interface->attr.if_source
11387           || sym->ts.interface->attr.intrinsic)
11388         {
11389           gfc_symbol *ifc = sym->ts.interface;
11390           resolve_symbol (ifc);
11391
11392           if (ifc->attr.intrinsic)
11393             resolve_intrinsic (ifc, &ifc->declared_at);
11394
11395           if (ifc->result)
11396             sym->ts = ifc->result->ts;
11397           else   
11398             sym->ts = ifc->ts;
11399           sym->ts.interface = ifc;
11400           sym->attr.function = ifc->attr.function;
11401           sym->attr.subroutine = ifc->attr.subroutine;
11402           gfc_copy_formal_args (sym, ifc);
11403
11404           sym->attr.allocatable = ifc->attr.allocatable;
11405           sym->attr.pointer = ifc->attr.pointer;
11406           sym->attr.pure = ifc->attr.pure;
11407           sym->attr.elemental = ifc->attr.elemental;
11408           sym->attr.dimension = ifc->attr.dimension;
11409           sym->attr.contiguous = ifc->attr.contiguous;
11410           sym->attr.recursive = ifc->attr.recursive;
11411           sym->attr.always_explicit = ifc->attr.always_explicit;
11412           sym->attr.ext_attr |= ifc->attr.ext_attr;
11413           /* Copy array spec.  */
11414           sym->as = gfc_copy_array_spec (ifc->as);
11415           if (sym->as)
11416             {
11417               int i;
11418               for (i = 0; i < sym->as->rank; i++)
11419                 {
11420                   gfc_expr_replace_symbols (sym->as->lower[i], sym);
11421                   gfc_expr_replace_symbols (sym->as->upper[i], sym);
11422                 }
11423             }
11424           /* Copy char length.  */
11425           if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11426             {
11427               sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11428               gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
11429               if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
11430                     && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
11431                 return;
11432             }
11433         }
11434       else if (sym->ts.interface->name[0] != '\0')
11435         {
11436           gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
11437                     sym->ts.interface->name, sym->name, &sym->declared_at);
11438           return;
11439         }
11440     }
11441
11442   if (sym->attr.is_protected && !sym->attr.proc_pointer
11443       && (sym->attr.procedure || sym->attr.external))
11444     {
11445       if (sym->attr.external)
11446         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
11447                    "at %L", &sym->declared_at);
11448       else
11449         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
11450                    "at %L", &sym->declared_at);
11451
11452       return;
11453     }
11454
11455
11456   /* F2008, C530. */
11457   if (sym->attr.contiguous
11458       && (!sym->attr.dimension || (sym->as->type != AS_ASSUMED_SHAPE
11459                                    && !sym->attr.pointer)))
11460     {
11461       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
11462                   "array pointer or an assumed-shape array", sym->name,
11463                   &sym->declared_at);
11464       return;
11465     }
11466
11467   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
11468     return;
11469
11470   /* Symbols that are module procedures with results (functions) have
11471      the types and array specification copied for type checking in
11472      procedures that call them, as well as for saving to a module
11473      file.  These symbols can't stand the scrutiny that their results
11474      can.  */
11475   mp_flag = (sym->result != NULL && sym->result != sym);
11476
11477   /* Make sure that the intrinsic is consistent with its internal 
11478      representation. This needs to be done before assigning a default 
11479      type to avoid spurious warnings.  */
11480   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
11481       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
11482     return;
11483
11484   /* For associate names, resolve corresponding expression and make sure
11485      they get their type-spec set this way.  */
11486   if (sym->assoc)
11487     {
11488       gcc_assert (sym->attr.flavor == FL_VARIABLE);
11489       if (gfc_resolve_expr (sym->assoc->target) != SUCCESS)
11490         return;
11491
11492       sym->ts = sym->assoc->target->ts;
11493       gcc_assert (sym->ts.type != BT_UNKNOWN);
11494     }
11495
11496   /* Assign default type to symbols that need one and don't have one.  */
11497   if (sym->ts.type == BT_UNKNOWN)
11498     {
11499       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
11500         gfc_set_default_type (sym, 1, NULL);
11501
11502       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
11503           && !sym->attr.function && !sym->attr.subroutine
11504           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
11505         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
11506
11507       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
11508         {
11509           /* The specific case of an external procedure should emit an error
11510              in the case that there is no implicit type.  */
11511           if (!mp_flag)
11512             gfc_set_default_type (sym, sym->attr.external, NULL);
11513           else
11514             {
11515               /* Result may be in another namespace.  */
11516               resolve_symbol (sym->result);
11517
11518               if (!sym->result->attr.proc_pointer)
11519                 {
11520                   sym->ts = sym->result->ts;
11521                   sym->as = gfc_copy_array_spec (sym->result->as);
11522                   sym->attr.dimension = sym->result->attr.dimension;
11523                   sym->attr.pointer = sym->result->attr.pointer;
11524                   sym->attr.allocatable = sym->result->attr.allocatable;
11525                   sym->attr.contiguous = sym->result->attr.contiguous;
11526                 }
11527             }
11528         }
11529     }
11530
11531   /* Assumed size arrays and assumed shape arrays must be dummy
11532      arguments.  */
11533
11534   if (sym->as != NULL
11535       && ((sym->as->type == AS_ASSUMED_SIZE && !sym->as->cp_was_assumed)
11536           || sym->as->type == AS_ASSUMED_SHAPE)
11537       && sym->attr.dummy == 0)
11538     {
11539       if (sym->as->type == AS_ASSUMED_SIZE)
11540         gfc_error ("Assumed size array at %L must be a dummy argument",
11541                    &sym->declared_at);
11542       else
11543         gfc_error ("Assumed shape array at %L must be a dummy argument",
11544                    &sym->declared_at);
11545       return;
11546     }
11547
11548   /* Make sure symbols with known intent or optional are really dummy
11549      variable.  Because of ENTRY statement, this has to be deferred
11550      until resolution time.  */
11551
11552   if (!sym->attr.dummy
11553       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
11554     {
11555       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
11556       return;
11557     }
11558
11559   if (sym->attr.value && !sym->attr.dummy)
11560     {
11561       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
11562                  "it is not a dummy argument", sym->name, &sym->declared_at);
11563       return;
11564     }
11565
11566   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
11567     {
11568       gfc_charlen *cl = sym->ts.u.cl;
11569       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
11570         {
11571           gfc_error ("Character dummy variable '%s' at %L with VALUE "
11572                      "attribute must have constant length",
11573                      sym->name, &sym->declared_at);
11574           return;
11575         }
11576
11577       if (sym->ts.is_c_interop
11578           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
11579         {
11580           gfc_error ("C interoperable character dummy variable '%s' at %L "
11581                      "with VALUE attribute must have length one",
11582                      sym->name, &sym->declared_at);
11583           return;
11584         }
11585     }
11586
11587   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
11588      do this for something that was implicitly typed because that is handled
11589      in gfc_set_default_type.  Handle dummy arguments and procedure
11590      definitions separately.  Also, anything that is use associated is not
11591      handled here but instead is handled in the module it is declared in.
11592      Finally, derived type definitions are allowed to be BIND(C) since that
11593      only implies that they're interoperable, and they are checked fully for
11594      interoperability when a variable is declared of that type.  */
11595   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
11596       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
11597       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
11598     {
11599       gfc_try t = SUCCESS;
11600       
11601       /* First, make sure the variable is declared at the
11602          module-level scope (J3/04-007, Section 15.3).  */
11603       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
11604           sym->attr.in_common == 0)
11605         {
11606           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
11607                      "is neither a COMMON block nor declared at the "
11608                      "module level scope", sym->name, &(sym->declared_at));
11609           t = FAILURE;
11610         }
11611       else if (sym->common_head != NULL)
11612         {
11613           t = verify_com_block_vars_c_interop (sym->common_head);
11614         }
11615       else
11616         {
11617           /* If type() declaration, we need to verify that the components
11618              of the given type are all C interoperable, etc.  */
11619           if (sym->ts.type == BT_DERIVED &&
11620               sym->ts.u.derived->attr.is_c_interop != 1)
11621             {
11622               /* Make sure the user marked the derived type as BIND(C).  If
11623                  not, call the verify routine.  This could print an error
11624                  for the derived type more than once if multiple variables
11625                  of that type are declared.  */
11626               if (sym->ts.u.derived->attr.is_bind_c != 1)
11627                 verify_bind_c_derived_type (sym->ts.u.derived);
11628               t = FAILURE;
11629             }
11630           
11631           /* Verify the variable itself as C interoperable if it
11632              is BIND(C).  It is not possible for this to succeed if
11633              the verify_bind_c_derived_type failed, so don't have to handle
11634              any error returned by verify_bind_c_derived_type.  */
11635           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
11636                                  sym->common_block);
11637         }
11638
11639       if (t == FAILURE)
11640         {
11641           /* clear the is_bind_c flag to prevent reporting errors more than
11642              once if something failed.  */
11643           sym->attr.is_bind_c = 0;
11644           return;
11645         }
11646     }
11647
11648   /* If a derived type symbol has reached this point, without its
11649      type being declared, we have an error.  Notice that most
11650      conditions that produce undefined derived types have already
11651      been dealt with.  However, the likes of:
11652      implicit type(t) (t) ..... call foo (t) will get us here if
11653      the type is not declared in the scope of the implicit
11654      statement. Change the type to BT_UNKNOWN, both because it is so
11655      and to prevent an ICE.  */
11656   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
11657       && !sym->ts.u.derived->attr.zero_comp)
11658     {
11659       gfc_error ("The derived type '%s' at %L is of type '%s', "
11660                  "which has not been defined", sym->name,
11661                   &sym->declared_at, sym->ts.u.derived->name);
11662       sym->ts.type = BT_UNKNOWN;
11663       return;
11664     }
11665
11666   /* Make sure that the derived type has been resolved and that the
11667      derived type is visible in the symbol's namespace, if it is a
11668      module function and is not PRIVATE.  */
11669   if (sym->ts.type == BT_DERIVED
11670         && sym->ts.u.derived->attr.use_assoc
11671         && sym->ns->proc_name
11672         && sym->ns->proc_name->attr.flavor == FL_MODULE)
11673     {
11674       gfc_symbol *ds;
11675
11676       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
11677         return;
11678
11679       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
11680       if (!ds && sym->attr.function
11681             && gfc_check_access (sym->attr.access, sym->ns->default_access))
11682         {
11683           symtree = gfc_new_symtree (&sym->ns->sym_root,
11684                                      sym->ts.u.derived->name);
11685           symtree->n.sym = sym->ts.u.derived;
11686           sym->ts.u.derived->refs++;
11687         }
11688     }
11689
11690   /* Unless the derived-type declaration is use associated, Fortran 95
11691      does not allow public entries of private derived types.
11692      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
11693      161 in 95-006r3.  */
11694   if (sym->ts.type == BT_DERIVED
11695       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
11696       && !sym->ts.u.derived->attr.use_assoc
11697       && gfc_check_access (sym->attr.access, sym->ns->default_access)
11698       && !gfc_check_access (sym->ts.u.derived->attr.access,
11699                             sym->ts.u.derived->ns->default_access)
11700       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
11701                          "of PRIVATE derived type '%s'",
11702                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
11703                          : "variable", sym->name, &sym->declared_at,
11704                          sym->ts.u.derived->name) == FAILURE)
11705     return;
11706
11707   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
11708      default initialization is defined (5.1.2.4.4).  */
11709   if (sym->ts.type == BT_DERIVED
11710       && sym->attr.dummy
11711       && sym->attr.intent == INTENT_OUT
11712       && sym->as
11713       && sym->as->type == AS_ASSUMED_SIZE)
11714     {
11715       for (c = sym->ts.u.derived->components; c; c = c->next)
11716         {
11717           if (c->initializer)
11718             {
11719               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
11720                          "ASSUMED SIZE and so cannot have a default initializer",
11721                          sym->name, &sym->declared_at);
11722               return;
11723             }
11724         }
11725     }
11726
11727   /* F2008, C526.  */
11728   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11729        || sym->attr.codimension)
11730       && sym->attr.result)
11731     gfc_error ("Function result '%s' at %L shall not be a coarray or have "
11732                "a coarray component", sym->name, &sym->declared_at);
11733
11734   /* F2008, C524.  */
11735   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
11736       && sym->ts.u.derived->ts.is_iso_c)
11737     gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11738                "shall not be a coarray", sym->name, &sym->declared_at);
11739
11740   /* F2008, C525.  */
11741   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp
11742       && (sym->attr.codimension || sym->attr.pointer || sym->attr.dimension
11743           || sym->attr.allocatable))
11744     gfc_error ("Variable '%s' at %L with coarray component "
11745                "shall be a nonpointer, nonallocatable scalar",
11746                sym->name, &sym->declared_at);
11747
11748   /* F2008, C526.  The function-result case was handled above.  */
11749   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11750        || sym->attr.codimension)
11751       && !(sym->attr.allocatable || sym->attr.dummy || sym->attr.save
11752            || sym->ns->proc_name->attr.flavor == FL_MODULE
11753            || sym->ns->proc_name->attr.is_main_program
11754            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
11755     gfc_error ("Variable '%s' at %L is a coarray or has a coarray "
11756                "component and is not ALLOCATABLE, SAVE nor a "
11757                "dummy argument", sym->name, &sym->declared_at);
11758   /* F2008, C528.  */  /* FIXME: sym->as check due to PR 43412.  */
11759   else if (sym->attr.codimension && !sym->attr.allocatable
11760       && sym->as && sym->as->cotype == AS_DEFERRED)
11761     gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
11762                 "deferred shape", sym->name, &sym->declared_at);
11763   else if (sym->attr.codimension && sym->attr.allocatable
11764       && (sym->as->type != AS_DEFERRED || sym->as->cotype != AS_DEFERRED))
11765     gfc_error ("Allocatable coarray variable '%s' at %L must have "
11766                "deferred shape", sym->name, &sym->declared_at);
11767
11768
11769   /* F2008, C541.  */
11770   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11771        || (sym->attr.codimension && sym->attr.allocatable))
11772       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
11773     gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
11774                "allocatable coarray or have coarray components",
11775                sym->name, &sym->declared_at);
11776
11777   if (sym->attr.codimension && sym->attr.dummy
11778       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
11779     gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
11780                "procedure '%s'", sym->name, &sym->declared_at,
11781                sym->ns->proc_name->name);
11782
11783   switch (sym->attr.flavor)
11784     {
11785     case FL_VARIABLE:
11786       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
11787         return;
11788       break;
11789
11790     case FL_PROCEDURE:
11791       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
11792         return;
11793       break;
11794
11795     case FL_NAMELIST:
11796       if (resolve_fl_namelist (sym) == FAILURE)
11797         return;
11798       break;
11799
11800     case FL_PARAMETER:
11801       if (resolve_fl_parameter (sym) == FAILURE)
11802         return;
11803       break;
11804
11805     default:
11806       break;
11807     }
11808
11809   /* Resolve array specifier. Check as well some constraints
11810      on COMMON blocks.  */
11811
11812   check_constant = sym->attr.in_common && !sym->attr.pointer;
11813
11814   /* Set the formal_arg_flag so that check_conflict will not throw
11815      an error for host associated variables in the specification
11816      expression for an array_valued function.  */
11817   if (sym->attr.function && sym->as)
11818     formal_arg_flag = 1;
11819
11820   gfc_resolve_array_spec (sym->as, check_constant);
11821
11822   formal_arg_flag = 0;
11823
11824   /* Resolve formal namespaces.  */
11825   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
11826       && !sym->attr.contained && !sym->attr.intrinsic)
11827     gfc_resolve (sym->formal_ns);
11828
11829   /* Make sure the formal namespace is present.  */
11830   if (sym->formal && !sym->formal_ns)
11831     {
11832       gfc_formal_arglist *formal = sym->formal;
11833       while (formal && !formal->sym)
11834         formal = formal->next;
11835
11836       if (formal)
11837         {
11838           sym->formal_ns = formal->sym->ns;
11839           sym->formal_ns->refs++;
11840         }
11841     }
11842
11843   /* Check threadprivate restrictions.  */
11844   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
11845       && (!sym->attr.in_common
11846           && sym->module == NULL
11847           && (sym->ns->proc_name == NULL
11848               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
11849     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
11850
11851   /* If we have come this far we can apply default-initializers, as
11852      described in 14.7.5, to those variables that have not already
11853      been assigned one.  */
11854   if (sym->ts.type == BT_DERIVED
11855       && sym->attr.referenced
11856       && sym->ns == gfc_current_ns
11857       && !sym->value
11858       && !sym->attr.allocatable
11859       && !sym->attr.alloc_comp)
11860     {
11861       symbol_attribute *a = &sym->attr;
11862
11863       if ((!a->save && !a->dummy && !a->pointer
11864            && !a->in_common && !a->use_assoc
11865            && !(a->function && sym != sym->result))
11866           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
11867         apply_default_init (sym);
11868     }
11869
11870   /* If this symbol has a type-spec, check it.  */
11871   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
11872       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
11873     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
11874           == FAILURE)
11875       return;
11876 }
11877
11878
11879 /************* Resolve DATA statements *************/
11880
11881 static struct
11882 {
11883   gfc_data_value *vnode;
11884   mpz_t left;
11885 }
11886 values;
11887
11888
11889 /* Advance the values structure to point to the next value in the data list.  */
11890
11891 static gfc_try
11892 next_data_value (void)
11893 {
11894   while (mpz_cmp_ui (values.left, 0) == 0)
11895     {
11896
11897       if (values.vnode->next == NULL)
11898         return FAILURE;
11899
11900       values.vnode = values.vnode->next;
11901       mpz_set (values.left, values.vnode->repeat);
11902     }
11903
11904   return SUCCESS;
11905 }
11906
11907
11908 static gfc_try
11909 check_data_variable (gfc_data_variable *var, locus *where)
11910 {
11911   gfc_expr *e;
11912   mpz_t size;
11913   mpz_t offset;
11914   gfc_try t;
11915   ar_type mark = AR_UNKNOWN;
11916   int i;
11917   mpz_t section_index[GFC_MAX_DIMENSIONS];
11918   gfc_ref *ref;
11919   gfc_array_ref *ar;
11920   gfc_symbol *sym;
11921   int has_pointer;
11922
11923   if (gfc_resolve_expr (var->expr) == FAILURE)
11924     return FAILURE;
11925
11926   ar = NULL;
11927   mpz_init_set_si (offset, 0);
11928   e = var->expr;
11929
11930   if (e->expr_type != EXPR_VARIABLE)
11931     gfc_internal_error ("check_data_variable(): Bad expression");
11932
11933   sym = e->symtree->n.sym;
11934
11935   if (sym->ns->is_block_data && !sym->attr.in_common)
11936     {
11937       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
11938                  sym->name, &sym->declared_at);
11939     }
11940
11941   if (e->ref == NULL && sym->as)
11942     {
11943       gfc_error ("DATA array '%s' at %L must be specified in a previous"
11944                  " declaration", sym->name, where);
11945       return FAILURE;
11946     }
11947
11948   has_pointer = sym->attr.pointer;
11949
11950   for (ref = e->ref; ref; ref = ref->next)
11951     {
11952       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
11953         has_pointer = 1;
11954
11955       if (ref->type == REF_ARRAY && ref->u.ar.codimen)
11956         {
11957           gfc_error ("DATA element '%s' at %L cannot have a coindex",
11958                      sym->name, where);
11959           return FAILURE;
11960         }
11961
11962       if (has_pointer
11963             && ref->type == REF_ARRAY
11964             && ref->u.ar.type != AR_FULL)
11965           {
11966             gfc_error ("DATA element '%s' at %L is a pointer and so must "
11967                         "be a full array", sym->name, where);
11968             return FAILURE;
11969           }
11970     }
11971
11972   if (e->rank == 0 || has_pointer)
11973     {
11974       mpz_init_set_ui (size, 1);
11975       ref = NULL;
11976     }
11977   else
11978     {
11979       ref = e->ref;
11980
11981       /* Find the array section reference.  */
11982       for (ref = e->ref; ref; ref = ref->next)
11983         {
11984           if (ref->type != REF_ARRAY)
11985             continue;
11986           if (ref->u.ar.type == AR_ELEMENT)
11987             continue;
11988           break;
11989         }
11990       gcc_assert (ref);
11991
11992       /* Set marks according to the reference pattern.  */
11993       switch (ref->u.ar.type)
11994         {
11995         case AR_FULL:
11996           mark = AR_FULL;
11997           break;
11998
11999         case AR_SECTION:
12000           ar = &ref->u.ar;
12001           /* Get the start position of array section.  */
12002           gfc_get_section_index (ar, section_index, &offset);
12003           mark = AR_SECTION;
12004           break;
12005
12006         default:
12007           gcc_unreachable ();
12008         }
12009
12010       if (gfc_array_size (e, &size) == FAILURE)
12011         {
12012           gfc_error ("Nonconstant array section at %L in DATA statement",
12013                      &e->where);
12014           mpz_clear (offset);
12015           return FAILURE;
12016         }
12017     }
12018
12019   t = SUCCESS;
12020
12021   while (mpz_cmp_ui (size, 0) > 0)
12022     {
12023       if (next_data_value () == FAILURE)
12024         {
12025           gfc_error ("DATA statement at %L has more variables than values",
12026                      where);
12027           t = FAILURE;
12028           break;
12029         }
12030
12031       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
12032       if (t == FAILURE)
12033         break;
12034
12035       /* If we have more than one element left in the repeat count,
12036          and we have more than one element left in the target variable,
12037          then create a range assignment.  */
12038       /* FIXME: Only done for full arrays for now, since array sections
12039          seem tricky.  */
12040       if (mark == AR_FULL && ref && ref->next == NULL
12041           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
12042         {
12043           mpz_t range;
12044
12045           if (mpz_cmp (size, values.left) >= 0)
12046             {
12047               mpz_init_set (range, values.left);
12048               mpz_sub (size, size, values.left);
12049               mpz_set_ui (values.left, 0);
12050             }
12051           else
12052             {
12053               mpz_init_set (range, size);
12054               mpz_sub (values.left, values.left, size);
12055               mpz_set_ui (size, 0);
12056             }
12057
12058           t = gfc_assign_data_value_range (var->expr, values.vnode->expr,
12059                                            offset, range);
12060
12061           mpz_add (offset, offset, range);
12062           mpz_clear (range);
12063
12064           if (t == FAILURE)
12065             break;
12066         }
12067
12068       /* Assign initial value to symbol.  */
12069       else
12070         {
12071           mpz_sub_ui (values.left, values.left, 1);
12072           mpz_sub_ui (size, size, 1);
12073
12074           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
12075           if (t == FAILURE)
12076             break;
12077
12078           if (mark == AR_FULL)
12079             mpz_add_ui (offset, offset, 1);
12080
12081           /* Modify the array section indexes and recalculate the offset
12082              for next element.  */
12083           else if (mark == AR_SECTION)
12084             gfc_advance_section (section_index, ar, &offset);
12085         }
12086     }
12087
12088   if (mark == AR_SECTION)
12089     {
12090       for (i = 0; i < ar->dimen; i++)
12091         mpz_clear (section_index[i]);
12092     }
12093
12094   mpz_clear (size);
12095   mpz_clear (offset);
12096
12097   return t;
12098 }
12099
12100
12101 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
12102
12103 /* Iterate over a list of elements in a DATA statement.  */
12104
12105 static gfc_try
12106 traverse_data_list (gfc_data_variable *var, locus *where)
12107 {
12108   mpz_t trip;
12109   iterator_stack frame;
12110   gfc_expr *e, *start, *end, *step;
12111   gfc_try retval = SUCCESS;
12112
12113   mpz_init (frame.value);
12114   mpz_init (trip);
12115
12116   start = gfc_copy_expr (var->iter.start);
12117   end = gfc_copy_expr (var->iter.end);
12118   step = gfc_copy_expr (var->iter.step);
12119
12120   if (gfc_simplify_expr (start, 1) == FAILURE
12121       || start->expr_type != EXPR_CONSTANT)
12122     {
12123       gfc_error ("start of implied-do loop at %L could not be "
12124                  "simplified to a constant value", &start->where);
12125       retval = FAILURE;
12126       goto cleanup;
12127     }
12128   if (gfc_simplify_expr (end, 1) == FAILURE
12129       || end->expr_type != EXPR_CONSTANT)
12130     {
12131       gfc_error ("end of implied-do loop at %L could not be "
12132                  "simplified to a constant value", &start->where);
12133       retval = FAILURE;
12134       goto cleanup;
12135     }
12136   if (gfc_simplify_expr (step, 1) == FAILURE
12137       || step->expr_type != EXPR_CONSTANT)
12138     {
12139       gfc_error ("step of implied-do loop at %L could not be "
12140                  "simplified to a constant value", &start->where);
12141       retval = FAILURE;
12142       goto cleanup;
12143     }
12144
12145   mpz_set (trip, end->value.integer);
12146   mpz_sub (trip, trip, start->value.integer);
12147   mpz_add (trip, trip, step->value.integer);
12148
12149   mpz_div (trip, trip, step->value.integer);
12150
12151   mpz_set (frame.value, start->value.integer);
12152
12153   frame.prev = iter_stack;
12154   frame.variable = var->iter.var->symtree;
12155   iter_stack = &frame;
12156
12157   while (mpz_cmp_ui (trip, 0) > 0)
12158     {
12159       if (traverse_data_var (var->list, where) == FAILURE)
12160         {
12161           retval = FAILURE;
12162           goto cleanup;
12163         }
12164
12165       e = gfc_copy_expr (var->expr);
12166       if (gfc_simplify_expr (e, 1) == FAILURE)
12167         {
12168           gfc_free_expr (e);
12169           retval = FAILURE;
12170           goto cleanup;
12171         }
12172
12173       mpz_add (frame.value, frame.value, step->value.integer);
12174
12175       mpz_sub_ui (trip, trip, 1);
12176     }
12177
12178 cleanup:
12179   mpz_clear (frame.value);
12180   mpz_clear (trip);
12181
12182   gfc_free_expr (start);
12183   gfc_free_expr (end);
12184   gfc_free_expr (step);
12185
12186   iter_stack = frame.prev;
12187   return retval;
12188 }
12189
12190
12191 /* Type resolve variables in the variable list of a DATA statement.  */
12192
12193 static gfc_try
12194 traverse_data_var (gfc_data_variable *var, locus *where)
12195 {
12196   gfc_try t;
12197
12198   for (; var; var = var->next)
12199     {
12200       if (var->expr == NULL)
12201         t = traverse_data_list (var, where);
12202       else
12203         t = check_data_variable (var, where);
12204
12205       if (t == FAILURE)
12206         return FAILURE;
12207     }
12208
12209   return SUCCESS;
12210 }
12211
12212
12213 /* Resolve the expressions and iterators associated with a data statement.
12214    This is separate from the assignment checking because data lists should
12215    only be resolved once.  */
12216
12217 static gfc_try
12218 resolve_data_variables (gfc_data_variable *d)
12219 {
12220   for (; d; d = d->next)
12221     {
12222       if (d->list == NULL)
12223         {
12224           if (gfc_resolve_expr (d->expr) == FAILURE)
12225             return FAILURE;
12226         }
12227       else
12228         {
12229           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
12230             return FAILURE;
12231
12232           if (resolve_data_variables (d->list) == FAILURE)
12233             return FAILURE;
12234         }
12235     }
12236
12237   return SUCCESS;
12238 }
12239
12240
12241 /* Resolve a single DATA statement.  We implement this by storing a pointer to
12242    the value list into static variables, and then recursively traversing the
12243    variables list, expanding iterators and such.  */
12244
12245 static void
12246 resolve_data (gfc_data *d)
12247 {
12248
12249   if (resolve_data_variables (d->var) == FAILURE)
12250     return;
12251
12252   values.vnode = d->value;
12253   if (d->value == NULL)
12254     mpz_set_ui (values.left, 0);
12255   else
12256     mpz_set (values.left, d->value->repeat);
12257
12258   if (traverse_data_var (d->var, &d->where) == FAILURE)
12259     return;
12260
12261   /* At this point, we better not have any values left.  */
12262
12263   if (next_data_value () == SUCCESS)
12264     gfc_error ("DATA statement at %L has more values than variables",
12265                &d->where);
12266 }
12267
12268
12269 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
12270    accessed by host or use association, is a dummy argument to a pure function,
12271    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
12272    is storage associated with any such variable, shall not be used in the
12273    following contexts: (clients of this function).  */
12274
12275 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
12276    procedure.  Returns zero if assignment is OK, nonzero if there is a
12277    problem.  */
12278 int
12279 gfc_impure_variable (gfc_symbol *sym)
12280 {
12281   gfc_symbol *proc;
12282   gfc_namespace *ns;
12283
12284   if (sym->attr.use_assoc || sym->attr.in_common)
12285     return 1;
12286
12287   /* Check if the symbol's ns is inside the pure procedure.  */
12288   for (ns = gfc_current_ns; ns; ns = ns->parent)
12289     {
12290       if (ns == sym->ns)
12291         break;
12292       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
12293         return 1;
12294     }
12295
12296   proc = sym->ns->proc_name;
12297   if (sym->attr.dummy && gfc_pure (proc)
12298         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
12299                 ||
12300              proc->attr.function))
12301     return 1;
12302
12303   /* TODO: Sort out what can be storage associated, if anything, and include
12304      it here.  In principle equivalences should be scanned but it does not
12305      seem to be possible to storage associate an impure variable this way.  */
12306   return 0;
12307 }
12308
12309
12310 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
12311    current namespace is inside a pure procedure.  */
12312
12313 int
12314 gfc_pure (gfc_symbol *sym)
12315 {
12316   symbol_attribute attr;
12317   gfc_namespace *ns;
12318
12319   if (sym == NULL)
12320     {
12321       /* Check if the current namespace or one of its parents
12322         belongs to a pure procedure.  */
12323       for (ns = gfc_current_ns; ns; ns = ns->parent)
12324         {
12325           sym = ns->proc_name;
12326           if (sym == NULL)
12327             return 0;
12328           attr = sym->attr;
12329           if (attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental))
12330             return 1;
12331         }
12332       return 0;
12333     }
12334
12335   attr = sym->attr;
12336
12337   return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
12338 }
12339
12340
12341 /* Test whether the current procedure is elemental or not.  */
12342
12343 int
12344 gfc_elemental (gfc_symbol *sym)
12345 {
12346   symbol_attribute attr;
12347
12348   if (sym == NULL)
12349     sym = gfc_current_ns->proc_name;
12350   if (sym == NULL)
12351     return 0;
12352   attr = sym->attr;
12353
12354   return attr.flavor == FL_PROCEDURE && attr.elemental;
12355 }
12356
12357
12358 /* Warn about unused labels.  */
12359
12360 static void
12361 warn_unused_fortran_label (gfc_st_label *label)
12362 {
12363   if (label == NULL)
12364     return;
12365
12366   warn_unused_fortran_label (label->left);
12367
12368   if (label->defined == ST_LABEL_UNKNOWN)
12369     return;
12370
12371   switch (label->referenced)
12372     {
12373     case ST_LABEL_UNKNOWN:
12374       gfc_warning ("Label %d at %L defined but not used", label->value,
12375                    &label->where);
12376       break;
12377
12378     case ST_LABEL_BAD_TARGET:
12379       gfc_warning ("Label %d at %L defined but cannot be used",
12380                    label->value, &label->where);
12381       break;
12382
12383     default:
12384       break;
12385     }
12386
12387   warn_unused_fortran_label (label->right);
12388 }
12389
12390
12391 /* Returns the sequence type of a symbol or sequence.  */
12392
12393 static seq_type
12394 sequence_type (gfc_typespec ts)
12395 {
12396   seq_type result;
12397   gfc_component *c;
12398
12399   switch (ts.type)
12400   {
12401     case BT_DERIVED:
12402
12403       if (ts.u.derived->components == NULL)
12404         return SEQ_NONDEFAULT;
12405
12406       result = sequence_type (ts.u.derived->components->ts);
12407       for (c = ts.u.derived->components->next; c; c = c->next)
12408         if (sequence_type (c->ts) != result)
12409           return SEQ_MIXED;
12410
12411       return result;
12412
12413     case BT_CHARACTER:
12414       if (ts.kind != gfc_default_character_kind)
12415           return SEQ_NONDEFAULT;
12416
12417       return SEQ_CHARACTER;
12418
12419     case BT_INTEGER:
12420       if (ts.kind != gfc_default_integer_kind)
12421           return SEQ_NONDEFAULT;
12422
12423       return SEQ_NUMERIC;
12424
12425     case BT_REAL:
12426       if (!(ts.kind == gfc_default_real_kind
12427             || ts.kind == gfc_default_double_kind))
12428           return SEQ_NONDEFAULT;
12429
12430       return SEQ_NUMERIC;
12431
12432     case BT_COMPLEX:
12433       if (ts.kind != gfc_default_complex_kind)
12434           return SEQ_NONDEFAULT;
12435
12436       return SEQ_NUMERIC;
12437
12438     case BT_LOGICAL:
12439       if (ts.kind != gfc_default_logical_kind)
12440           return SEQ_NONDEFAULT;
12441
12442       return SEQ_NUMERIC;
12443
12444     default:
12445       return SEQ_NONDEFAULT;
12446   }
12447 }
12448
12449
12450 /* Resolve derived type EQUIVALENCE object.  */
12451
12452 static gfc_try
12453 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
12454 {
12455   gfc_component *c = derived->components;
12456
12457   if (!derived)
12458     return SUCCESS;
12459
12460   /* Shall not be an object of nonsequence derived type.  */
12461   if (!derived->attr.sequence)
12462     {
12463       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
12464                  "attribute to be an EQUIVALENCE object", sym->name,
12465                  &e->where);
12466       return FAILURE;
12467     }
12468
12469   /* Shall not have allocatable components.  */
12470   if (derived->attr.alloc_comp)
12471     {
12472       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
12473                  "components to be an EQUIVALENCE object",sym->name,
12474                  &e->where);
12475       return FAILURE;
12476     }
12477
12478   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
12479     {
12480       gfc_error ("Derived type variable '%s' at %L with default "
12481                  "initialization cannot be in EQUIVALENCE with a variable "
12482                  "in COMMON", sym->name, &e->where);
12483       return FAILURE;
12484     }
12485
12486   for (; c ; c = c->next)
12487     {
12488       if (c->ts.type == BT_DERIVED
12489           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
12490         return FAILURE;
12491
12492       /* Shall not be an object of sequence derived type containing a pointer
12493          in the structure.  */
12494       if (c->attr.pointer)
12495         {
12496           gfc_error ("Derived type variable '%s' at %L with pointer "
12497                      "component(s) cannot be an EQUIVALENCE object",
12498                      sym->name, &e->where);
12499           return FAILURE;
12500         }
12501     }
12502   return SUCCESS;
12503 }
12504
12505
12506 /* Resolve equivalence object. 
12507    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
12508    an allocatable array, an object of nonsequence derived type, an object of
12509    sequence derived type containing a pointer at any level of component
12510    selection, an automatic object, a function name, an entry name, a result
12511    name, a named constant, a structure component, or a subobject of any of
12512    the preceding objects.  A substring shall not have length zero.  A
12513    derived type shall not have components with default initialization nor
12514    shall two objects of an equivalence group be initialized.
12515    Either all or none of the objects shall have an protected attribute.
12516    The simple constraints are done in symbol.c(check_conflict) and the rest
12517    are implemented here.  */
12518
12519 static void
12520 resolve_equivalence (gfc_equiv *eq)
12521 {
12522   gfc_symbol *sym;
12523   gfc_symbol *first_sym;
12524   gfc_expr *e;
12525   gfc_ref *r;
12526   locus *last_where = NULL;
12527   seq_type eq_type, last_eq_type;
12528   gfc_typespec *last_ts;
12529   int object, cnt_protected;
12530   const char *msg;
12531
12532   last_ts = &eq->expr->symtree->n.sym->ts;
12533
12534   first_sym = eq->expr->symtree->n.sym;
12535
12536   cnt_protected = 0;
12537
12538   for (object = 1; eq; eq = eq->eq, object++)
12539     {
12540       e = eq->expr;
12541
12542       e->ts = e->symtree->n.sym->ts;
12543       /* match_varspec might not know yet if it is seeing
12544          array reference or substring reference, as it doesn't
12545          know the types.  */
12546       if (e->ref && e->ref->type == REF_ARRAY)
12547         {
12548           gfc_ref *ref = e->ref;
12549           sym = e->symtree->n.sym;
12550
12551           if (sym->attr.dimension)
12552             {
12553               ref->u.ar.as = sym->as;
12554               ref = ref->next;
12555             }
12556
12557           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
12558           if (e->ts.type == BT_CHARACTER
12559               && ref
12560               && ref->type == REF_ARRAY
12561               && ref->u.ar.dimen == 1
12562               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
12563               && ref->u.ar.stride[0] == NULL)
12564             {
12565               gfc_expr *start = ref->u.ar.start[0];
12566               gfc_expr *end = ref->u.ar.end[0];
12567               void *mem = NULL;
12568
12569               /* Optimize away the (:) reference.  */
12570               if (start == NULL && end == NULL)
12571                 {
12572                   if (e->ref == ref)
12573                     e->ref = ref->next;
12574                   else
12575                     e->ref->next = ref->next;
12576                   mem = ref;
12577                 }
12578               else
12579                 {
12580                   ref->type = REF_SUBSTRING;
12581                   if (start == NULL)
12582                     start = gfc_get_int_expr (gfc_default_integer_kind,
12583                                               NULL, 1);
12584                   ref->u.ss.start = start;
12585                   if (end == NULL && e->ts.u.cl)
12586                     end = gfc_copy_expr (e->ts.u.cl->length);
12587                   ref->u.ss.end = end;
12588                   ref->u.ss.length = e->ts.u.cl;
12589                   e->ts.u.cl = NULL;
12590                 }
12591               ref = ref->next;
12592               gfc_free (mem);
12593             }
12594
12595           /* Any further ref is an error.  */
12596           if (ref)
12597             {
12598               gcc_assert (ref->type == REF_ARRAY);
12599               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
12600                          &ref->u.ar.where);
12601               continue;
12602             }
12603         }
12604
12605       if (gfc_resolve_expr (e) == FAILURE)
12606         continue;
12607
12608       sym = e->symtree->n.sym;
12609
12610       if (sym->attr.is_protected)
12611         cnt_protected++;
12612       if (cnt_protected > 0 && cnt_protected != object)
12613         {
12614               gfc_error ("Either all or none of the objects in the "
12615                          "EQUIVALENCE set at %L shall have the "
12616                          "PROTECTED attribute",
12617                          &e->where);
12618               break;
12619         }
12620
12621       /* Shall not equivalence common block variables in a PURE procedure.  */
12622       if (sym->ns->proc_name
12623           && sym->ns->proc_name->attr.pure
12624           && sym->attr.in_common)
12625         {
12626           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
12627                      "object in the pure procedure '%s'",
12628                      sym->name, &e->where, sym->ns->proc_name->name);
12629           break;
12630         }
12631
12632       /* Shall not be a named constant.  */
12633       if (e->expr_type == EXPR_CONSTANT)
12634         {
12635           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
12636                      "object", sym->name, &e->where);
12637           continue;
12638         }
12639
12640       if (e->ts.type == BT_DERIVED
12641           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
12642         continue;
12643
12644       /* Check that the types correspond correctly:
12645          Note 5.28:
12646          A numeric sequence structure may be equivalenced to another sequence
12647          structure, an object of default integer type, default real type, double
12648          precision real type, default logical type such that components of the
12649          structure ultimately only become associated to objects of the same
12650          kind. A character sequence structure may be equivalenced to an object
12651          of default character kind or another character sequence structure.
12652          Other objects may be equivalenced only to objects of the same type and
12653          kind parameters.  */
12654
12655       /* Identical types are unconditionally OK.  */
12656       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
12657         goto identical_types;
12658
12659       last_eq_type = sequence_type (*last_ts);
12660       eq_type = sequence_type (sym->ts);
12661
12662       /* Since the pair of objects is not of the same type, mixed or
12663          non-default sequences can be rejected.  */
12664
12665       msg = "Sequence %s with mixed components in EQUIVALENCE "
12666             "statement at %L with different type objects";
12667       if ((object ==2
12668            && last_eq_type == SEQ_MIXED
12669            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
12670               == FAILURE)
12671           || (eq_type == SEQ_MIXED
12672               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12673                                  &e->where) == FAILURE))
12674         continue;
12675
12676       msg = "Non-default type object or sequence %s in EQUIVALENCE "
12677             "statement at %L with objects of different type";
12678       if ((object ==2
12679            && last_eq_type == SEQ_NONDEFAULT
12680            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
12681                               last_where) == FAILURE)
12682           || (eq_type == SEQ_NONDEFAULT
12683               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12684                                  &e->where) == FAILURE))
12685         continue;
12686
12687       msg ="Non-CHARACTER object '%s' in default CHARACTER "
12688            "EQUIVALENCE statement at %L";
12689       if (last_eq_type == SEQ_CHARACTER
12690           && eq_type != SEQ_CHARACTER
12691           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12692                              &e->where) == FAILURE)
12693                 continue;
12694
12695       msg ="Non-NUMERIC object '%s' in default NUMERIC "
12696            "EQUIVALENCE statement at %L";
12697       if (last_eq_type == SEQ_NUMERIC
12698           && eq_type != SEQ_NUMERIC
12699           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12700                              &e->where) == FAILURE)
12701                 continue;
12702
12703   identical_types:
12704       last_ts =&sym->ts;
12705       last_where = &e->where;
12706
12707       if (!e->ref)
12708         continue;
12709
12710       /* Shall not be an automatic array.  */
12711       if (e->ref->type == REF_ARRAY
12712           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
12713         {
12714           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
12715                      "an EQUIVALENCE object", sym->name, &e->where);
12716           continue;
12717         }
12718
12719       r = e->ref;
12720       while (r)
12721         {
12722           /* Shall not be a structure component.  */
12723           if (r->type == REF_COMPONENT)
12724             {
12725               gfc_error ("Structure component '%s' at %L cannot be an "
12726                          "EQUIVALENCE object",
12727                          r->u.c.component->name, &e->where);
12728               break;
12729             }
12730
12731           /* A substring shall not have length zero.  */
12732           if (r->type == REF_SUBSTRING)
12733             {
12734               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
12735                 {
12736                   gfc_error ("Substring at %L has length zero",
12737                              &r->u.ss.start->where);
12738                   break;
12739                 }
12740             }
12741           r = r->next;
12742         }
12743     }
12744 }
12745
12746
12747 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
12748
12749 static void
12750 resolve_fntype (gfc_namespace *ns)
12751 {
12752   gfc_entry_list *el;
12753   gfc_symbol *sym;
12754
12755   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
12756     return;
12757
12758   /* If there are any entries, ns->proc_name is the entry master
12759      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
12760   if (ns->entries)
12761     sym = ns->entries->sym;
12762   else
12763     sym = ns->proc_name;
12764   if (sym->result == sym
12765       && sym->ts.type == BT_UNKNOWN
12766       && gfc_set_default_type (sym, 0, NULL) == FAILURE
12767       && !sym->attr.untyped)
12768     {
12769       gfc_error ("Function '%s' at %L has no IMPLICIT type",
12770                  sym->name, &sym->declared_at);
12771       sym->attr.untyped = 1;
12772     }
12773
12774   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
12775       && !sym->attr.contained
12776       && !gfc_check_access (sym->ts.u.derived->attr.access,
12777                             sym->ts.u.derived->ns->default_access)
12778       && gfc_check_access (sym->attr.access, sym->ns->default_access))
12779     {
12780       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
12781                       "%L of PRIVATE type '%s'", sym->name,
12782                       &sym->declared_at, sym->ts.u.derived->name);
12783     }
12784
12785     if (ns->entries)
12786     for (el = ns->entries->next; el; el = el->next)
12787       {
12788         if (el->sym->result == el->sym
12789             && el->sym->ts.type == BT_UNKNOWN
12790             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
12791             && !el->sym->attr.untyped)
12792           {
12793             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
12794                        el->sym->name, &el->sym->declared_at);
12795             el->sym->attr.untyped = 1;
12796           }
12797       }
12798 }
12799
12800
12801 /* 12.3.2.1.1 Defined operators.  */
12802
12803 static gfc_try
12804 check_uop_procedure (gfc_symbol *sym, locus where)
12805 {
12806   gfc_formal_arglist *formal;
12807
12808   if (!sym->attr.function)
12809     {
12810       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
12811                  sym->name, &where);
12812       return FAILURE;
12813     }
12814
12815   if (sym->ts.type == BT_CHARACTER
12816       && !(sym->ts.u.cl && sym->ts.u.cl->length)
12817       && !(sym->result && sym->result->ts.u.cl
12818            && sym->result->ts.u.cl->length))
12819     {
12820       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
12821                  "character length", sym->name, &where);
12822       return FAILURE;
12823     }
12824
12825   formal = sym->formal;
12826   if (!formal || !formal->sym)
12827     {
12828       gfc_error ("User operator procedure '%s' at %L must have at least "
12829                  "one argument", sym->name, &where);
12830       return FAILURE;
12831     }
12832
12833   if (formal->sym->attr.intent != INTENT_IN)
12834     {
12835       gfc_error ("First argument of operator interface at %L must be "
12836                  "INTENT(IN)", &where);
12837       return FAILURE;
12838     }
12839
12840   if (formal->sym->attr.optional)
12841     {
12842       gfc_error ("First argument of operator interface at %L cannot be "
12843                  "optional", &where);
12844       return FAILURE;
12845     }
12846
12847   formal = formal->next;
12848   if (!formal || !formal->sym)
12849     return SUCCESS;
12850
12851   if (formal->sym->attr.intent != INTENT_IN)
12852     {
12853       gfc_error ("Second argument of operator interface at %L must be "
12854                  "INTENT(IN)", &where);
12855       return FAILURE;
12856     }
12857
12858   if (formal->sym->attr.optional)
12859     {
12860       gfc_error ("Second argument of operator interface at %L cannot be "
12861                  "optional", &where);
12862       return FAILURE;
12863     }
12864
12865   if (formal->next)
12866     {
12867       gfc_error ("Operator interface at %L must have, at most, two "
12868                  "arguments", &where);
12869       return FAILURE;
12870     }
12871
12872   return SUCCESS;
12873 }
12874
12875 static void
12876 gfc_resolve_uops (gfc_symtree *symtree)
12877 {
12878   gfc_interface *itr;
12879
12880   if (symtree == NULL)
12881     return;
12882
12883   gfc_resolve_uops (symtree->left);
12884   gfc_resolve_uops (symtree->right);
12885
12886   for (itr = symtree->n.uop->op; itr; itr = itr->next)
12887     check_uop_procedure (itr->sym, itr->sym->declared_at);
12888 }
12889
12890
12891 /* Examine all of the expressions associated with a program unit,
12892    assign types to all intermediate expressions, make sure that all
12893    assignments are to compatible types and figure out which names
12894    refer to which functions or subroutines.  It doesn't check code
12895    block, which is handled by resolve_code.  */
12896
12897 static void
12898 resolve_types (gfc_namespace *ns)
12899 {
12900   gfc_namespace *n;
12901   gfc_charlen *cl;
12902   gfc_data *d;
12903   gfc_equiv *eq;
12904   gfc_namespace* old_ns = gfc_current_ns;
12905
12906   /* Check that all IMPLICIT types are ok.  */
12907   if (!ns->seen_implicit_none)
12908     {
12909       unsigned letter;
12910       for (letter = 0; letter != GFC_LETTERS; ++letter)
12911         if (ns->set_flag[letter]
12912             && resolve_typespec_used (&ns->default_type[letter],
12913                                       &ns->implicit_loc[letter],
12914                                       NULL) == FAILURE)
12915           return;
12916     }
12917
12918   gfc_current_ns = ns;
12919
12920   resolve_entries (ns);
12921
12922   resolve_common_vars (ns->blank_common.head, false);
12923   resolve_common_blocks (ns->common_root);
12924
12925   resolve_contained_functions (ns);
12926
12927   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
12928
12929   for (cl = ns->cl_list; cl; cl = cl->next)
12930     resolve_charlen (cl);
12931
12932   gfc_traverse_ns (ns, resolve_symbol);
12933
12934   resolve_fntype (ns);
12935
12936   for (n = ns->contained; n; n = n->sibling)
12937     {
12938       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
12939         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
12940                    "also be PURE", n->proc_name->name,
12941                    &n->proc_name->declared_at);
12942
12943       resolve_types (n);
12944     }
12945
12946   forall_flag = 0;
12947   gfc_check_interfaces (ns);
12948
12949   gfc_traverse_ns (ns, resolve_values);
12950
12951   if (ns->save_all)
12952     gfc_save_all (ns);
12953
12954   iter_stack = NULL;
12955   for (d = ns->data; d; d = d->next)
12956     resolve_data (d);
12957
12958   iter_stack = NULL;
12959   gfc_traverse_ns (ns, gfc_formalize_init_value);
12960
12961   gfc_traverse_ns (ns, gfc_verify_binding_labels);
12962
12963   if (ns->common_root != NULL)
12964     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
12965
12966   for (eq = ns->equiv; eq; eq = eq->next)
12967     resolve_equivalence (eq);
12968
12969   /* Warn about unused labels.  */
12970   if (warn_unused_label)
12971     warn_unused_fortran_label (ns->st_labels);
12972
12973   gfc_resolve_uops (ns->uop_root);
12974
12975   gfc_current_ns = old_ns;
12976 }
12977
12978
12979 /* Call resolve_code recursively.  */
12980
12981 static void
12982 resolve_codes (gfc_namespace *ns)
12983 {
12984   gfc_namespace *n;
12985   bitmap_obstack old_obstack;
12986
12987   for (n = ns->contained; n; n = n->sibling)
12988     resolve_codes (n);
12989
12990   gfc_current_ns = ns;
12991
12992   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
12993   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
12994     cs_base = NULL;
12995
12996   /* Set to an out of range value.  */
12997   current_entry_id = -1;
12998
12999   old_obstack = labels_obstack;
13000   bitmap_obstack_initialize (&labels_obstack);
13001
13002   resolve_code (ns->code, ns);
13003
13004   bitmap_obstack_release (&labels_obstack);
13005   labels_obstack = old_obstack;
13006 }
13007
13008
13009 /* This function is called after a complete program unit has been compiled.
13010    Its purpose is to examine all of the expressions associated with a program
13011    unit, assign types to all intermediate expressions, make sure that all
13012    assignments are to compatible types and figure out which names refer to
13013    which functions or subroutines.  */
13014
13015 void
13016 gfc_resolve (gfc_namespace *ns)
13017 {
13018   gfc_namespace *old_ns;
13019   code_stack *old_cs_base;
13020
13021   if (ns->resolved)
13022     return;
13023
13024   ns->resolved = -1;
13025   old_ns = gfc_current_ns;
13026   old_cs_base = cs_base;
13027
13028   resolve_types (ns);
13029   resolve_codes (ns);
13030
13031   gfc_current_ns = old_ns;
13032   cs_base = old_cs_base;
13033   ns->resolved = 1;
13034 }