OSDN Git Service

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