OSDN Git Service

2010-06-09 Janus Weil <janus@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010
3    Free Software Foundation, Inc.
4    Contributed by Andy Vaught
5
6 This file is part of GCC.
7
8 GCC is free software; you can redistribute it and/or modify it under
9 the terms of the GNU General Public License as published by the Free
10 Software Foundation; either version 3, or (at your option) any later
11 version.
12
13 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
14 WARRANTY; without even the implied warranty of MERCHANTABILITY or
15 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
16 for more details.
17
18 You should have received a copy of the GNU General Public License
19 along with GCC; see the file COPYING3.  If not see
20 <http://www.gnu.org/licenses/>.  */
21
22 #include "config.h"
23 #include "system.h"
24 #include "flags.h"
25 #include "gfortran.h"
26 #include "obstack.h"
27 #include "bitmap.h"
28 #include "arith.h"  /* For gfc_compare_expr().  */
29 #include "dependency.h"
30 #include "data.h"
31 #include "target-memory.h" /* for gfc_simplify_transfer */
32 #include "constructor.h"
33
34 /* Types used in equivalence statements.  */
35
36 typedef enum seq_type
37 {
38   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
39 }
40 seq_type;
41
42 /* Stack to keep track of the nesting of blocks as we move through the
43    code.  See resolve_branch() and resolve_code().  */
44
45 typedef struct code_stack
46 {
47   struct gfc_code *head, *current;
48   struct code_stack *prev;
49
50   /* This bitmap keeps track of the targets valid for a branch from
51      inside this block except for END {IF|SELECT}s of enclosing
52      blocks.  */
53   bitmap reachable_labels;
54 }
55 code_stack;
56
57 static code_stack *cs_base = NULL;
58
59
60 /* Nonzero if we're inside a FORALL block.  */
61
62 static int forall_flag;
63
64 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
65
66 static int omp_workshare_flag;
67
68 /* Nonzero if we are processing a formal arglist. The corresponding function
69    resets the flag each time that it is read.  */
70 static int formal_arg_flag = 0;
71
72 /* True if we are resolving a specification expression.  */
73 static int specification_expr = 0;
74
75 /* The id of the last entry seen.  */
76 static int current_entry_id;
77
78 /* We use bitmaps to determine if a branch target is valid.  */
79 static bitmap_obstack labels_obstack;
80
81 /* True when simplifying a EXPR_VARIABLE argument to an inquiry function.  */
82 static bool inquiry_argument = false;
83
84 int
85 gfc_is_formal_arg (void)
86 {
87   return formal_arg_flag;
88 }
89
90 /* Is the symbol host associated?  */
91 static bool
92 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
93 {
94   for (ns = ns->parent; ns; ns = ns->parent)
95     {      
96       if (sym->ns == ns)
97         return true;
98     }
99
100   return false;
101 }
102
103 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
104    an ABSTRACT derived-type.  If where is not NULL, an error message with that
105    locus is printed, optionally using name.  */
106
107 static gfc_try
108 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
109 {
110   if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
111     {
112       if (where)
113         {
114           if (name)
115             gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
116                        name, where, ts->u.derived->name);
117           else
118             gfc_error ("ABSTRACT type '%s' used at %L",
119                        ts->u.derived->name, where);
120         }
121
122       return FAILURE;
123     }
124
125   return SUCCESS;
126 }
127
128
129 /* Resolve types of formal argument lists.  These have to be done early so that
130    the formal argument lists of module procedures can be copied to the
131    containing module before the individual procedures are resolved
132    individually.  We also resolve argument lists of procedures in interface
133    blocks because they are self-contained scoping units.
134
135    Since a dummy argument cannot be a non-dummy procedure, the only
136    resort left for untyped names are the IMPLICIT types.  */
137
138 static void
139 resolve_formal_arglist (gfc_symbol *proc)
140 {
141   gfc_formal_arglist *f;
142   gfc_symbol *sym;
143   int i;
144
145   if (proc->result != NULL)
146     sym = proc->result;
147   else
148     sym = proc;
149
150   if (gfc_elemental (proc)
151       || sym->attr.pointer || sym->attr.allocatable
152       || (sym->as && sym->as->rank > 0))
153     {
154       proc->attr.always_explicit = 1;
155       sym->attr.always_explicit = 1;
156     }
157
158   formal_arg_flag = 1;
159
160   for (f = proc->formal; f; f = f->next)
161     {
162       sym = f->sym;
163
164       if (sym == NULL)
165         {
166           /* Alternate return placeholder.  */
167           if (gfc_elemental (proc))
168             gfc_error ("Alternate return specifier in elemental subroutine "
169                        "'%s' at %L is not allowed", proc->name,
170                        &proc->declared_at);
171           if (proc->attr.function)
172             gfc_error ("Alternate return specifier in function "
173                        "'%s' at %L is not allowed", proc->name,
174                        &proc->declared_at);
175           continue;
176         }
177
178       if (sym->attr.if_source != IFSRC_UNKNOWN)
179         resolve_formal_arglist (sym);
180
181       if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
182         {
183           if (gfc_pure (proc) && !gfc_pure (sym))
184             {
185               gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
186                          "also be PURE", sym->name, &sym->declared_at);
187               continue;
188             }
189
190           if (gfc_elemental (proc))
191             {
192               gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
193                          "procedure", &sym->declared_at);
194               continue;
195             }
196
197           if (sym->attr.function
198                 && sym->ts.type == BT_UNKNOWN
199                 && sym->attr.intrinsic)
200             {
201               gfc_intrinsic_sym *isym;
202               isym = gfc_find_function (sym->name);
203               if (isym == NULL || !isym->specific)
204                 {
205                   gfc_error ("Unable to find a specific INTRINSIC procedure "
206                              "for the reference '%s' at %L", sym->name,
207                              &sym->declared_at);
208                 }
209               sym->ts = isym->ts;
210             }
211
212           continue;
213         }
214
215       if (sym->ts.type == BT_UNKNOWN)
216         {
217           if (!sym->attr.function || sym->result == sym)
218             gfc_set_default_type (sym, 1, sym->ns);
219         }
220
221       gfc_resolve_array_spec (sym->as, 0);
222
223       /* We can't tell if an array with dimension (:) is assumed or deferred
224          shape until we know if it has the pointer or allocatable attributes.
225       */
226       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
227           && !(sym->attr.pointer || sym->attr.allocatable))
228         {
229           sym->as->type = AS_ASSUMED_SHAPE;
230           for (i = 0; i < sym->as->rank; i++)
231             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
232                                                   NULL, 1);
233         }
234
235       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
236           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
237           || sym->attr.optional)
238         {
239           proc->attr.always_explicit = 1;
240           if (proc->result)
241             proc->result->attr.always_explicit = 1;
242         }
243
244       /* If the flavor is unknown at this point, it has to be a variable.
245          A procedure specification would have already set the type.  */
246
247       if (sym->attr.flavor == FL_UNKNOWN)
248         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
249
250       if (gfc_pure (proc) && !sym->attr.pointer
251           && sym->attr.flavor != FL_PROCEDURE)
252         {
253           if (proc->attr.function && sym->attr.intent != INTENT_IN)
254             gfc_error ("Argument '%s' of pure function '%s' at %L must be "
255                        "INTENT(IN)", sym->name, proc->name,
256                        &sym->declared_at);
257
258           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
259             gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
260                        "have its INTENT specified", sym->name, proc->name,
261                        &sym->declared_at);
262         }
263
264       if (gfc_elemental (proc))
265         {
266           /* F2008, C1289.  */
267           if (sym->attr.codimension)
268             {
269               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
270                          "procedure", sym->name, &sym->declared_at);
271               continue;
272             }
273
274           if (sym->as != NULL)
275             {
276               gfc_error ("Argument '%s' of elemental procedure at %L must "
277                          "be scalar", sym->name, &sym->declared_at);
278               continue;
279             }
280
281           if (sym->attr.pointer)
282             {
283               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
284                          "have the POINTER attribute", sym->name,
285                          &sym->declared_at);
286               continue;
287             }
288
289           if (sym->attr.flavor == FL_PROCEDURE)
290             {
291               gfc_error ("Dummy procedure '%s' not allowed in elemental "
292                          "procedure '%s' at %L", sym->name, proc->name,
293                          &sym->declared_at);
294               continue;
295             }
296         }
297
298       /* Each dummy shall be specified to be scalar.  */
299       if (proc->attr.proc == PROC_ST_FUNCTION)
300         {
301           if (sym->as != NULL)
302             {
303               gfc_error ("Argument '%s' of statement function at %L must "
304                          "be scalar", sym->name, &sym->declared_at);
305               continue;
306             }
307
308           if (sym->ts.type == BT_CHARACTER)
309             {
310               gfc_charlen *cl = sym->ts.u.cl;
311               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
312                 {
313                   gfc_error ("Character-valued argument '%s' of statement "
314                              "function at %L must have constant length",
315                              sym->name, &sym->declared_at);
316                   continue;
317                 }
318             }
319         }
320     }
321   formal_arg_flag = 0;
322 }
323
324
325 /* Work function called when searching for symbols that have argument lists
326    associated with them.  */
327
328 static void
329 find_arglists (gfc_symbol *sym)
330 {
331   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
332     return;
333
334   resolve_formal_arglist (sym);
335 }
336
337
338 /* Given a namespace, resolve all formal argument lists within the namespace.
339  */
340
341 static void
342 resolve_formal_arglists (gfc_namespace *ns)
343 {
344   if (ns == NULL)
345     return;
346
347   gfc_traverse_ns (ns, find_arglists);
348 }
349
350
351 static void
352 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
353 {
354   gfc_try t;
355
356   /* If this namespace is not a function or an entry master function,
357      ignore it.  */
358   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
359       || sym->attr.entry_master)
360     return;
361
362   /* Try to find out of what the return type is.  */
363   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
364     {
365       t = gfc_set_default_type (sym->result, 0, ns);
366
367       if (t == FAILURE && !sym->result->attr.untyped)
368         {
369           if (sym->result == sym)
370             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
371                        sym->name, &sym->declared_at);
372           else if (!sym->result->attr.proc_pointer)
373             gfc_error ("Result '%s' of contained function '%s' at %L has "
374                        "no IMPLICIT type", sym->result->name, sym->name,
375                        &sym->result->declared_at);
376           sym->result->attr.untyped = 1;
377         }
378     }
379
380   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
381      type, lists the only ways a character length value of * can be used:
382      dummy arguments of procedures, named constants, and function results
383      in external functions.  Internal function results and results of module
384      procedures are not on this list, ergo, not permitted.  */
385
386   if (sym->result->ts.type == BT_CHARACTER)
387     {
388       gfc_charlen *cl = sym->result->ts.u.cl;
389       if (!cl || !cl->length)
390         {
391           /* See if this is a module-procedure and adapt error message
392              accordingly.  */
393           bool module_proc;
394           gcc_assert (ns->parent && ns->parent->proc_name);
395           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
396
397           gfc_error ("Character-valued %s '%s' at %L must not be"
398                      " assumed length",
399                      module_proc ? _("module procedure")
400                                  : _("internal function"),
401                      sym->name, &sym->declared_at);
402         }
403     }
404 }
405
406
407 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
408    introduce duplicates.  */
409
410 static void
411 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
412 {
413   gfc_formal_arglist *f, *new_arglist;
414   gfc_symbol *new_sym;
415
416   for (; new_args != NULL; new_args = new_args->next)
417     {
418       new_sym = new_args->sym;
419       /* See if this arg is already in the formal argument list.  */
420       for (f = proc->formal; f; f = f->next)
421         {
422           if (new_sym == f->sym)
423             break;
424         }
425
426       if (f)
427         continue;
428
429       /* Add a new argument.  Argument order is not important.  */
430       new_arglist = gfc_get_formal_arglist ();
431       new_arglist->sym = new_sym;
432       new_arglist->next = proc->formal;
433       proc->formal  = new_arglist;
434     }
435 }
436
437
438 /* Flag the arguments that are not present in all entries.  */
439
440 static void
441 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
442 {
443   gfc_formal_arglist *f, *head;
444   head = new_args;
445
446   for (f = proc->formal; f; f = f->next)
447     {
448       if (f->sym == NULL)
449         continue;
450
451       for (new_args = head; new_args; new_args = new_args->next)
452         {
453           if (new_args->sym == f->sym)
454             break;
455         }
456
457       if (new_args)
458         continue;
459
460       f->sym->attr.not_always_present = 1;
461     }
462 }
463
464
465 /* Resolve alternate entry points.  If a symbol has multiple entry points we
466    create a new master symbol for the main routine, and turn the existing
467    symbol into an entry point.  */
468
469 static void
470 resolve_entries (gfc_namespace *ns)
471 {
472   gfc_namespace *old_ns;
473   gfc_code *c;
474   gfc_symbol *proc;
475   gfc_entry_list *el;
476   char name[GFC_MAX_SYMBOL_LEN + 1];
477   static int master_count = 0;
478
479   if (ns->proc_name == NULL)
480     return;
481
482   /* No need to do anything if this procedure doesn't have alternate entry
483      points.  */
484   if (!ns->entries)
485     return;
486
487   /* We may already have resolved alternate entry points.  */
488   if (ns->proc_name->attr.entry_master)
489     return;
490
491   /* If this isn't a procedure something has gone horribly wrong.  */
492   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
493
494   /* Remember the current namespace.  */
495   old_ns = gfc_current_ns;
496
497   gfc_current_ns = ns;
498
499   /* Add the main entry point to the list of entry points.  */
500   el = gfc_get_entry_list ();
501   el->sym = ns->proc_name;
502   el->id = 0;
503   el->next = ns->entries;
504   ns->entries = el;
505   ns->proc_name->attr.entry = 1;
506
507   /* If it is a module function, it needs to be in the right namespace
508      so that gfc_get_fake_result_decl can gather up the results. The
509      need for this arose in get_proc_name, where these beasts were
510      left in their own namespace, to keep prior references linked to
511      the entry declaration.*/
512   if (ns->proc_name->attr.function
513       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
514     el->sym->ns = ns;
515
516   /* Do the same for entries where the master is not a module
517      procedure.  These are retained in the module namespace because
518      of the module procedure declaration.  */
519   for (el = el->next; el; el = el->next)
520     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
521           && el->sym->attr.mod_proc)
522       el->sym->ns = ns;
523   el = ns->entries;
524
525   /* Add an entry statement for it.  */
526   c = gfc_get_code ();
527   c->op = EXEC_ENTRY;
528   c->ext.entry = el;
529   c->next = ns->code;
530   ns->code = c;
531
532   /* Create a new symbol for the master function.  */
533   /* Give the internal function a unique name (within this file).
534      Also include the function name so the user has some hope of figuring
535      out what is going on.  */
536   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
537             master_count++, ns->proc_name->name);
538   gfc_get_ha_symbol (name, &proc);
539   gcc_assert (proc != NULL);
540
541   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
542   if (ns->proc_name->attr.subroutine)
543     gfc_add_subroutine (&proc->attr, proc->name, NULL);
544   else
545     {
546       gfc_symbol *sym;
547       gfc_typespec *ts, *fts;
548       gfc_array_spec *as, *fas;
549       gfc_add_function (&proc->attr, proc->name, NULL);
550       proc->result = proc;
551       fas = ns->entries->sym->as;
552       fas = fas ? fas : ns->entries->sym->result->as;
553       fts = &ns->entries->sym->result->ts;
554       if (fts->type == BT_UNKNOWN)
555         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
556       for (el = ns->entries->next; el; el = el->next)
557         {
558           ts = &el->sym->result->ts;
559           as = el->sym->as;
560           as = as ? as : el->sym->result->as;
561           if (ts->type == BT_UNKNOWN)
562             ts = gfc_get_default_type (el->sym->result->name, NULL);
563
564           if (! gfc_compare_types (ts, fts)
565               || (el->sym->result->attr.dimension
566                   != ns->entries->sym->result->attr.dimension)
567               || (el->sym->result->attr.pointer
568                   != ns->entries->sym->result->attr.pointer))
569             break;
570           else if (as && fas && ns->entries->sym->result != el->sym->result
571                       && gfc_compare_array_spec (as, fas) == 0)
572             gfc_error ("Function %s at %L has entries with mismatched "
573                        "array specifications", ns->entries->sym->name,
574                        &ns->entries->sym->declared_at);
575           /* The characteristics need to match and thus both need to have
576              the same string length, i.e. both len=*, or both len=4.
577              Having both len=<variable> is also possible, but difficult to
578              check at compile time.  */
579           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
580                    && (((ts->u.cl->length && !fts->u.cl->length)
581                         ||(!ts->u.cl->length && fts->u.cl->length))
582                        || (ts->u.cl->length
583                            && ts->u.cl->length->expr_type
584                               != fts->u.cl->length->expr_type)
585                        || (ts->u.cl->length
586                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
587                            && mpz_cmp (ts->u.cl->length->value.integer,
588                                        fts->u.cl->length->value.integer) != 0)))
589             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
590                             "entries returning variables of different "
591                             "string lengths", ns->entries->sym->name,
592                             &ns->entries->sym->declared_at);
593         }
594
595       if (el == NULL)
596         {
597           sym = ns->entries->sym->result;
598           /* All result types the same.  */
599           proc->ts = *fts;
600           if (sym->attr.dimension)
601             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
602           if (sym->attr.pointer)
603             gfc_add_pointer (&proc->attr, NULL);
604         }
605       else
606         {
607           /* Otherwise the result will be passed through a union by
608              reference.  */
609           proc->attr.mixed_entry_master = 1;
610           for (el = ns->entries; el; el = el->next)
611             {
612               sym = el->sym->result;
613               if (sym->attr.dimension)
614                 {
615                   if (el == ns->entries)
616                     gfc_error ("FUNCTION result %s can't be an array in "
617                                "FUNCTION %s at %L", sym->name,
618                                ns->entries->sym->name, &sym->declared_at);
619                   else
620                     gfc_error ("ENTRY result %s can't be an array in "
621                                "FUNCTION %s at %L", sym->name,
622                                ns->entries->sym->name, &sym->declared_at);
623                 }
624               else if (sym->attr.pointer)
625                 {
626                   if (el == ns->entries)
627                     gfc_error ("FUNCTION result %s can't be a POINTER in "
628                                "FUNCTION %s at %L", sym->name,
629                                ns->entries->sym->name, &sym->declared_at);
630                   else
631                     gfc_error ("ENTRY result %s can't be a POINTER in "
632                                "FUNCTION %s at %L", sym->name,
633                                ns->entries->sym->name, &sym->declared_at);
634                 }
635               else
636                 {
637                   ts = &sym->ts;
638                   if (ts->type == BT_UNKNOWN)
639                     ts = gfc_get_default_type (sym->name, NULL);
640                   switch (ts->type)
641                     {
642                     case BT_INTEGER:
643                       if (ts->kind == gfc_default_integer_kind)
644                         sym = NULL;
645                       break;
646                     case BT_REAL:
647                       if (ts->kind == gfc_default_real_kind
648                           || ts->kind == gfc_default_double_kind)
649                         sym = NULL;
650                       break;
651                     case BT_COMPLEX:
652                       if (ts->kind == gfc_default_complex_kind)
653                         sym = NULL;
654                       break;
655                     case BT_LOGICAL:
656                       if (ts->kind == gfc_default_logical_kind)
657                         sym = NULL;
658                       break;
659                     case BT_UNKNOWN:
660                       /* We will issue error elsewhere.  */
661                       sym = NULL;
662                       break;
663                     default:
664                       break;
665                     }
666                   if (sym)
667                     {
668                       if (el == ns->entries)
669                         gfc_error ("FUNCTION result %s can't be of type %s "
670                                    "in FUNCTION %s at %L", sym->name,
671                                    gfc_typename (ts), ns->entries->sym->name,
672                                    &sym->declared_at);
673                       else
674                         gfc_error ("ENTRY result %s can't be of type %s "
675                                    "in FUNCTION %s at %L", sym->name,
676                                    gfc_typename (ts), ns->entries->sym->name,
677                                    &sym->declared_at);
678                     }
679                 }
680             }
681         }
682     }
683   proc->attr.access = ACCESS_PRIVATE;
684   proc->attr.entry_master = 1;
685
686   /* Merge all the entry point arguments.  */
687   for (el = ns->entries; el; el = el->next)
688     merge_argument_lists (proc, el->sym->formal);
689
690   /* Check the master formal arguments for any that are not
691      present in all entry points.  */
692   for (el = ns->entries; el; el = el->next)
693     check_argument_lists (proc, el->sym->formal);
694
695   /* Use the master function for the function body.  */
696   ns->proc_name = proc;
697
698   /* Finalize the new symbols.  */
699   gfc_commit_symbols ();
700
701   /* Restore the original namespace.  */
702   gfc_current_ns = old_ns;
703 }
704
705
706 /* Resolve common variables.  */
707 static void
708 resolve_common_vars (gfc_symbol *sym, bool named_common)
709 {
710   gfc_symbol *csym = sym;
711
712   for (; csym; csym = csym->common_next)
713     {
714       if (csym->value || csym->attr.data)
715         {
716           if (!csym->ns->is_block_data)
717             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
718                             "but only in BLOCK DATA initialization is "
719                             "allowed", csym->name, &csym->declared_at);
720           else if (!named_common)
721             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
722                             "in a blank COMMON but initialization is only "
723                             "allowed in named common blocks", csym->name,
724                             &csym->declared_at);
725         }
726
727       if (csym->ts.type != BT_DERIVED)
728         continue;
729
730       if (!(csym->ts.u.derived->attr.sequence
731             || csym->ts.u.derived->attr.is_bind_c))
732         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
733                        "has neither the SEQUENCE nor the BIND(C) "
734                        "attribute", csym->name, &csym->declared_at);
735       if (csym->ts.u.derived->attr.alloc_comp)
736         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
737                        "has an ultimate component that is "
738                        "allocatable", csym->name, &csym->declared_at);
739       if (gfc_has_default_initializer (csym->ts.u.derived))
740         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
741                        "may not have default initializer", csym->name,
742                        &csym->declared_at);
743
744       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
745         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
746     }
747 }
748
749 /* Resolve common blocks.  */
750 static void
751 resolve_common_blocks (gfc_symtree *common_root)
752 {
753   gfc_symbol *sym;
754
755   if (common_root == NULL)
756     return;
757
758   if (common_root->left)
759     resolve_common_blocks (common_root->left);
760   if (common_root->right)
761     resolve_common_blocks (common_root->right);
762
763   resolve_common_vars (common_root->n.common->head, true);
764
765   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
766   if (sym == NULL)
767     return;
768
769   if (sym->attr.flavor == FL_PARAMETER)
770     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
771                sym->name, &common_root->n.common->where, &sym->declared_at);
772
773   if (sym->attr.intrinsic)
774     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
775                sym->name, &common_root->n.common->where);
776   else if (sym->attr.result
777            || gfc_is_function_return_value (sym, gfc_current_ns))
778     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
779                     "that is also a function result", sym->name,
780                     &common_root->n.common->where);
781   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
782            && sym->attr.proc != PROC_ST_FUNCTION)
783     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
784                     "that is also a global procedure", sym->name,
785                     &common_root->n.common->where);
786 }
787
788
789 /* Resolve contained function types.  Because contained functions can call one
790    another, they have to be worked out before any of the contained procedures
791    can be resolved.
792
793    The good news is that if a function doesn't already have a type, the only
794    way it can get one is through an IMPLICIT type or a RESULT variable, because
795    by definition contained functions are contained namespace they're contained
796    in, not in a sibling or parent namespace.  */
797
798 static void
799 resolve_contained_functions (gfc_namespace *ns)
800 {
801   gfc_namespace *child;
802   gfc_entry_list *el;
803
804   resolve_formal_arglists (ns);
805
806   for (child = ns->contained; child; child = child->sibling)
807     {
808       /* Resolve alternate entry points first.  */
809       resolve_entries (child);
810
811       /* Then check function return types.  */
812       resolve_contained_fntype (child->proc_name, child);
813       for (el = child->entries; el; el = el->next)
814         resolve_contained_fntype (el->sym, child);
815     }
816 }
817
818
819 /* Resolve all of the elements of a structure constructor and make sure that
820    the types are correct.  */
821
822 static gfc_try
823 resolve_structure_cons (gfc_expr *expr)
824 {
825   gfc_constructor *cons;
826   gfc_component *comp;
827   gfc_try t;
828   symbol_attribute a;
829
830   t = SUCCESS;
831   cons = gfc_constructor_first (expr->value.constructor);
832   /* A constructor may have references if it is the result of substituting a
833      parameter variable.  In this case we just pull out the component we
834      want.  */
835   if (expr->ref)
836     comp = expr->ref->u.c.sym->components;
837   else
838     comp = expr->ts.u.derived->components;
839
840   /* See if the user is trying to invoke a structure constructor for one of
841      the iso_c_binding derived types.  */
842   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
843       && expr->ts.u.derived->ts.is_iso_c && cons
844       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
845     {
846       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
847                  expr->ts.u.derived->name, &(expr->where));
848       return FAILURE;
849     }
850
851   /* Return if structure constructor is c_null_(fun)prt.  */
852   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
853       && expr->ts.u.derived->ts.is_iso_c && cons
854       && cons->expr && cons->expr->expr_type == EXPR_NULL)
855     return SUCCESS;
856
857   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
858     {
859       int rank;
860
861       if (!cons->expr)
862         continue;
863
864       if (gfc_resolve_expr (cons->expr) == FAILURE)
865         {
866           t = FAILURE;
867           continue;
868         }
869
870       rank = comp->as ? comp->as->rank : 0;
871       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
872           && (comp->attr.allocatable || cons->expr->rank))
873         {
874           gfc_error ("The rank of the element in the derived type "
875                      "constructor at %L does not match that of the "
876                      "component (%d/%d)", &cons->expr->where,
877                      cons->expr->rank, rank);
878           t = FAILURE;
879         }
880
881       /* If we don't have the right type, try to convert it.  */
882
883       if (!gfc_compare_types (&cons->expr->ts, &comp->ts))
884         {
885           t = FAILURE;
886           if (strcmp (comp->name, "$extends") == 0)
887             {
888               /* Can afford to be brutal with the $extends initializer.
889                  The derived type can get lost because it is PRIVATE
890                  but it is not usage constrained by the standard.  */
891               cons->expr->ts = comp->ts;
892               t = SUCCESS;
893             }
894           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
895             gfc_error ("The element in the derived type constructor at %L, "
896                        "for pointer component '%s', is %s but should be %s",
897                        &cons->expr->where, comp->name,
898                        gfc_basic_typename (cons->expr->ts.type),
899                        gfc_basic_typename (comp->ts.type));
900           else
901             t = gfc_convert_type (cons->expr, &comp->ts, 1);
902         }
903
904       if (cons->expr->expr_type == EXPR_NULL
905           && !(comp->attr.pointer || comp->attr.allocatable
906                || comp->attr.proc_pointer
907                || (comp->ts.type == BT_CLASS
908                    && (CLASS_DATA (comp)->attr.pointer
909                        || CLASS_DATA (comp)->attr.allocatable))))
910         {
911           t = FAILURE;
912           gfc_error ("The NULL in the derived type constructor at %L is "
913                      "being applied to component '%s', which is neither "
914                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
915                      comp->name);
916         }
917
918       if (!comp->attr.pointer || cons->expr->expr_type == EXPR_NULL)
919         continue;
920
921       a = gfc_expr_attr (cons->expr);
922
923       if (!a.pointer && !a.target)
924         {
925           t = FAILURE;
926           gfc_error ("The element in the derived type constructor at %L, "
927                      "for pointer component '%s' should be a POINTER or "
928                      "a TARGET", &cons->expr->where, comp->name);
929         }
930
931       /* F2003, C1272 (3).  */
932       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
933           && (gfc_impure_variable (cons->expr->symtree->n.sym)
934               || gfc_is_coindexed (cons->expr)))
935         {
936           t = FAILURE;
937           gfc_error ("Invalid expression in the derived type constructor for "
938                      "pointer component '%s' at %L in PURE procedure",
939                      comp->name, &cons->expr->where);
940         }
941     }
942
943   return t;
944 }
945
946
947 /****************** Expression name resolution ******************/
948
949 /* Returns 0 if a symbol was not declared with a type or
950    attribute declaration statement, nonzero otherwise.  */
951
952 static int
953 was_declared (gfc_symbol *sym)
954 {
955   symbol_attribute a;
956
957   a = sym->attr;
958
959   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
960     return 1;
961
962   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
963       || a.optional || a.pointer || a.save || a.target || a.volatile_
964       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
965       || a.asynchronous || a.codimension)
966     return 1;
967
968   return 0;
969 }
970
971
972 /* Determine if a symbol is generic or not.  */
973
974 static int
975 generic_sym (gfc_symbol *sym)
976 {
977   gfc_symbol *s;
978
979   if (sym->attr.generic ||
980       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
981     return 1;
982
983   if (was_declared (sym) || sym->ns->parent == NULL)
984     return 0;
985
986   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
987   
988   if (s != NULL)
989     {
990       if (s == sym)
991         return 0;
992       else
993         return generic_sym (s);
994     }
995
996   return 0;
997 }
998
999
1000 /* Determine if a symbol is specific or not.  */
1001
1002 static int
1003 specific_sym (gfc_symbol *sym)
1004 {
1005   gfc_symbol *s;
1006
1007   if (sym->attr.if_source == IFSRC_IFBODY
1008       || sym->attr.proc == PROC_MODULE
1009       || sym->attr.proc == PROC_INTERNAL
1010       || sym->attr.proc == PROC_ST_FUNCTION
1011       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1012       || sym->attr.external)
1013     return 1;
1014
1015   if (was_declared (sym) || sym->ns->parent == NULL)
1016     return 0;
1017
1018   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1019
1020   return (s == NULL) ? 0 : specific_sym (s);
1021 }
1022
1023
1024 /* Figure out if the procedure is specific, generic or unknown.  */
1025
1026 typedef enum
1027 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1028 proc_type;
1029
1030 static proc_type
1031 procedure_kind (gfc_symbol *sym)
1032 {
1033   if (generic_sym (sym))
1034     return PTYPE_GENERIC;
1035
1036   if (specific_sym (sym))
1037     return PTYPE_SPECIFIC;
1038
1039   return PTYPE_UNKNOWN;
1040 }
1041
1042 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1043    is nonzero when matching actual arguments.  */
1044
1045 static int need_full_assumed_size = 0;
1046
1047 static bool
1048 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1049 {
1050   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1051       return false;
1052
1053   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1054      What should it be?  */
1055   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1056           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1057                && (e->ref->u.ar.type == AR_FULL))
1058     {
1059       gfc_error ("The upper bound in the last dimension must "
1060                  "appear in the reference to the assumed size "
1061                  "array '%s' at %L", sym->name, &e->where);
1062       return true;
1063     }
1064   return false;
1065 }
1066
1067
1068 /* Look for bad assumed size array references in argument expressions
1069   of elemental and array valued intrinsic procedures.  Since this is
1070   called from procedure resolution functions, it only recurses at
1071   operators.  */
1072
1073 static bool
1074 resolve_assumed_size_actual (gfc_expr *e)
1075 {
1076   if (e == NULL)
1077    return false;
1078
1079   switch (e->expr_type)
1080     {
1081     case EXPR_VARIABLE:
1082       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1083         return true;
1084       break;
1085
1086     case EXPR_OP:
1087       if (resolve_assumed_size_actual (e->value.op.op1)
1088           || resolve_assumed_size_actual (e->value.op.op2))
1089         return true;
1090       break;
1091
1092     default:
1093       break;
1094     }
1095   return false;
1096 }
1097
1098
1099 /* Check a generic procedure, passed as an actual argument, to see if
1100    there is a matching specific name.  If none, it is an error, and if
1101    more than one, the reference is ambiguous.  */
1102 static int
1103 count_specific_procs (gfc_expr *e)
1104 {
1105   int n;
1106   gfc_interface *p;
1107   gfc_symbol *sym;
1108         
1109   n = 0;
1110   sym = e->symtree->n.sym;
1111
1112   for (p = sym->generic; p; p = p->next)
1113     if (strcmp (sym->name, p->sym->name) == 0)
1114       {
1115         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1116                                        sym->name);
1117         n++;
1118       }
1119
1120   if (n > 1)
1121     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1122                &e->where);
1123
1124   if (n == 0)
1125     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1126                "argument at %L", sym->name, &e->where);
1127
1128   return n;
1129 }
1130
1131
1132 /* See if a call to sym could possibly be a not allowed RECURSION because of
1133    a missing RECURIVE declaration.  This means that either sym is the current
1134    context itself, or sym is the parent of a contained procedure calling its
1135    non-RECURSIVE containing procedure.
1136    This also works if sym is an ENTRY.  */
1137
1138 static bool
1139 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1140 {
1141   gfc_symbol* proc_sym;
1142   gfc_symbol* context_proc;
1143   gfc_namespace* real_context;
1144
1145   if (sym->attr.flavor == FL_PROGRAM)
1146     return false;
1147
1148   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1149
1150   /* If we've got an ENTRY, find real procedure.  */
1151   if (sym->attr.entry && sym->ns->entries)
1152     proc_sym = sym->ns->entries->sym;
1153   else
1154     proc_sym = sym;
1155
1156   /* If sym is RECURSIVE, all is well of course.  */
1157   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1158     return false;
1159
1160   /* Find the context procedure's "real" symbol if it has entries.
1161      We look for a procedure symbol, so recurse on the parents if we don't
1162      find one (like in case of a BLOCK construct).  */
1163   for (real_context = context; ; real_context = real_context->parent)
1164     {
1165       /* We should find something, eventually!  */
1166       gcc_assert (real_context);
1167
1168       context_proc = (real_context->entries ? real_context->entries->sym
1169                                             : real_context->proc_name);
1170
1171       /* In some special cases, there may not be a proc_name, like for this
1172          invalid code:
1173          real(bad_kind()) function foo () ...
1174          when checking the call to bad_kind ().
1175          In these cases, we simply return here and assume that the
1176          call is ok.  */
1177       if (!context_proc)
1178         return false;
1179
1180       if (context_proc->attr.flavor != FL_LABEL)
1181         break;
1182     }
1183
1184   /* A call from sym's body to itself is recursion, of course.  */
1185   if (context_proc == proc_sym)
1186     return true;
1187
1188   /* The same is true if context is a contained procedure and sym the
1189      containing one.  */
1190   if (context_proc->attr.contained)
1191     {
1192       gfc_symbol* parent_proc;
1193
1194       gcc_assert (context->parent);
1195       parent_proc = (context->parent->entries ? context->parent->entries->sym
1196                                               : context->parent->proc_name);
1197
1198       if (parent_proc == proc_sym)
1199         return true;
1200     }
1201
1202   return false;
1203 }
1204
1205
1206 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1207    its typespec and formal argument list.  */
1208
1209 static gfc_try
1210 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1211 {
1212   gfc_intrinsic_sym* isym;
1213   const char* symstd;
1214
1215   if (sym->formal)
1216     return SUCCESS;
1217
1218   /* We already know this one is an intrinsic, so we don't call
1219      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1220      gfc_find_subroutine directly to check whether it is a function or
1221      subroutine.  */
1222
1223   if ((isym = gfc_find_function (sym->name)))
1224     {
1225       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1226           && !sym->attr.implicit_type)
1227         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1228                       " ignored", sym->name, &sym->declared_at);
1229
1230       if (!sym->attr.function &&
1231           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1232         return FAILURE;
1233
1234       sym->ts = isym->ts;
1235     }
1236   else if ((isym = gfc_find_subroutine (sym->name)))
1237     {
1238       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1239         {
1240           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1241                       " specifier", sym->name, &sym->declared_at);
1242           return FAILURE;
1243         }
1244
1245       if (!sym->attr.subroutine &&
1246           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1247         return FAILURE;
1248     }
1249   else
1250     {
1251       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1252                  &sym->declared_at);
1253       return FAILURE;
1254     }
1255
1256   gfc_copy_formal_args_intr (sym, isym);
1257
1258   /* Check it is actually available in the standard settings.  */
1259   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1260       == FAILURE)
1261     {
1262       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1263                  " available in the current standard settings but %s.  Use"
1264                  " an appropriate -std=* option or enable -fall-intrinsics"
1265                  " in order to use it.",
1266                  sym->name, &sym->declared_at, symstd);
1267       return FAILURE;
1268     }
1269
1270   return SUCCESS;
1271 }
1272
1273
1274 /* Resolve a procedure expression, like passing it to a called procedure or as
1275    RHS for a procedure pointer assignment.  */
1276
1277 static gfc_try
1278 resolve_procedure_expression (gfc_expr* expr)
1279 {
1280   gfc_symbol* sym;
1281
1282   if (expr->expr_type != EXPR_VARIABLE)
1283     return SUCCESS;
1284   gcc_assert (expr->symtree);
1285
1286   sym = expr->symtree->n.sym;
1287
1288   if (sym->attr.intrinsic)
1289     resolve_intrinsic (sym, &expr->where);
1290
1291   if (sym->attr.flavor != FL_PROCEDURE
1292       || (sym->attr.function && sym->result == sym))
1293     return SUCCESS;
1294
1295   /* A non-RECURSIVE procedure that is used as procedure expression within its
1296      own body is in danger of being called recursively.  */
1297   if (is_illegal_recursion (sym, gfc_current_ns))
1298     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1299                  " itself recursively.  Declare it RECURSIVE or use"
1300                  " -frecursive", sym->name, &expr->where);
1301   
1302   return SUCCESS;
1303 }
1304
1305
1306 /* Resolve an actual argument list.  Most of the time, this is just
1307    resolving the expressions in the list.
1308    The exception is that we sometimes have to decide whether arguments
1309    that look like procedure arguments are really simple variable
1310    references.  */
1311
1312 static gfc_try
1313 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1314                         bool no_formal_args)
1315 {
1316   gfc_symbol *sym;
1317   gfc_symtree *parent_st;
1318   gfc_expr *e;
1319   int save_need_full_assumed_size;
1320   gfc_component *comp;
1321
1322   for (; arg; arg = arg->next)
1323     {
1324       e = arg->expr;
1325       if (e == NULL)
1326         {
1327           /* Check the label is a valid branching target.  */
1328           if (arg->label)
1329             {
1330               if (arg->label->defined == ST_LABEL_UNKNOWN)
1331                 {
1332                   gfc_error ("Label %d referenced at %L is never defined",
1333                              arg->label->value, &arg->label->where);
1334                   return FAILURE;
1335                 }
1336             }
1337           continue;
1338         }
1339
1340       if (gfc_is_proc_ptr_comp (e, &comp))
1341         {
1342           e->ts = comp->ts;
1343           if (e->expr_type == EXPR_PPC)
1344             {
1345               if (comp->as != NULL)
1346                 e->rank = comp->as->rank;
1347               e->expr_type = EXPR_FUNCTION;
1348             }
1349           if (gfc_resolve_expr (e) == FAILURE)                          
1350             return FAILURE; 
1351           goto argument_list;
1352         }
1353
1354       if (e->expr_type == EXPR_VARIABLE
1355             && e->symtree->n.sym->attr.generic
1356             && no_formal_args
1357             && count_specific_procs (e) != 1)
1358         return FAILURE;
1359
1360       if (e->ts.type != BT_PROCEDURE)
1361         {
1362           save_need_full_assumed_size = need_full_assumed_size;
1363           if (e->expr_type != EXPR_VARIABLE)
1364             need_full_assumed_size = 0;
1365           if (gfc_resolve_expr (e) != SUCCESS)
1366             return FAILURE;
1367           need_full_assumed_size = save_need_full_assumed_size;
1368           goto argument_list;
1369         }
1370
1371       /* See if the expression node should really be a variable reference.  */
1372
1373       sym = e->symtree->n.sym;
1374
1375       if (sym->attr.flavor == FL_PROCEDURE
1376           || sym->attr.intrinsic
1377           || sym->attr.external)
1378         {
1379           int actual_ok;
1380
1381           /* If a procedure is not already determined to be something else
1382              check if it is intrinsic.  */
1383           if (!sym->attr.intrinsic
1384               && !(sym->attr.external || sym->attr.use_assoc
1385                    || sym->attr.if_source == IFSRC_IFBODY)
1386               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1387             sym->attr.intrinsic = 1;
1388
1389           if (sym->attr.proc == PROC_ST_FUNCTION)
1390             {
1391               gfc_error ("Statement function '%s' at %L is not allowed as an "
1392                          "actual argument", sym->name, &e->where);
1393             }
1394
1395           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1396                                                sym->attr.subroutine);
1397           if (sym->attr.intrinsic && actual_ok == 0)
1398             {
1399               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1400                          "actual argument", sym->name, &e->where);
1401             }
1402
1403           if (sym->attr.contained && !sym->attr.use_assoc
1404               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1405             {
1406               gfc_error ("Internal procedure '%s' is not allowed as an "
1407                          "actual argument at %L", sym->name, &e->where);
1408             }
1409
1410           if (sym->attr.elemental && !sym->attr.intrinsic)
1411             {
1412               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1413                          "allowed as an actual argument at %L", sym->name,
1414                          &e->where);
1415             }
1416
1417           /* Check if a generic interface has a specific procedure
1418             with the same name before emitting an error.  */
1419           if (sym->attr.generic && count_specific_procs (e) != 1)
1420             return FAILURE;
1421           
1422           /* Just in case a specific was found for the expression.  */
1423           sym = e->symtree->n.sym;
1424
1425           /* If the symbol is the function that names the current (or
1426              parent) scope, then we really have a variable reference.  */
1427
1428           if (gfc_is_function_return_value (sym, sym->ns))
1429             goto got_variable;
1430
1431           /* If all else fails, see if we have a specific intrinsic.  */
1432           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1433             {
1434               gfc_intrinsic_sym *isym;
1435
1436               isym = gfc_find_function (sym->name);
1437               if (isym == NULL || !isym->specific)
1438                 {
1439                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1440                              "for the reference '%s' at %L", sym->name,
1441                              &e->where);
1442                   return FAILURE;
1443                 }
1444               sym->ts = isym->ts;
1445               sym->attr.intrinsic = 1;
1446               sym->attr.function = 1;
1447             }
1448
1449           if (gfc_resolve_expr (e) == FAILURE)
1450             return FAILURE;
1451           goto argument_list;
1452         }
1453
1454       /* See if the name is a module procedure in a parent unit.  */
1455
1456       if (was_declared (sym) || sym->ns->parent == NULL)
1457         goto got_variable;
1458
1459       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1460         {
1461           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1462           return FAILURE;
1463         }
1464
1465       if (parent_st == NULL)
1466         goto got_variable;
1467
1468       sym = parent_st->n.sym;
1469       e->symtree = parent_st;           /* Point to the right thing.  */
1470
1471       if (sym->attr.flavor == FL_PROCEDURE
1472           || sym->attr.intrinsic
1473           || sym->attr.external)
1474         {
1475           if (gfc_resolve_expr (e) == FAILURE)
1476             return FAILURE;
1477           goto argument_list;
1478         }
1479
1480     got_variable:
1481       e->expr_type = EXPR_VARIABLE;
1482       e->ts = sym->ts;
1483       if (sym->as != NULL)
1484         {
1485           e->rank = sym->as->rank;
1486           e->ref = gfc_get_ref ();
1487           e->ref->type = REF_ARRAY;
1488           e->ref->u.ar.type = AR_FULL;
1489           e->ref->u.ar.as = sym->as;
1490         }
1491
1492       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1493          primary.c (match_actual_arg). If above code determines that it
1494          is a  variable instead, it needs to be resolved as it was not
1495          done at the beginning of this function.  */
1496       save_need_full_assumed_size = need_full_assumed_size;
1497       if (e->expr_type != EXPR_VARIABLE)
1498         need_full_assumed_size = 0;
1499       if (gfc_resolve_expr (e) != SUCCESS)
1500         return FAILURE;
1501       need_full_assumed_size = save_need_full_assumed_size;
1502
1503     argument_list:
1504       /* Check argument list functions %VAL, %LOC and %REF.  There is
1505          nothing to do for %REF.  */
1506       if (arg->name && arg->name[0] == '%')
1507         {
1508           if (strncmp ("%VAL", arg->name, 4) == 0)
1509             {
1510               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1511                 {
1512                   gfc_error ("By-value argument at %L is not of numeric "
1513                              "type", &e->where);
1514                   return FAILURE;
1515                 }
1516
1517               if (e->rank)
1518                 {
1519                   gfc_error ("By-value argument at %L cannot be an array or "
1520                              "an array section", &e->where);
1521                 return FAILURE;
1522                 }
1523
1524               /* Intrinsics are still PROC_UNKNOWN here.  However,
1525                  since same file external procedures are not resolvable
1526                  in gfortran, it is a good deal easier to leave them to
1527                  intrinsic.c.  */
1528               if (ptype != PROC_UNKNOWN
1529                   && ptype != PROC_DUMMY
1530                   && ptype != PROC_EXTERNAL
1531                   && ptype != PROC_MODULE)
1532                 {
1533                   gfc_error ("By-value argument at %L is not allowed "
1534                              "in this context", &e->where);
1535                   return FAILURE;
1536                 }
1537             }
1538
1539           /* Statement functions have already been excluded above.  */
1540           else if (strncmp ("%LOC", arg->name, 4) == 0
1541                    && e->ts.type == BT_PROCEDURE)
1542             {
1543               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1544                 {
1545                   gfc_error ("Passing internal procedure at %L by location "
1546                              "not allowed", &e->where);
1547                   return FAILURE;
1548                 }
1549             }
1550         }
1551
1552       /* Fortran 2008, C1237.  */
1553       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1554           && gfc_has_ultimate_pointer (e))
1555         {
1556           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1557                      "component", &e->where);
1558           return FAILURE;
1559         }
1560     }
1561
1562   return SUCCESS;
1563 }
1564
1565
1566 /* Do the checks of the actual argument list that are specific to elemental
1567    procedures.  If called with c == NULL, we have a function, otherwise if
1568    expr == NULL, we have a subroutine.  */
1569
1570 static gfc_try
1571 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1572 {
1573   gfc_actual_arglist *arg0;
1574   gfc_actual_arglist *arg;
1575   gfc_symbol *esym = NULL;
1576   gfc_intrinsic_sym *isym = NULL;
1577   gfc_expr *e = NULL;
1578   gfc_intrinsic_arg *iformal = NULL;
1579   gfc_formal_arglist *eformal = NULL;
1580   bool formal_optional = false;
1581   bool set_by_optional = false;
1582   int i;
1583   int rank = 0;
1584
1585   /* Is this an elemental procedure?  */
1586   if (expr && expr->value.function.actual != NULL)
1587     {
1588       if (expr->value.function.esym != NULL
1589           && expr->value.function.esym->attr.elemental)
1590         {
1591           arg0 = expr->value.function.actual;
1592           esym = expr->value.function.esym;
1593         }
1594       else if (expr->value.function.isym != NULL
1595                && expr->value.function.isym->elemental)
1596         {
1597           arg0 = expr->value.function.actual;
1598           isym = expr->value.function.isym;
1599         }
1600       else
1601         return SUCCESS;
1602     }
1603   else if (c && c->ext.actual != NULL)
1604     {
1605       arg0 = c->ext.actual;
1606       
1607       if (c->resolved_sym)
1608         esym = c->resolved_sym;
1609       else
1610         esym = c->symtree->n.sym;
1611       gcc_assert (esym);
1612
1613       if (!esym->attr.elemental)
1614         return SUCCESS;
1615     }
1616   else
1617     return SUCCESS;
1618
1619   /* The rank of an elemental is the rank of its array argument(s).  */
1620   for (arg = arg0; arg; arg = arg->next)
1621     {
1622       if (arg->expr != NULL && arg->expr->rank > 0)
1623         {
1624           rank = arg->expr->rank;
1625           if (arg->expr->expr_type == EXPR_VARIABLE
1626               && arg->expr->symtree->n.sym->attr.optional)
1627             set_by_optional = true;
1628
1629           /* Function specific; set the result rank and shape.  */
1630           if (expr)
1631             {
1632               expr->rank = rank;
1633               if (!expr->shape && arg->expr->shape)
1634                 {
1635                   expr->shape = gfc_get_shape (rank);
1636                   for (i = 0; i < rank; i++)
1637                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1638                 }
1639             }
1640           break;
1641         }
1642     }
1643
1644   /* If it is an array, it shall not be supplied as an actual argument
1645      to an elemental procedure unless an array of the same rank is supplied
1646      as an actual argument corresponding to a nonoptional dummy argument of
1647      that elemental procedure(12.4.1.5).  */
1648   formal_optional = false;
1649   if (isym)
1650     iformal = isym->formal;
1651   else
1652     eformal = esym->formal;
1653
1654   for (arg = arg0; arg; arg = arg->next)
1655     {
1656       if (eformal)
1657         {
1658           if (eformal->sym && eformal->sym->attr.optional)
1659             formal_optional = true;
1660           eformal = eformal->next;
1661         }
1662       else if (isym && iformal)
1663         {
1664           if (iformal->optional)
1665             formal_optional = true;
1666           iformal = iformal->next;
1667         }
1668       else if (isym)
1669         formal_optional = true;
1670
1671       if (pedantic && arg->expr != NULL
1672           && arg->expr->expr_type == EXPR_VARIABLE
1673           && arg->expr->symtree->n.sym->attr.optional
1674           && formal_optional
1675           && arg->expr->rank
1676           && (set_by_optional || arg->expr->rank != rank)
1677           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1678         {
1679           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1680                        "MISSING, it cannot be the actual argument of an "
1681                        "ELEMENTAL procedure unless there is a non-optional "
1682                        "argument with the same rank (12.4.1.5)",
1683                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1684           return FAILURE;
1685         }
1686     }
1687
1688   for (arg = arg0; arg; arg = arg->next)
1689     {
1690       if (arg->expr == NULL || arg->expr->rank == 0)
1691         continue;
1692
1693       /* Being elemental, the last upper bound of an assumed size array
1694          argument must be present.  */
1695       if (resolve_assumed_size_actual (arg->expr))
1696         return FAILURE;
1697
1698       /* Elemental procedure's array actual arguments must conform.  */
1699       if (e != NULL)
1700         {
1701           if (gfc_check_conformance (arg->expr, e,
1702                                      "elemental procedure") == FAILURE)
1703             return FAILURE;
1704         }
1705       else
1706         e = arg->expr;
1707     }
1708
1709   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1710      is an array, the intent inout/out variable needs to be also an array.  */
1711   if (rank > 0 && esym && expr == NULL)
1712     for (eformal = esym->formal, arg = arg0; arg && eformal;
1713          arg = arg->next, eformal = eformal->next)
1714       if ((eformal->sym->attr.intent == INTENT_OUT
1715            || eformal->sym->attr.intent == INTENT_INOUT)
1716           && arg->expr && arg->expr->rank == 0)
1717         {
1718           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1719                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1720                      "actual argument is an array", &arg->expr->where,
1721                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1722                      : "INOUT", eformal->sym->name, esym->name);
1723           return FAILURE;
1724         }
1725   return SUCCESS;
1726 }
1727
1728
1729 /* Go through each actual argument in ACTUAL and see if it can be
1730    implemented as an inlined, non-copying intrinsic.  FNSYM is the
1731    function being called, or NULL if not known.  */
1732
1733 static void
1734 find_noncopying_intrinsics (gfc_symbol *fnsym, gfc_actual_arglist *actual)
1735 {
1736   gfc_actual_arglist *ap;
1737   gfc_expr *expr;
1738
1739   for (ap = actual; ap; ap = ap->next)
1740     if (ap->expr
1741         && (expr = gfc_get_noncopying_intrinsic_argument (ap->expr))
1742         && !gfc_check_fncall_dependency (expr, INTENT_IN, fnsym, actual,
1743                                          NOT_ELEMENTAL))
1744       ap->expr->inline_noncopying_intrinsic = 1;
1745 }
1746
1747
1748 /* This function does the checking of references to global procedures
1749    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1750    77 and 95 standards.  It checks for a gsymbol for the name, making
1751    one if it does not already exist.  If it already exists, then the
1752    reference being resolved must correspond to the type of gsymbol.
1753    Otherwise, the new symbol is equipped with the attributes of the
1754    reference.  The corresponding code that is called in creating
1755    global entities is parse.c.
1756
1757    In addition, for all but -std=legacy, the gsymbols are used to
1758    check the interfaces of external procedures from the same file.
1759    The namespace of the gsymbol is resolved and then, once this is
1760    done the interface is checked.  */
1761
1762
1763 static bool
1764 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1765 {
1766   if (!gsym_ns->proc_name->attr.recursive)
1767     return true;
1768
1769   if (sym->ns == gsym_ns)
1770     return false;
1771
1772   if (sym->ns->parent && sym->ns->parent == gsym_ns)
1773     return false;
1774
1775   return true;
1776 }
1777
1778 static bool
1779 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
1780 {
1781   if (gsym_ns->entries)
1782     {
1783       gfc_entry_list *entry = gsym_ns->entries;
1784
1785       for (; entry; entry = entry->next)
1786         {
1787           if (strcmp (sym->name, entry->sym->name) == 0)
1788             {
1789               if (strcmp (gsym_ns->proc_name->name,
1790                           sym->ns->proc_name->name) == 0)
1791                 return false;
1792
1793               if (sym->ns->parent
1794                   && strcmp (gsym_ns->proc_name->name,
1795                              sym->ns->parent->proc_name->name) == 0)
1796                 return false;
1797             }
1798         }
1799     }
1800   return true;
1801 }
1802
1803 static void
1804 resolve_global_procedure (gfc_symbol *sym, locus *where,
1805                           gfc_actual_arglist **actual, int sub)
1806 {
1807   gfc_gsymbol * gsym;
1808   gfc_namespace *ns;
1809   enum gfc_symbol_type type;
1810
1811   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
1812
1813   gsym = gfc_get_gsymbol (sym->name);
1814
1815   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
1816     gfc_global_used (gsym, where);
1817
1818   if (gfc_option.flag_whole_file
1819         && sym->attr.if_source == IFSRC_UNKNOWN
1820         && gsym->type != GSYM_UNKNOWN
1821         && gsym->ns
1822         && gsym->ns->resolved != -1
1823         && gsym->ns->proc_name
1824         && not_in_recursive (sym, gsym->ns)
1825         && not_entry_self_reference (sym, gsym->ns))
1826     {
1827       /* Resolve the gsymbol namespace if needed.  */
1828       if (!gsym->ns->resolved)
1829         {
1830           gfc_dt_list *old_dt_list;
1831
1832           /* Stash away derived types so that the backend_decls do not
1833              get mixed up.  */
1834           old_dt_list = gfc_derived_types;
1835           gfc_derived_types = NULL;
1836
1837           gfc_resolve (gsym->ns);
1838
1839           /* Store the new derived types with the global namespace.  */
1840           if (gfc_derived_types)
1841             gsym->ns->derived_types = gfc_derived_types;
1842
1843           /* Restore the derived types of this namespace.  */
1844           gfc_derived_types = old_dt_list;
1845         }
1846
1847       /* Make sure that translation for the gsymbol occurs before
1848          the procedure currently being resolved.  */
1849       ns = gfc_global_ns_list;
1850       for (; ns && ns != gsym->ns; ns = ns->sibling)
1851         {
1852           if (ns->sibling == gsym->ns)
1853             {
1854               ns->sibling = gsym->ns->sibling;
1855               gsym->ns->sibling = gfc_global_ns_list;
1856               gfc_global_ns_list = gsym->ns;
1857               break;
1858             }
1859         }
1860
1861       if (gsym->ns->proc_name->attr.function
1862             && gsym->ns->proc_name->as
1863             && gsym->ns->proc_name->as->rank
1864             && (!sym->as || sym->as->rank != gsym->ns->proc_name->as->rank))
1865         gfc_error ("The reference to function '%s' at %L either needs an "
1866                    "explicit INTERFACE or the rank is incorrect", sym->name,
1867                    where);
1868
1869       /* Non-assumed length character functions.  */
1870       if (sym->attr.function && sym->ts.type == BT_CHARACTER
1871           && gsym->ns->proc_name->ts.u.cl->length != NULL)
1872         {
1873           gfc_charlen *cl = sym->ts.u.cl;
1874
1875           if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
1876               && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
1877             {
1878               gfc_error ("Nonconstant character-length function '%s' at %L "
1879                          "must have an explicit interface", sym->name,
1880                          &sym->declared_at);
1881             }
1882         }
1883
1884       /* Differences in constant character lengths.  */
1885       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
1886         {
1887           long int l1 = 0, l2 = 0;
1888           gfc_charlen *cl1 = sym->ts.u.cl;
1889           gfc_charlen *cl2 = gsym->ns->proc_name->ts.u.cl;
1890
1891           if (cl1 != NULL
1892               && cl1->length != NULL
1893               && cl1->length->expr_type == EXPR_CONSTANT)
1894             l1 = mpz_get_si (cl1->length->value.integer);
1895
1896           if (cl2 != NULL
1897               && cl2->length != NULL
1898               && cl2->length->expr_type == EXPR_CONSTANT)
1899             l2 = mpz_get_si (cl2->length->value.integer);
1900
1901           if (l1 && l2 && l1 != l2)
1902             gfc_error ("Character length mismatch in return type of "
1903                        "function '%s' at %L (%ld/%ld)", sym->name,
1904                        &sym->declared_at, l1, l2);
1905         }
1906
1907      /* Type mismatch of function return type and expected type.  */
1908      if (sym->attr.function
1909          && !gfc_compare_types (&sym->ts, &gsym->ns->proc_name->ts))
1910         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
1911                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
1912                    gfc_typename (&gsym->ns->proc_name->ts));
1913
1914       /* Assumed shape arrays as dummy arguments.  */
1915       if (gsym->ns->proc_name->formal)
1916         {
1917           gfc_formal_arglist *arg = gsym->ns->proc_name->formal;
1918           for ( ; arg; arg = arg->next)
1919             if (arg->sym && arg->sym->as
1920                 && arg->sym->as->type == AS_ASSUMED_SHAPE)
1921               {
1922                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
1923                            "'%s' argument must have an explicit interface",
1924                            sym->name, &sym->declared_at, arg->sym->name);
1925                 break;
1926               }
1927             else if (arg->sym && arg->sym->attr.optional)
1928               {
1929                 gfc_error ("Procedure '%s' at %L with optional dummy argument "
1930                            "'%s' must have an explicit interface",
1931                            sym->name, &sym->declared_at, arg->sym->name);
1932                 break;
1933               }
1934         }
1935
1936       if (gfc_option.flag_whole_file == 1
1937           || ((gfc_option.warn_std & GFC_STD_LEGACY)
1938               && !(gfc_option.warn_std & GFC_STD_GNU)))
1939         gfc_errors_to_warnings (1);
1940
1941       gfc_procedure_use (gsym->ns->proc_name, actual, where);
1942
1943       gfc_errors_to_warnings (0);
1944     }
1945
1946   if (gsym->type == GSYM_UNKNOWN)
1947     {
1948       gsym->type = type;
1949       gsym->where = *where;
1950     }
1951
1952   gsym->used = 1;
1953 }
1954
1955
1956 /************* Function resolution *************/
1957
1958 /* Resolve a function call known to be generic.
1959    Section 14.1.2.4.1.  */
1960
1961 static match
1962 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
1963 {
1964   gfc_symbol *s;
1965
1966   if (sym->attr.generic)
1967     {
1968       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
1969       if (s != NULL)
1970         {
1971           expr->value.function.name = s->name;
1972           expr->value.function.esym = s;
1973
1974           if (s->ts.type != BT_UNKNOWN)
1975             expr->ts = s->ts;
1976           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
1977             expr->ts = s->result->ts;
1978
1979           if (s->as != NULL)
1980             expr->rank = s->as->rank;
1981           else if (s->result != NULL && s->result->as != NULL)
1982             expr->rank = s->result->as->rank;
1983
1984           gfc_set_sym_referenced (expr->value.function.esym);
1985
1986           return MATCH_YES;
1987         }
1988
1989       /* TODO: Need to search for elemental references in generic
1990          interface.  */
1991     }
1992
1993   if (sym->attr.intrinsic)
1994     return gfc_intrinsic_func_interface (expr, 0);
1995
1996   return MATCH_NO;
1997 }
1998
1999
2000 static gfc_try
2001 resolve_generic_f (gfc_expr *expr)
2002 {
2003   gfc_symbol *sym;
2004   match m;
2005
2006   sym = expr->symtree->n.sym;
2007
2008   for (;;)
2009     {
2010       m = resolve_generic_f0 (expr, sym);
2011       if (m == MATCH_YES)
2012         return SUCCESS;
2013       else if (m == MATCH_ERROR)
2014         return FAILURE;
2015
2016 generic:
2017       if (sym->ns->parent == NULL)
2018         break;
2019       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2020
2021       if (sym == NULL)
2022         break;
2023       if (!generic_sym (sym))
2024         goto generic;
2025     }
2026
2027   /* Last ditch attempt.  See if the reference is to an intrinsic
2028      that possesses a matching interface.  14.1.2.4  */
2029   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
2030     {
2031       gfc_error ("There is no specific function for the generic '%s' at %L",
2032                  expr->symtree->n.sym->name, &expr->where);
2033       return FAILURE;
2034     }
2035
2036   m = gfc_intrinsic_func_interface (expr, 0);
2037   if (m == MATCH_YES)
2038     return SUCCESS;
2039   if (m == MATCH_NO)
2040     gfc_error ("Generic function '%s' at %L is not consistent with a "
2041                "specific intrinsic interface", expr->symtree->n.sym->name,
2042                &expr->where);
2043
2044   return FAILURE;
2045 }
2046
2047
2048 /* Resolve a function call known to be specific.  */
2049
2050 static match
2051 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2052 {
2053   match m;
2054
2055   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2056     {
2057       if (sym->attr.dummy)
2058         {
2059           sym->attr.proc = PROC_DUMMY;
2060           goto found;
2061         }
2062
2063       sym->attr.proc = PROC_EXTERNAL;
2064       goto found;
2065     }
2066
2067   if (sym->attr.proc == PROC_MODULE
2068       || sym->attr.proc == PROC_ST_FUNCTION
2069       || sym->attr.proc == PROC_INTERNAL)
2070     goto found;
2071
2072   if (sym->attr.intrinsic)
2073     {
2074       m = gfc_intrinsic_func_interface (expr, 1);
2075       if (m == MATCH_YES)
2076         return MATCH_YES;
2077       if (m == MATCH_NO)
2078         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2079                    "with an intrinsic", sym->name, &expr->where);
2080
2081       return MATCH_ERROR;
2082     }
2083
2084   return MATCH_NO;
2085
2086 found:
2087   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2088
2089   if (sym->result)
2090     expr->ts = sym->result->ts;
2091   else
2092     expr->ts = sym->ts;
2093   expr->value.function.name = sym->name;
2094   expr->value.function.esym = sym;
2095   if (sym->as != NULL)
2096     expr->rank = sym->as->rank;
2097
2098   return MATCH_YES;
2099 }
2100
2101
2102 static gfc_try
2103 resolve_specific_f (gfc_expr *expr)
2104 {
2105   gfc_symbol *sym;
2106   match m;
2107
2108   sym = expr->symtree->n.sym;
2109
2110   for (;;)
2111     {
2112       m = resolve_specific_f0 (sym, expr);
2113       if (m == MATCH_YES)
2114         return SUCCESS;
2115       if (m == MATCH_ERROR)
2116         return FAILURE;
2117
2118       if (sym->ns->parent == NULL)
2119         break;
2120
2121       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2122
2123       if (sym == NULL)
2124         break;
2125     }
2126
2127   gfc_error ("Unable to resolve the specific function '%s' at %L",
2128              expr->symtree->n.sym->name, &expr->where);
2129
2130   return SUCCESS;
2131 }
2132
2133
2134 /* Resolve a procedure call not known to be generic nor specific.  */
2135
2136 static gfc_try
2137 resolve_unknown_f (gfc_expr *expr)
2138 {
2139   gfc_symbol *sym;
2140   gfc_typespec *ts;
2141
2142   sym = expr->symtree->n.sym;
2143
2144   if (sym->attr.dummy)
2145     {
2146       sym->attr.proc = PROC_DUMMY;
2147       expr->value.function.name = sym->name;
2148       goto set_type;
2149     }
2150
2151   /* See if we have an intrinsic function reference.  */
2152
2153   if (gfc_is_intrinsic (sym, 0, expr->where))
2154     {
2155       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2156         return SUCCESS;
2157       return FAILURE;
2158     }
2159
2160   /* The reference is to an external name.  */
2161
2162   sym->attr.proc = PROC_EXTERNAL;
2163   expr->value.function.name = sym->name;
2164   expr->value.function.esym = expr->symtree->n.sym;
2165
2166   if (sym->as != NULL)
2167     expr->rank = sym->as->rank;
2168
2169   /* Type of the expression is either the type of the symbol or the
2170      default type of the symbol.  */
2171
2172 set_type:
2173   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2174
2175   if (sym->ts.type != BT_UNKNOWN)
2176     expr->ts = sym->ts;
2177   else
2178     {
2179       ts = gfc_get_default_type (sym->name, sym->ns);
2180
2181       if (ts->type == BT_UNKNOWN)
2182         {
2183           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2184                      sym->name, &expr->where);
2185           return FAILURE;
2186         }
2187       else
2188         expr->ts = *ts;
2189     }
2190
2191   return SUCCESS;
2192 }
2193
2194
2195 /* Return true, if the symbol is an external procedure.  */
2196 static bool
2197 is_external_proc (gfc_symbol *sym)
2198 {
2199   if (!sym->attr.dummy && !sym->attr.contained
2200         && !(sym->attr.intrinsic
2201               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2202         && sym->attr.proc != PROC_ST_FUNCTION
2203         && !sym->attr.use_assoc
2204         && sym->name)
2205     return true;
2206
2207   return false;
2208 }
2209
2210
2211 /* Figure out if a function reference is pure or not.  Also set the name
2212    of the function for a potential error message.  Return nonzero if the
2213    function is PURE, zero if not.  */
2214 static int
2215 pure_stmt_function (gfc_expr *, gfc_symbol *);
2216
2217 static int
2218 pure_function (gfc_expr *e, const char **name)
2219 {
2220   int pure;
2221
2222   *name = NULL;
2223
2224   if (e->symtree != NULL
2225         && e->symtree->n.sym != NULL
2226         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2227     return pure_stmt_function (e, e->symtree->n.sym);
2228
2229   if (e->value.function.esym)
2230     {
2231       pure = gfc_pure (e->value.function.esym);
2232       *name = e->value.function.esym->name;
2233     }
2234   else if (e->value.function.isym)
2235     {
2236       pure = e->value.function.isym->pure
2237              || e->value.function.isym->elemental;
2238       *name = e->value.function.isym->name;
2239     }
2240   else
2241     {
2242       /* Implicit functions are not pure.  */
2243       pure = 0;
2244       *name = e->value.function.name;
2245     }
2246
2247   return pure;
2248 }
2249
2250
2251 static bool
2252 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2253                  int *f ATTRIBUTE_UNUSED)
2254 {
2255   const char *name;
2256
2257   /* Don't bother recursing into other statement functions
2258      since they will be checked individually for purity.  */
2259   if (e->expr_type != EXPR_FUNCTION
2260         || !e->symtree
2261         || e->symtree->n.sym == sym
2262         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2263     return false;
2264
2265   return pure_function (e, &name) ? false : true;
2266 }
2267
2268
2269 static int
2270 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2271 {
2272   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2273 }
2274
2275
2276 static gfc_try
2277 is_scalar_expr_ptr (gfc_expr *expr)
2278 {
2279   gfc_try retval = SUCCESS;
2280   gfc_ref *ref;
2281   int start;
2282   int end;
2283
2284   /* See if we have a gfc_ref, which means we have a substring, array
2285      reference, or a component.  */
2286   if (expr->ref != NULL)
2287     {
2288       ref = expr->ref;
2289       while (ref->next != NULL)
2290         ref = ref->next;
2291
2292       switch (ref->type)
2293         {
2294         case REF_SUBSTRING:
2295           if (ref->u.ss.length != NULL 
2296               && ref->u.ss.length->length != NULL
2297               && ref->u.ss.start
2298               && ref->u.ss.start->expr_type == EXPR_CONSTANT 
2299               && ref->u.ss.end
2300               && ref->u.ss.end->expr_type == EXPR_CONSTANT)
2301             {
2302               start = (int) mpz_get_si (ref->u.ss.start->value.integer);
2303               end = (int) mpz_get_si (ref->u.ss.end->value.integer);
2304               if (end - start + 1 != 1)
2305                 retval = FAILURE;
2306             }
2307           else
2308             retval = FAILURE;
2309           break;
2310         case REF_ARRAY:
2311           if (ref->u.ar.type == AR_ELEMENT)
2312             retval = SUCCESS;
2313           else if (ref->u.ar.type == AR_FULL)
2314             {
2315               /* The user can give a full array if the array is of size 1.  */
2316               if (ref->u.ar.as != NULL
2317                   && ref->u.ar.as->rank == 1
2318                   && ref->u.ar.as->type == AS_EXPLICIT
2319                   && ref->u.ar.as->lower[0] != NULL
2320                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2321                   && ref->u.ar.as->upper[0] != NULL
2322                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2323                 {
2324                   /* If we have a character string, we need to check if
2325                      its length is one.  */
2326                   if (expr->ts.type == BT_CHARACTER)
2327                     {
2328                       if (expr->ts.u.cl == NULL
2329                           || expr->ts.u.cl->length == NULL
2330                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2331                           != 0)
2332                         retval = FAILURE;
2333                     }
2334                   else
2335                     {
2336                       /* We have constant lower and upper bounds.  If the
2337                          difference between is 1, it can be considered a
2338                          scalar.  */
2339                       start = (int) mpz_get_si
2340                                 (ref->u.ar.as->lower[0]->value.integer);
2341                       end = (int) mpz_get_si
2342                                 (ref->u.ar.as->upper[0]->value.integer);
2343                       if (end - start + 1 != 1)
2344                         retval = FAILURE;
2345                    }
2346                 }
2347               else
2348                 retval = FAILURE;
2349             }
2350           else
2351             retval = FAILURE;
2352           break;
2353         default:
2354           retval = SUCCESS;
2355           break;
2356         }
2357     }
2358   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2359     {
2360       /* Character string.  Make sure it's of length 1.  */
2361       if (expr->ts.u.cl == NULL
2362           || expr->ts.u.cl->length == NULL
2363           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2364         retval = FAILURE;
2365     }
2366   else if (expr->rank != 0)
2367     retval = FAILURE;
2368
2369   return retval;
2370 }
2371
2372
2373 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2374    and, in the case of c_associated, set the binding label based on
2375    the arguments.  */
2376
2377 static gfc_try
2378 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2379                           gfc_symbol **new_sym)
2380 {
2381   char name[GFC_MAX_SYMBOL_LEN + 1];
2382   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2383   int optional_arg = 0, is_pointer = 0;
2384   gfc_try retval = SUCCESS;
2385   gfc_symbol *args_sym;
2386   gfc_typespec *arg_ts;
2387
2388   if (args->expr->expr_type == EXPR_CONSTANT
2389       || args->expr->expr_type == EXPR_OP
2390       || args->expr->expr_type == EXPR_NULL)
2391     {
2392       gfc_error ("Argument to '%s' at %L is not a variable",
2393                  sym->name, &(args->expr->where));
2394       return FAILURE;
2395     }
2396
2397   args_sym = args->expr->symtree->n.sym;
2398
2399   /* The typespec for the actual arg should be that stored in the expr
2400      and not necessarily that of the expr symbol (args_sym), because
2401      the actual expression could be a part-ref of the expr symbol.  */
2402   arg_ts = &(args->expr->ts);
2403
2404   is_pointer = gfc_is_data_pointer (args->expr);
2405     
2406   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2407     {
2408       /* If the user gave two args then they are providing something for
2409          the optional arg (the second cptr).  Therefore, set the name and
2410          binding label to the c_associated for two cptrs.  Otherwise,
2411          set c_associated to expect one cptr.  */
2412       if (args->next)
2413         {
2414           /* two args.  */
2415           sprintf (name, "%s_2", sym->name);
2416           sprintf (binding_label, "%s_2", sym->binding_label);
2417           optional_arg = 1;
2418         }
2419       else
2420         {
2421           /* one arg.  */
2422           sprintf (name, "%s_1", sym->name);
2423           sprintf (binding_label, "%s_1", sym->binding_label);
2424           optional_arg = 0;
2425         }
2426
2427       /* Get a new symbol for the version of c_associated that
2428          will get called.  */
2429       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2430     }
2431   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2432            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2433     {
2434       sprintf (name, "%s", sym->name);
2435       sprintf (binding_label, "%s", sym->binding_label);
2436
2437       /* Error check the call.  */
2438       if (args->next != NULL)
2439         {
2440           gfc_error_now ("More actual than formal arguments in '%s' "
2441                          "call at %L", name, &(args->expr->where));
2442           retval = FAILURE;
2443         }
2444       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2445         {
2446           /* Make sure we have either the target or pointer attribute.  */
2447           if (!args_sym->attr.target && !is_pointer)
2448             {
2449               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2450                              "a TARGET or an associated pointer",
2451                              args_sym->name,
2452                              sym->name, &(args->expr->where));
2453               retval = FAILURE;
2454             }
2455
2456           /* See if we have interoperable type and type param.  */
2457           if (verify_c_interop (arg_ts) == SUCCESS
2458               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2459             {
2460               if (args_sym->attr.target == 1)
2461                 {
2462                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2463                      has the target attribute and is interoperable.  */
2464                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2465                      allocatable variable that has the TARGET attribute and
2466                      is not an array of zero size.  */
2467                   if (args_sym->attr.allocatable == 1)
2468                     {
2469                       if (args_sym->attr.dimension != 0 
2470                           && (args_sym->as && args_sym->as->rank == 0))
2471                         {
2472                           gfc_error_now ("Allocatable variable '%s' used as a "
2473                                          "parameter to '%s' at %L must not be "
2474                                          "an array of zero size",
2475                                          args_sym->name, sym->name,
2476                                          &(args->expr->where));
2477                           retval = FAILURE;
2478                         }
2479                     }
2480                   else
2481                     {
2482                       /* A non-allocatable target variable with C
2483                          interoperable type and type parameters must be
2484                          interoperable.  */
2485                       if (args_sym && args_sym->attr.dimension)
2486                         {
2487                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2488                             {
2489                               gfc_error ("Assumed-shape array '%s' at %L "
2490                                          "cannot be an argument to the "
2491                                          "procedure '%s' because "
2492                                          "it is not C interoperable",
2493                                          args_sym->name,
2494                                          &(args->expr->where), sym->name);
2495                               retval = FAILURE;
2496                             }
2497                           else if (args_sym->as->type == AS_DEFERRED)
2498                             {
2499                               gfc_error ("Deferred-shape array '%s' at %L "
2500                                          "cannot be an argument to the "
2501                                          "procedure '%s' because "
2502                                          "it is not C interoperable",
2503                                          args_sym->name,
2504                                          &(args->expr->where), sym->name);
2505                               retval = FAILURE;
2506                             }
2507                         }
2508                               
2509                       /* Make sure it's not a character string.  Arrays of
2510                          any type should be ok if the variable is of a C
2511                          interoperable type.  */
2512                       if (arg_ts->type == BT_CHARACTER)
2513                         if (arg_ts->u.cl != NULL
2514                             && (arg_ts->u.cl->length == NULL
2515                                 || arg_ts->u.cl->length->expr_type
2516                                    != EXPR_CONSTANT
2517                                 || mpz_cmp_si
2518                                     (arg_ts->u.cl->length->value.integer, 1)
2519                                    != 0)
2520                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2521                           {
2522                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2523                                            "at %L must have a length of 1",
2524                                            args_sym->name, sym->name,
2525                                            &(args->expr->where));
2526                             retval = FAILURE;
2527                           }
2528                     }
2529                 }
2530               else if (is_pointer
2531                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2532                 {
2533                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2534                      scalar pointer.  */
2535                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2536                                  "associated scalar POINTER", args_sym->name,
2537                                  sym->name, &(args->expr->where));
2538                   retval = FAILURE;
2539                 }
2540             }
2541           else
2542             {
2543               /* The parameter is not required to be C interoperable.  If it
2544                  is not C interoperable, it must be a nonpolymorphic scalar
2545                  with no length type parameters.  It still must have either
2546                  the pointer or target attribute, and it can be
2547                  allocatable (but must be allocated when c_loc is called).  */
2548               if (args->expr->rank != 0 
2549                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2550                 {
2551                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2552                                  "scalar", args_sym->name, sym->name,
2553                                  &(args->expr->where));
2554                   retval = FAILURE;
2555                 }
2556               else if (arg_ts->type == BT_CHARACTER 
2557                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2558                 {
2559                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2560                                  "%L must have a length of 1",
2561                                  args_sym->name, sym->name,
2562                                  &(args->expr->where));
2563                   retval = FAILURE;
2564                 }
2565             }
2566         }
2567       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2568         {
2569           if (args_sym->attr.flavor != FL_PROCEDURE)
2570             {
2571               /* TODO: Update this error message to allow for procedure
2572                  pointers once they are implemented.  */
2573               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2574                              "procedure",
2575                              args_sym->name, sym->name,
2576                              &(args->expr->where));
2577               retval = FAILURE;
2578             }
2579           else if (args_sym->attr.is_bind_c != 1)
2580             {
2581               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2582                              "BIND(C)",
2583                              args_sym->name, sym->name,
2584                              &(args->expr->where));
2585               retval = FAILURE;
2586             }
2587         }
2588       
2589       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2590       *new_sym = sym;
2591     }
2592   else
2593     {
2594       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2595                           "iso_c_binding function: '%s'!\n", sym->name);
2596     }
2597
2598   return retval;
2599 }
2600
2601
2602 /* Resolve a function call, which means resolving the arguments, then figuring
2603    out which entity the name refers to.  */
2604 /* TODO: Check procedure arguments so that an INTENT(IN) isn't passed
2605    to INTENT(OUT) or INTENT(INOUT).  */
2606
2607 static gfc_try
2608 resolve_function (gfc_expr *expr)
2609 {
2610   gfc_actual_arglist *arg;
2611   gfc_symbol *sym;
2612   const char *name;
2613   gfc_try t;
2614   int temp;
2615   procedure_type p = PROC_INTRINSIC;
2616   bool no_formal_args;
2617
2618   sym = NULL;
2619   if (expr->symtree)
2620     sym = expr->symtree->n.sym;
2621
2622   /* If this is a procedure pointer component, it has already been resolved.  */
2623   if (gfc_is_proc_ptr_comp (expr, NULL))
2624     return SUCCESS;
2625   
2626   if (sym && sym->attr.intrinsic
2627       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2628     return FAILURE;
2629
2630   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2631     {
2632       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2633       return FAILURE;
2634     }
2635
2636   /* If this ia a deferred TBP with an abstract interface (which may
2637      of course be referenced), expr->value.function.esym will be set.  */
2638   if (sym && sym->attr.abstract && !expr->value.function.esym)
2639     {
2640       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2641                  sym->name, &expr->where);
2642       return FAILURE;
2643     }
2644
2645   /* Switch off assumed size checking and do this again for certain kinds
2646      of procedure, once the procedure itself is resolved.  */
2647   need_full_assumed_size++;
2648
2649   if (expr->symtree && expr->symtree->n.sym)
2650     p = expr->symtree->n.sym->attr.proc;
2651
2652   if (expr->value.function.isym && expr->value.function.isym->inquiry)
2653     inquiry_argument = true;
2654   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2655
2656   if (resolve_actual_arglist (expr->value.function.actual,
2657                               p, no_formal_args) == FAILURE)
2658     {
2659       inquiry_argument = false;
2660       return FAILURE;
2661     }
2662
2663   inquiry_argument = false;
2664  
2665   /* Need to setup the call to the correct c_associated, depending on
2666      the number of cptrs to user gives to compare.  */
2667   if (sym && sym->attr.is_iso_c == 1)
2668     {
2669       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2670           == FAILURE)
2671         return FAILURE;
2672       
2673       /* Get the symtree for the new symbol (resolved func).
2674          the old one will be freed later, when it's no longer used.  */
2675       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2676     }
2677   
2678   /* Resume assumed_size checking.  */
2679   need_full_assumed_size--;
2680
2681   /* If the procedure is external, check for usage.  */
2682   if (sym && is_external_proc (sym))
2683     resolve_global_procedure (sym, &expr->where,
2684                               &expr->value.function.actual, 0);
2685
2686   if (sym && sym->ts.type == BT_CHARACTER
2687       && sym->ts.u.cl
2688       && sym->ts.u.cl->length == NULL
2689       && !sym->attr.dummy
2690       && expr->value.function.esym == NULL
2691       && !sym->attr.contained)
2692     {
2693       /* Internal procedures are taken care of in resolve_contained_fntype.  */
2694       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2695                  "be used at %L since it is not a dummy argument",
2696                  sym->name, &expr->where);
2697       return FAILURE;
2698     }
2699
2700   /* See if function is already resolved.  */
2701
2702   if (expr->value.function.name != NULL)
2703     {
2704       if (expr->ts.type == BT_UNKNOWN)
2705         expr->ts = sym->ts;
2706       t = SUCCESS;
2707     }
2708   else
2709     {
2710       /* Apply the rules of section 14.1.2.  */
2711
2712       switch (procedure_kind (sym))
2713         {
2714         case PTYPE_GENERIC:
2715           t = resolve_generic_f (expr);
2716           break;
2717
2718         case PTYPE_SPECIFIC:
2719           t = resolve_specific_f (expr);
2720           break;
2721
2722         case PTYPE_UNKNOWN:
2723           t = resolve_unknown_f (expr);
2724           break;
2725
2726         default:
2727           gfc_internal_error ("resolve_function(): bad function type");
2728         }
2729     }
2730
2731   /* If the expression is still a function (it might have simplified),
2732      then we check to see if we are calling an elemental function.  */
2733
2734   if (expr->expr_type != EXPR_FUNCTION)
2735     return t;
2736
2737   temp = need_full_assumed_size;
2738   need_full_assumed_size = 0;
2739
2740   if (resolve_elemental_actual (expr, NULL) == FAILURE)
2741     return FAILURE;
2742
2743   if (omp_workshare_flag
2744       && expr->value.function.esym
2745       && ! gfc_elemental (expr->value.function.esym))
2746     {
2747       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
2748                  "in WORKSHARE construct", expr->value.function.esym->name,
2749                  &expr->where);
2750       t = FAILURE;
2751     }
2752
2753 #define GENERIC_ID expr->value.function.isym->id
2754   else if (expr->value.function.actual != NULL
2755            && expr->value.function.isym != NULL
2756            && GENERIC_ID != GFC_ISYM_LBOUND
2757            && GENERIC_ID != GFC_ISYM_LEN
2758            && GENERIC_ID != GFC_ISYM_LOC
2759            && GENERIC_ID != GFC_ISYM_PRESENT)
2760     {
2761       /* Array intrinsics must also have the last upper bound of an
2762          assumed size array argument.  UBOUND and SIZE have to be
2763          excluded from the check if the second argument is anything
2764          than a constant.  */
2765
2766       for (arg = expr->value.function.actual; arg; arg = arg->next)
2767         {
2768           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
2769               && arg->next != NULL && arg->next->expr)
2770             {
2771               if (arg->next->expr->expr_type != EXPR_CONSTANT)
2772                 break;
2773
2774               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
2775                 break;
2776
2777               if ((int)mpz_get_si (arg->next->expr->value.integer)
2778                         < arg->expr->rank)
2779                 break;
2780             }
2781
2782           if (arg->expr != NULL
2783               && arg->expr->rank > 0
2784               && resolve_assumed_size_actual (arg->expr))
2785             return FAILURE;
2786         }
2787     }
2788 #undef GENERIC_ID
2789
2790   need_full_assumed_size = temp;
2791   name = NULL;
2792
2793   if (!pure_function (expr, &name) && name)
2794     {
2795       if (forall_flag)
2796         {
2797           gfc_error ("reference to non-PURE function '%s' at %L inside a "
2798                      "FORALL %s", name, &expr->where,
2799                      forall_flag == 2 ? "mask" : "block");
2800           t = FAILURE;
2801         }
2802       else if (gfc_pure (NULL))
2803         {
2804           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
2805                      "procedure within a PURE procedure", name, &expr->where);
2806           t = FAILURE;
2807         }
2808     }
2809
2810   /* Functions without the RECURSIVE attribution are not allowed to
2811    * call themselves.  */
2812   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
2813     {
2814       gfc_symbol *esym;
2815       esym = expr->value.function.esym;
2816
2817       if (is_illegal_recursion (esym, gfc_current_ns))
2818       {
2819         if (esym->attr.entry && esym->ns->entries)
2820           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
2821                      " function '%s' is not RECURSIVE",
2822                      esym->name, &expr->where, esym->ns->entries->sym->name);
2823         else
2824           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
2825                      " is not RECURSIVE", esym->name, &expr->where);
2826
2827         t = FAILURE;
2828       }
2829     }
2830
2831   /* Character lengths of use associated functions may contains references to
2832      symbols not referenced from the current program unit otherwise.  Make sure
2833      those symbols are marked as referenced.  */
2834
2835   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
2836       && expr->value.function.esym->attr.use_assoc)
2837     {
2838       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
2839     }
2840
2841   if (t == SUCCESS
2842         && !((expr->value.function.esym
2843                 && expr->value.function.esym->attr.elemental)
2844                         ||
2845              (expr->value.function.isym
2846                 && expr->value.function.isym->elemental)))
2847     find_noncopying_intrinsics (expr->value.function.esym,
2848                                 expr->value.function.actual);
2849
2850   /* Make sure that the expression has a typespec that works.  */
2851   if (expr->ts.type == BT_UNKNOWN)
2852     {
2853       if (expr->symtree->n.sym->result
2854             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
2855             && !expr->symtree->n.sym->result->attr.proc_pointer)
2856         expr->ts = expr->symtree->n.sym->result->ts;
2857     }
2858
2859   return t;
2860 }
2861
2862
2863 /************* Subroutine resolution *************/
2864
2865 static void
2866 pure_subroutine (gfc_code *c, gfc_symbol *sym)
2867 {
2868   if (gfc_pure (sym))
2869     return;
2870
2871   if (forall_flag)
2872     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
2873                sym->name, &c->loc);
2874   else if (gfc_pure (NULL))
2875     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
2876                &c->loc);
2877 }
2878
2879
2880 static match
2881 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
2882 {
2883   gfc_symbol *s;
2884
2885   if (sym->attr.generic)
2886     {
2887       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
2888       if (s != NULL)
2889         {
2890           c->resolved_sym = s;
2891           pure_subroutine (c, s);
2892           return MATCH_YES;
2893         }
2894
2895       /* TODO: Need to search for elemental references in generic interface.  */
2896     }
2897
2898   if (sym->attr.intrinsic)
2899     return gfc_intrinsic_sub_interface (c, 0);
2900
2901   return MATCH_NO;
2902 }
2903
2904
2905 static gfc_try
2906 resolve_generic_s (gfc_code *c)
2907 {
2908   gfc_symbol *sym;
2909   match m;
2910
2911   sym = c->symtree->n.sym;
2912
2913   for (;;)
2914     {
2915       m = resolve_generic_s0 (c, sym);
2916       if (m == MATCH_YES)
2917         return SUCCESS;
2918       else if (m == MATCH_ERROR)
2919         return FAILURE;
2920
2921 generic:
2922       if (sym->ns->parent == NULL)
2923         break;
2924       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2925
2926       if (sym == NULL)
2927         break;
2928       if (!generic_sym (sym))
2929         goto generic;
2930     }
2931
2932   /* Last ditch attempt.  See if the reference is to an intrinsic
2933      that possesses a matching interface.  14.1.2.4  */
2934   sym = c->symtree->n.sym;
2935
2936   if (!gfc_is_intrinsic (sym, 1, c->loc))
2937     {
2938       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
2939                  sym->name, &c->loc);
2940       return FAILURE;
2941     }
2942
2943   m = gfc_intrinsic_sub_interface (c, 0);
2944   if (m == MATCH_YES)
2945     return SUCCESS;
2946   if (m == MATCH_NO)
2947     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
2948                "intrinsic subroutine interface", sym->name, &c->loc);
2949
2950   return FAILURE;
2951 }
2952
2953
2954 /* Set the name and binding label of the subroutine symbol in the call
2955    expression represented by 'c' to include the type and kind of the
2956    second parameter.  This function is for resolving the appropriate
2957    version of c_f_pointer() and c_f_procpointer().  For example, a
2958    call to c_f_pointer() for a default integer pointer could have a
2959    name of c_f_pointer_i4.  If no second arg exists, which is an error
2960    for these two functions, it defaults to the generic symbol's name
2961    and binding label.  */
2962
2963 static void
2964 set_name_and_label (gfc_code *c, gfc_symbol *sym,
2965                     char *name, char *binding_label)
2966 {
2967   gfc_expr *arg = NULL;
2968   char type;
2969   int kind;
2970
2971   /* The second arg of c_f_pointer and c_f_procpointer determines
2972      the type and kind for the procedure name.  */
2973   arg = c->ext.actual->next->expr;
2974
2975   if (arg != NULL)
2976     {
2977       /* Set up the name to have the given symbol's name,
2978          plus the type and kind.  */
2979       /* a derived type is marked with the type letter 'u' */
2980       if (arg->ts.type == BT_DERIVED)
2981         {
2982           type = 'd';
2983           kind = 0; /* set the kind as 0 for now */
2984         }
2985       else
2986         {
2987           type = gfc_type_letter (arg->ts.type);
2988           kind = arg->ts.kind;
2989         }
2990
2991       if (arg->ts.type == BT_CHARACTER)
2992         /* Kind info for character strings not needed.  */
2993         kind = 0;
2994
2995       sprintf (name, "%s_%c%d", sym->name, type, kind);
2996       /* Set up the binding label as the given symbol's label plus
2997          the type and kind.  */
2998       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
2999     }
3000   else
3001     {
3002       /* If the second arg is missing, set the name and label as
3003          was, cause it should at least be found, and the missing
3004          arg error will be caught by compare_parameters().  */
3005       sprintf (name, "%s", sym->name);
3006       sprintf (binding_label, "%s", sym->binding_label);
3007     }
3008    
3009   return;
3010 }
3011
3012
3013 /* Resolve a generic version of the iso_c_binding procedure given
3014    (sym) to the specific one based on the type and kind of the
3015    argument(s).  Currently, this function resolves c_f_pointer() and
3016    c_f_procpointer based on the type and kind of the second argument
3017    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3018    Upon successfully exiting, c->resolved_sym will hold the resolved
3019    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3020    otherwise.  */
3021
3022 match
3023 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3024 {
3025   gfc_symbol *new_sym;
3026   /* this is fine, since we know the names won't use the max */
3027   char name[GFC_MAX_SYMBOL_LEN + 1];
3028   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3029   /* default to success; will override if find error */
3030   match m = MATCH_YES;
3031
3032   /* Make sure the actual arguments are in the necessary order (based on the 
3033      formal args) before resolving.  */
3034   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3035
3036   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3037       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3038     {
3039       set_name_and_label (c, sym, name, binding_label);
3040       
3041       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3042         {
3043           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3044             {
3045               /* Make sure we got a third arg if the second arg has non-zero
3046                  rank.  We must also check that the type and rank are
3047                  correct since we short-circuit this check in
3048                  gfc_procedure_use() (called above to sort actual args).  */
3049               if (c->ext.actual->next->expr->rank != 0)
3050                 {
3051                   if(c->ext.actual->next->next == NULL 
3052                      || c->ext.actual->next->next->expr == NULL)
3053                     {
3054                       m = MATCH_ERROR;
3055                       gfc_error ("Missing SHAPE parameter for call to %s "
3056                                  "at %L", sym->name, &(c->loc));
3057                     }
3058                   else if (c->ext.actual->next->next->expr->ts.type
3059                            != BT_INTEGER
3060                            || c->ext.actual->next->next->expr->rank != 1)
3061                     {
3062                       m = MATCH_ERROR;
3063                       gfc_error ("SHAPE parameter for call to %s at %L must "
3064                                  "be a rank 1 INTEGER array", sym->name,
3065                                  &(c->loc));
3066                     }
3067                 }
3068             }
3069         }
3070       
3071       if (m != MATCH_ERROR)
3072         {
3073           /* the 1 means to add the optional arg to formal list */
3074           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3075          
3076           /* for error reporting, say it's declared where the original was */
3077           new_sym->declared_at = sym->declared_at;
3078         }
3079     }
3080   else
3081     {
3082       /* no differences for c_loc or c_funloc */
3083       new_sym = sym;
3084     }
3085
3086   /* set the resolved symbol */
3087   if (m != MATCH_ERROR)
3088     c->resolved_sym = new_sym;
3089   else
3090     c->resolved_sym = sym;
3091   
3092   return m;
3093 }
3094
3095
3096 /* Resolve a subroutine call known to be specific.  */
3097
3098 static match
3099 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3100 {
3101   match m;
3102
3103   if(sym->attr.is_iso_c)
3104     {
3105       m = gfc_iso_c_sub_interface (c,sym);
3106       return m;
3107     }
3108   
3109   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3110     {
3111       if (sym->attr.dummy)
3112         {
3113           sym->attr.proc = PROC_DUMMY;
3114           goto found;
3115         }
3116
3117       sym->attr.proc = PROC_EXTERNAL;
3118       goto found;
3119     }
3120
3121   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3122     goto found;
3123
3124   if (sym->attr.intrinsic)
3125     {
3126       m = gfc_intrinsic_sub_interface (c, 1);
3127       if (m == MATCH_YES)
3128         return MATCH_YES;
3129       if (m == MATCH_NO)
3130         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3131                    "with an intrinsic", sym->name, &c->loc);
3132
3133       return MATCH_ERROR;
3134     }
3135
3136   return MATCH_NO;
3137
3138 found:
3139   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3140
3141   c->resolved_sym = sym;
3142   pure_subroutine (c, sym);
3143
3144   return MATCH_YES;
3145 }
3146
3147
3148 static gfc_try
3149 resolve_specific_s (gfc_code *c)
3150 {
3151   gfc_symbol *sym;
3152   match m;
3153
3154   sym = c->symtree->n.sym;
3155
3156   for (;;)
3157     {
3158       m = resolve_specific_s0 (c, sym);
3159       if (m == MATCH_YES)
3160         return SUCCESS;
3161       if (m == MATCH_ERROR)
3162         return FAILURE;
3163
3164       if (sym->ns->parent == NULL)
3165         break;
3166
3167       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3168
3169       if (sym == NULL)
3170         break;
3171     }
3172
3173   sym = c->symtree->n.sym;
3174   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3175              sym->name, &c->loc);
3176
3177   return FAILURE;
3178 }
3179
3180
3181 /* Resolve a subroutine call not known to be generic nor specific.  */
3182
3183 static gfc_try
3184 resolve_unknown_s (gfc_code *c)
3185 {
3186   gfc_symbol *sym;
3187
3188   sym = c->symtree->n.sym;
3189
3190   if (sym->attr.dummy)
3191     {
3192       sym->attr.proc = PROC_DUMMY;
3193       goto found;
3194     }
3195
3196   /* See if we have an intrinsic function reference.  */
3197
3198   if (gfc_is_intrinsic (sym, 1, c->loc))
3199     {
3200       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3201         return SUCCESS;
3202       return FAILURE;
3203     }
3204
3205   /* The reference is to an external name.  */
3206
3207 found:
3208   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3209
3210   c->resolved_sym = sym;
3211
3212   pure_subroutine (c, sym);
3213
3214   return SUCCESS;
3215 }
3216
3217
3218 /* Resolve a subroutine call.  Although it was tempting to use the same code
3219    for functions, subroutines and functions are stored differently and this
3220    makes things awkward.  */
3221
3222 static gfc_try
3223 resolve_call (gfc_code *c)
3224 {
3225   gfc_try t;
3226   procedure_type ptype = PROC_INTRINSIC;
3227   gfc_symbol *csym, *sym;
3228   bool no_formal_args;
3229
3230   csym = c->symtree ? c->symtree->n.sym : NULL;
3231
3232   if (csym && csym->ts.type != BT_UNKNOWN)
3233     {
3234       gfc_error ("'%s' at %L has a type, which is not consistent with "
3235                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3236       return FAILURE;
3237     }
3238
3239   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3240     {
3241       gfc_symtree *st;
3242       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3243       sym = st ? st->n.sym : NULL;
3244       if (sym && csym != sym
3245               && sym->ns == gfc_current_ns
3246               && sym->attr.flavor == FL_PROCEDURE
3247               && sym->attr.contained)
3248         {
3249           sym->refs++;
3250           if (csym->attr.generic)
3251             c->symtree->n.sym = sym;
3252           else
3253             c->symtree = st;
3254           csym = c->symtree->n.sym;
3255         }
3256     }
3257
3258   /* If this ia a deferred TBP with an abstract interface
3259      (which may of course be referenced), c->expr1 will be set.  */
3260   if (csym && csym->attr.abstract && !c->expr1)
3261     {
3262       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3263                  csym->name, &c->loc);
3264       return FAILURE;
3265     }
3266
3267   /* Subroutines without the RECURSIVE attribution are not allowed to
3268    * call themselves.  */
3269   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3270     {
3271       if (csym->attr.entry && csym->ns->entries)
3272         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3273                    " subroutine '%s' is not RECURSIVE",
3274                    csym->name, &c->loc, csym->ns->entries->sym->name);
3275       else
3276         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3277                    " is not RECURSIVE", csym->name, &c->loc);
3278
3279       t = FAILURE;
3280     }
3281
3282   /* Switch off assumed size checking and do this again for certain kinds
3283      of procedure, once the procedure itself is resolved.  */
3284   need_full_assumed_size++;
3285
3286   if (csym)
3287     ptype = csym->attr.proc;
3288
3289   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3290   if (resolve_actual_arglist (c->ext.actual, ptype,
3291                               no_formal_args) == FAILURE)
3292     return FAILURE;
3293
3294   /* Resume assumed_size checking.  */
3295   need_full_assumed_size--;
3296
3297   /* If external, check for usage.  */
3298   if (csym && is_external_proc (csym))
3299     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3300
3301   t = SUCCESS;
3302   if (c->resolved_sym == NULL)
3303     {
3304       c->resolved_isym = NULL;
3305       switch (procedure_kind (csym))
3306         {
3307         case PTYPE_GENERIC:
3308           t = resolve_generic_s (c);
3309           break;
3310
3311         case PTYPE_SPECIFIC:
3312           t = resolve_specific_s (c);
3313           break;
3314
3315         case PTYPE_UNKNOWN:
3316           t = resolve_unknown_s (c);
3317           break;
3318
3319         default:
3320           gfc_internal_error ("resolve_subroutine(): bad function type");
3321         }
3322     }
3323
3324   /* Some checks of elemental subroutine actual arguments.  */
3325   if (resolve_elemental_actual (NULL, c) == FAILURE)
3326     return FAILURE;
3327
3328   if (t == SUCCESS && !(c->resolved_sym && c->resolved_sym->attr.elemental))
3329     find_noncopying_intrinsics (c->resolved_sym, c->ext.actual);
3330   return t;
3331 }
3332
3333
3334 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3335    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3336    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3337    if their shapes do not match.  If either op1->shape or op2->shape is
3338    NULL, return SUCCESS.  */
3339
3340 static gfc_try
3341 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3342 {
3343   gfc_try t;
3344   int i;
3345
3346   t = SUCCESS;
3347
3348   if (op1->shape != NULL && op2->shape != NULL)
3349     {
3350       for (i = 0; i < op1->rank; i++)
3351         {
3352           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3353            {
3354              gfc_error ("Shapes for operands at %L and %L are not conformable",
3355                          &op1->where, &op2->where);
3356              t = FAILURE;
3357              break;
3358            }
3359         }
3360     }
3361
3362   return t;
3363 }
3364
3365
3366 /* Resolve an operator expression node.  This can involve replacing the
3367    operation with a user defined function call.  */
3368
3369 static gfc_try
3370 resolve_operator (gfc_expr *e)
3371 {
3372   gfc_expr *op1, *op2;
3373   char msg[200];
3374   bool dual_locus_error;
3375   gfc_try t;
3376
3377   /* Resolve all subnodes-- give them types.  */
3378
3379   switch (e->value.op.op)
3380     {
3381     default:
3382       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3383         return FAILURE;
3384
3385     /* Fall through...  */
3386
3387     case INTRINSIC_NOT:
3388     case INTRINSIC_UPLUS:
3389     case INTRINSIC_UMINUS:
3390     case INTRINSIC_PARENTHESES:
3391       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3392         return FAILURE;
3393       break;
3394     }
3395
3396   /* Typecheck the new node.  */
3397
3398   op1 = e->value.op.op1;
3399   op2 = e->value.op.op2;
3400   dual_locus_error = false;
3401
3402   if ((op1 && op1->expr_type == EXPR_NULL)
3403       || (op2 && op2->expr_type == EXPR_NULL))
3404     {
3405       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3406       goto bad_op;
3407     }
3408
3409   switch (e->value.op.op)
3410     {
3411     case INTRINSIC_UPLUS:
3412     case INTRINSIC_UMINUS:
3413       if (op1->ts.type == BT_INTEGER
3414           || op1->ts.type == BT_REAL
3415           || op1->ts.type == BT_COMPLEX)
3416         {
3417           e->ts = op1->ts;
3418           break;
3419         }
3420
3421       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3422                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3423       goto bad_op;
3424
3425     case INTRINSIC_PLUS:
3426     case INTRINSIC_MINUS:
3427     case INTRINSIC_TIMES:
3428     case INTRINSIC_DIVIDE:
3429     case INTRINSIC_POWER:
3430       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3431         {
3432           gfc_type_convert_binary (e, 1);
3433           break;
3434         }
3435
3436       sprintf (msg,
3437                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3438                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3439                gfc_typename (&op2->ts));
3440       goto bad_op;
3441
3442     case INTRINSIC_CONCAT:
3443       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3444           && op1->ts.kind == op2->ts.kind)
3445         {
3446           e->ts.type = BT_CHARACTER;
3447           e->ts.kind = op1->ts.kind;
3448           break;
3449         }
3450
3451       sprintf (msg,
3452                _("Operands of string concatenation operator at %%L are %s/%s"),
3453                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3454       goto bad_op;
3455
3456     case INTRINSIC_AND:
3457     case INTRINSIC_OR:
3458     case INTRINSIC_EQV:
3459     case INTRINSIC_NEQV:
3460       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3461         {
3462           e->ts.type = BT_LOGICAL;
3463           e->ts.kind = gfc_kind_max (op1, op2);
3464           if (op1->ts.kind < e->ts.kind)
3465             gfc_convert_type (op1, &e->ts, 2);
3466           else if (op2->ts.kind < e->ts.kind)
3467             gfc_convert_type (op2, &e->ts, 2);
3468           break;
3469         }
3470
3471       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3472                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3473                gfc_typename (&op2->ts));
3474
3475       goto bad_op;
3476
3477     case INTRINSIC_NOT:
3478       if (op1->ts.type == BT_LOGICAL)
3479         {
3480           e->ts.type = BT_LOGICAL;
3481           e->ts.kind = op1->ts.kind;
3482           break;
3483         }
3484
3485       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3486                gfc_typename (&op1->ts));
3487       goto bad_op;
3488
3489     case INTRINSIC_GT:
3490     case INTRINSIC_GT_OS:
3491     case INTRINSIC_GE:
3492     case INTRINSIC_GE_OS:
3493     case INTRINSIC_LT:
3494     case INTRINSIC_LT_OS:
3495     case INTRINSIC_LE:
3496     case INTRINSIC_LE_OS:
3497       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3498         {
3499           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3500           goto bad_op;
3501         }
3502
3503       /* Fall through...  */
3504
3505     case INTRINSIC_EQ:
3506     case INTRINSIC_EQ_OS:
3507     case INTRINSIC_NE:
3508     case INTRINSIC_NE_OS:
3509       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3510           && op1->ts.kind == op2->ts.kind)
3511         {
3512           e->ts.type = BT_LOGICAL;
3513           e->ts.kind = gfc_default_logical_kind;
3514           break;
3515         }
3516
3517       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3518         {
3519           gfc_type_convert_binary (e, 1);
3520
3521           e->ts.type = BT_LOGICAL;
3522           e->ts.kind = gfc_default_logical_kind;
3523           break;
3524         }
3525
3526       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3527         sprintf (msg,
3528                  _("Logicals at %%L must be compared with %s instead of %s"),
3529                  (e->value.op.op == INTRINSIC_EQ 
3530                   || e->value.op.op == INTRINSIC_EQ_OS)
3531                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3532       else
3533         sprintf (msg,
3534                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3535                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3536                  gfc_typename (&op2->ts));
3537
3538       goto bad_op;
3539
3540     case INTRINSIC_USER:
3541       if (e->value.op.uop->op == NULL)
3542         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3543       else if (op2 == NULL)
3544         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3545                  e->value.op.uop->name, gfc_typename (&op1->ts));
3546       else
3547         sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3548                  e->value.op.uop->name, gfc_typename (&op1->ts),
3549                  gfc_typename (&op2->ts));
3550
3551       goto bad_op;
3552
3553     case INTRINSIC_PARENTHESES:
3554       e->ts = op1->ts;
3555       if (e->ts.type == BT_CHARACTER)
3556         e->ts.u.cl = op1->ts.u.cl;
3557       break;
3558
3559     default:
3560       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3561     }
3562
3563   /* Deal with arrayness of an operand through an operator.  */
3564
3565   t = SUCCESS;
3566
3567   switch (e->value.op.op)
3568     {
3569     case INTRINSIC_PLUS:
3570     case INTRINSIC_MINUS:
3571     case INTRINSIC_TIMES:
3572     case INTRINSIC_DIVIDE:
3573     case INTRINSIC_POWER:
3574     case INTRINSIC_CONCAT:
3575     case INTRINSIC_AND:
3576     case INTRINSIC_OR:
3577     case INTRINSIC_EQV:
3578     case INTRINSIC_NEQV:
3579     case INTRINSIC_EQ:
3580     case INTRINSIC_EQ_OS:
3581     case INTRINSIC_NE:
3582     case INTRINSIC_NE_OS:
3583     case INTRINSIC_GT:
3584     case INTRINSIC_GT_OS:
3585     case INTRINSIC_GE:
3586     case INTRINSIC_GE_OS:
3587     case INTRINSIC_LT:
3588     case INTRINSIC_LT_OS:
3589     case INTRINSIC_LE:
3590     case INTRINSIC_LE_OS:
3591
3592       if (op1->rank == 0 && op2->rank == 0)
3593         e->rank = 0;
3594
3595       if (op1->rank == 0 && op2->rank != 0)
3596         {
3597           e->rank = op2->rank;
3598
3599           if (e->shape == NULL)
3600             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3601         }
3602
3603       if (op1->rank != 0 && op2->rank == 0)
3604         {
3605           e->rank = op1->rank;
3606
3607           if (e->shape == NULL)
3608             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3609         }
3610
3611       if (op1->rank != 0 && op2->rank != 0)
3612         {
3613           if (op1->rank == op2->rank)
3614             {
3615               e->rank = op1->rank;
3616               if (e->shape == NULL)
3617                 {
3618                   t = compare_shapes(op1, op2);
3619                   if (t == FAILURE)
3620                     e->shape = NULL;
3621                   else
3622                 e->shape = gfc_copy_shape (op1->shape, op1->rank);
3623                 }
3624             }
3625           else
3626             {
3627               /* Allow higher level expressions to work.  */
3628               e->rank = 0;
3629
3630               /* Try user-defined operators, and otherwise throw an error.  */
3631               dual_locus_error = true;
3632               sprintf (msg,
3633                        _("Inconsistent ranks for operator at %%L and %%L"));
3634               goto bad_op;
3635             }
3636         }
3637
3638       break;
3639
3640     case INTRINSIC_PARENTHESES:
3641     case INTRINSIC_NOT:
3642     case INTRINSIC_UPLUS:
3643     case INTRINSIC_UMINUS:
3644       /* Simply copy arrayness attribute */
3645       e->rank = op1->rank;
3646
3647       if (e->shape == NULL)
3648         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3649
3650       break;
3651
3652     default:
3653       break;
3654     }
3655
3656   /* Attempt to simplify the expression.  */
3657   if (t == SUCCESS)
3658     {
3659       t = gfc_simplify_expr (e, 0);
3660       /* Some calls do not succeed in simplification and return FAILURE
3661          even though there is no error; e.g. variable references to
3662          PARAMETER arrays.  */
3663       if (!gfc_is_constant_expr (e))
3664         t = SUCCESS;
3665     }
3666   return t;
3667
3668 bad_op:
3669
3670   {
3671     bool real_error;
3672     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3673       return SUCCESS;
3674
3675     if (real_error)
3676       return FAILURE;
3677   }
3678
3679   if (dual_locus_error)
3680     gfc_error (msg, &op1->where, &op2->where);
3681   else
3682     gfc_error (msg, &e->where);
3683
3684   return FAILURE;
3685 }
3686
3687
3688 /************** Array resolution subroutines **************/
3689
3690 typedef enum
3691 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3692 comparison;
3693
3694 /* Compare two integer expressions.  */
3695
3696 static comparison
3697 compare_bound (gfc_expr *a, gfc_expr *b)
3698 {
3699   int i;
3700
3701   if (a == NULL || a->expr_type != EXPR_CONSTANT
3702       || b == NULL || b->expr_type != EXPR_CONSTANT)
3703     return CMP_UNKNOWN;
3704
3705   /* If either of the types isn't INTEGER, we must have
3706      raised an error earlier.  */
3707
3708   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3709     return CMP_UNKNOWN;
3710
3711   i = mpz_cmp (a->value.integer, b->value.integer);
3712
3713   if (i < 0)
3714     return CMP_LT;
3715   if (i > 0)
3716     return CMP_GT;
3717   return CMP_EQ;
3718 }
3719
3720
3721 /* Compare an integer expression with an integer.  */
3722
3723 static comparison
3724 compare_bound_int (gfc_expr *a, int b)
3725 {
3726   int i;
3727
3728   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3729     return CMP_UNKNOWN;
3730
3731   if (a->ts.type != BT_INTEGER)
3732     gfc_internal_error ("compare_bound_int(): Bad expression");
3733
3734   i = mpz_cmp_si (a->value.integer, b);
3735
3736   if (i < 0)
3737     return CMP_LT;
3738   if (i > 0)
3739     return CMP_GT;
3740   return CMP_EQ;
3741 }
3742
3743
3744 /* Compare an integer expression with a mpz_t.  */
3745
3746 static comparison
3747 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
3748 {
3749   int i;
3750
3751   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3752     return CMP_UNKNOWN;
3753
3754   if (a->ts.type != BT_INTEGER)
3755     gfc_internal_error ("compare_bound_int(): Bad expression");
3756
3757   i = mpz_cmp (a->value.integer, b);
3758
3759   if (i < 0)
3760     return CMP_LT;
3761   if (i > 0)
3762     return CMP_GT;
3763   return CMP_EQ;
3764 }
3765
3766
3767 /* Compute the last value of a sequence given by a triplet.  
3768    Return 0 if it wasn't able to compute the last value, or if the
3769    sequence if empty, and 1 otherwise.  */
3770
3771 static int
3772 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
3773                                 gfc_expr *stride, mpz_t last)
3774 {
3775   mpz_t rem;
3776
3777   if (start == NULL || start->expr_type != EXPR_CONSTANT
3778       || end == NULL || end->expr_type != EXPR_CONSTANT
3779       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
3780     return 0;
3781
3782   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
3783       || (stride != NULL && stride->ts.type != BT_INTEGER))
3784     return 0;
3785
3786   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
3787     {
3788       if (compare_bound (start, end) == CMP_GT)
3789         return 0;
3790       mpz_set (last, end->value.integer);
3791       return 1;
3792     }
3793
3794   if (compare_bound_int (stride, 0) == CMP_GT)
3795     {
3796       /* Stride is positive */
3797       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
3798         return 0;
3799     }
3800   else
3801     {
3802       /* Stride is negative */
3803       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
3804         return 0;
3805     }
3806
3807   mpz_init (rem);
3808   mpz_sub (rem, end->value.integer, start->value.integer);
3809   mpz_tdiv_r (rem, rem, stride->value.integer);
3810   mpz_sub (last, end->value.integer, rem);
3811   mpz_clear (rem);
3812
3813   return 1;
3814 }
3815
3816
3817 /* Compare a single dimension of an array reference to the array
3818    specification.  */
3819
3820 static gfc_try
3821 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
3822 {
3823   mpz_t last_value;
3824
3825   if (ar->dimen_type[i] == DIMEN_STAR)
3826     {
3827       gcc_assert (ar->stride[i] == NULL);
3828       /* This implies [*] as [*:] and [*:3] are not possible.  */
3829       if (ar->start[i] == NULL)
3830         {
3831           gcc_assert (ar->end[i] == NULL);
3832           return SUCCESS;
3833         }
3834     }
3835
3836 /* Given start, end and stride values, calculate the minimum and
3837    maximum referenced indexes.  */
3838
3839   switch (ar->dimen_type[i])
3840     {
3841     case DIMEN_VECTOR:
3842       break;
3843
3844     case DIMEN_STAR:
3845     case DIMEN_ELEMENT:
3846       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
3847         {
3848           if (i < as->rank)
3849             gfc_warning ("Array reference at %L is out of bounds "
3850                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
3851                          mpz_get_si (ar->start[i]->value.integer),
3852                          mpz_get_si (as->lower[i]->value.integer), i+1);
3853           else
3854             gfc_warning ("Array reference at %L is out of bounds "
3855                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
3856                          mpz_get_si (ar->start[i]->value.integer),
3857                          mpz_get_si (as->lower[i]->value.integer),
3858                          i + 1 - as->rank);
3859           return SUCCESS;
3860         }
3861       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
3862         {
3863           if (i < as->rank)
3864             gfc_warning ("Array reference at %L is out of bounds "
3865                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
3866                          mpz_get_si (ar->start[i]->value.integer),
3867                          mpz_get_si (as->upper[i]->value.integer), i+1);
3868           else
3869             gfc_warning ("Array reference at %L is out of bounds "
3870                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
3871                          mpz_get_si (ar->start[i]->value.integer),
3872                          mpz_get_si (as->upper[i]->value.integer),
3873                          i + 1 - as->rank);
3874           return SUCCESS;
3875         }
3876
3877       break;
3878
3879     case DIMEN_RANGE:
3880       {
3881 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
3882 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
3883
3884         comparison comp_start_end = compare_bound (AR_START, AR_END);
3885
3886         /* Check for zero stride, which is not allowed.  */
3887         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
3888           {
3889             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
3890             return FAILURE;
3891           }
3892
3893         /* if start == len || (stride > 0 && start < len)
3894                            || (stride < 0 && start > len),
3895            then the array section contains at least one element.  In this
3896            case, there is an out-of-bounds access if
3897            (start < lower || start > upper).  */
3898         if (compare_bound (AR_START, AR_END) == CMP_EQ
3899             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
3900                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
3901             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
3902                 && comp_start_end == CMP_GT))
3903           {
3904             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
3905               {
3906                 gfc_warning ("Lower array reference at %L is out of bounds "
3907                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3908                        mpz_get_si (AR_START->value.integer),
3909                        mpz_get_si (as->lower[i]->value.integer), i+1);
3910                 return SUCCESS;
3911               }
3912             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
3913               {
3914                 gfc_warning ("Lower array reference at %L is out of bounds "
3915                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3916                        mpz_get_si (AR_START->value.integer),
3917                        mpz_get_si (as->upper[i]->value.integer), i+1);
3918                 return SUCCESS;
3919               }
3920           }
3921
3922         /* If we can compute the highest index of the array section,
3923            then it also has to be between lower and upper.  */
3924         mpz_init (last_value);
3925         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
3926                                             last_value))
3927           {
3928             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
3929               {
3930                 gfc_warning ("Upper array reference at %L is out of bounds "
3931                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
3932                        mpz_get_si (last_value),
3933                        mpz_get_si (as->lower[i]->value.integer), i+1);
3934                 mpz_clear (last_value);
3935                 return SUCCESS;
3936               }
3937             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
3938               {
3939                 gfc_warning ("Upper array reference at %L is out of bounds "
3940                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
3941                        mpz_get_si (last_value),
3942                        mpz_get_si (as->upper[i]->value.integer), i+1);
3943                 mpz_clear (last_value);
3944                 return SUCCESS;
3945               }
3946           }
3947         mpz_clear (last_value);
3948
3949 #undef AR_START
3950 #undef AR_END
3951       }
3952       break;
3953
3954     default:
3955       gfc_internal_error ("check_dimension(): Bad array reference");
3956     }
3957
3958   return SUCCESS;
3959 }
3960
3961
3962 /* Compare an array reference with an array specification.  */
3963
3964 static gfc_try
3965 compare_spec_to_ref (gfc_array_ref *ar)
3966 {
3967   gfc_array_spec *as;
3968   int i;
3969
3970   as = ar->as;
3971   i = as->rank - 1;
3972   /* TODO: Full array sections are only allowed as actual parameters.  */
3973   if (as->type == AS_ASSUMED_SIZE
3974       && (/*ar->type == AR_FULL
3975           ||*/ (ar->type == AR_SECTION
3976               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
3977     {
3978       gfc_error ("Rightmost upper bound of assumed size array section "
3979                  "not specified at %L", &ar->where);
3980       return FAILURE;
3981     }
3982
3983   if (ar->type == AR_FULL)
3984     return SUCCESS;
3985
3986   if (as->rank != ar->dimen)
3987     {
3988       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
3989                  &ar->where, ar->dimen, as->rank);
3990       return FAILURE;
3991     }
3992
3993   /* ar->codimen == 0 is a local array.  */
3994   if (as->corank != ar->codimen && ar->codimen != 0)
3995     {
3996       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
3997                  &ar->where, ar->codimen, as->corank);
3998       return FAILURE;
3999     }
4000
4001   for (i = 0; i < as->rank; i++)
4002     if (check_dimension (i, ar, as) == FAILURE)
4003       return FAILURE;
4004
4005   /* Local access has no coarray spec.  */
4006   if (ar->codimen != 0)
4007     for (i = as->rank; i < as->rank + as->corank; i++)
4008       {
4009         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate)
4010           {
4011             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4012                        i + 1 - as->rank, &ar->where);
4013             return FAILURE;
4014           }
4015         if (check_dimension (i, ar, as) == FAILURE)
4016           return FAILURE;
4017       }
4018
4019   return SUCCESS;
4020 }
4021
4022
4023 /* Resolve one part of an array index.  */
4024
4025 static gfc_try
4026 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4027                      int force_index_integer_kind)
4028 {
4029   gfc_typespec ts;
4030
4031   if (index == NULL)
4032     return SUCCESS;
4033
4034   if (gfc_resolve_expr (index) == FAILURE)
4035     return FAILURE;
4036
4037   if (check_scalar && index->rank != 0)
4038     {
4039       gfc_error ("Array index at %L must be scalar", &index->where);
4040       return FAILURE;
4041     }
4042
4043   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4044     {
4045       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4046                  &index->where, gfc_basic_typename (index->ts.type));
4047       return FAILURE;
4048     }
4049
4050   if (index->ts.type == BT_REAL)
4051     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4052                         &index->where) == FAILURE)
4053       return FAILURE;
4054
4055   if ((index->ts.kind != gfc_index_integer_kind
4056        && force_index_integer_kind)
4057       || index->ts.type != BT_INTEGER)
4058     {
4059       gfc_clear_ts (&ts);
4060       ts.type = BT_INTEGER;
4061       ts.kind = gfc_index_integer_kind;
4062
4063       gfc_convert_type_warn (index, &ts, 2, 0);
4064     }
4065
4066   return SUCCESS;
4067 }
4068
4069 /* Resolve one part of an array index.  */
4070
4071 gfc_try
4072 gfc_resolve_index (gfc_expr *index, int check_scalar)
4073 {
4074   return gfc_resolve_index_1 (index, check_scalar, 1);
4075 }
4076
4077 /* Resolve a dim argument to an intrinsic function.  */
4078
4079 gfc_try
4080 gfc_resolve_dim_arg (gfc_expr *dim)
4081 {
4082   if (dim == NULL)
4083     return SUCCESS;
4084
4085   if (gfc_resolve_expr (dim) == FAILURE)
4086     return FAILURE;
4087
4088   if (dim->rank != 0)
4089     {
4090       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4091       return FAILURE;
4092
4093     }
4094
4095   if (dim->ts.type != BT_INTEGER)
4096     {
4097       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4098       return FAILURE;
4099     }
4100
4101   if (dim->ts.kind != gfc_index_integer_kind)
4102     {
4103       gfc_typespec ts;
4104
4105       gfc_clear_ts (&ts);
4106       ts.type = BT_INTEGER;
4107       ts.kind = gfc_index_integer_kind;
4108
4109       gfc_convert_type_warn (dim, &ts, 2, 0);
4110     }
4111
4112   return SUCCESS;
4113 }
4114
4115 /* Given an expression that contains array references, update those array
4116    references to point to the right array specifications.  While this is
4117    filled in during matching, this information is difficult to save and load
4118    in a module, so we take care of it here.
4119
4120    The idea here is that the original array reference comes from the
4121    base symbol.  We traverse the list of reference structures, setting
4122    the stored reference to references.  Component references can
4123    provide an additional array specification.  */
4124
4125 static void
4126 find_array_spec (gfc_expr *e)
4127 {
4128   gfc_array_spec *as;
4129   gfc_component *c;
4130   gfc_symbol *derived;
4131   gfc_ref *ref;
4132
4133   if (e->symtree->n.sym->ts.type == BT_CLASS)
4134     as = CLASS_DATA (e->symtree->n.sym)->as;
4135   else
4136     as = e->symtree->n.sym->as;
4137   derived = NULL;
4138
4139   for (ref = e->ref; ref; ref = ref->next)
4140     switch (ref->type)
4141       {
4142       case REF_ARRAY:
4143         if (as == NULL)
4144           gfc_internal_error ("find_array_spec(): Missing spec");
4145
4146         ref->u.ar.as = as;
4147         as = NULL;
4148         break;
4149
4150       case REF_COMPONENT:
4151         if (derived == NULL)
4152           derived = e->symtree->n.sym->ts.u.derived;
4153
4154         if (derived->attr.is_class)
4155           derived = derived->components->ts.u.derived;
4156
4157         c = derived->components;
4158
4159         for (; c; c = c->next)
4160           if (c == ref->u.c.component)
4161             {
4162               /* Track the sequence of component references.  */
4163               if (c->ts.type == BT_DERIVED)
4164                 derived = c->ts.u.derived;
4165               break;
4166             }
4167
4168         if (c == NULL)
4169           gfc_internal_error ("find_array_spec(): Component not found");
4170
4171         if (c->attr.dimension)
4172           {
4173             if (as != NULL)
4174               gfc_internal_error ("find_array_spec(): unused as(1)");
4175             as = c->as;
4176           }
4177
4178         break;
4179
4180       case REF_SUBSTRING:
4181         break;
4182       }
4183
4184   if (as != NULL)
4185     gfc_internal_error ("find_array_spec(): unused as(2)");
4186 }
4187
4188
4189 /* Resolve an array reference.  */
4190
4191 static gfc_try
4192 resolve_array_ref (gfc_array_ref *ar)
4193 {
4194   int i, check_scalar;
4195   gfc_expr *e;
4196
4197   for (i = 0; i < ar->dimen + ar->codimen; i++)
4198     {
4199       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4200
4201       /* Do not force gfc_index_integer_kind for the start.  We can
4202          do fine with any integer kind.  This avoids temporary arrays
4203          created for indexing with a vector.  */
4204       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4205         return FAILURE;
4206       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4207         return FAILURE;
4208       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4209         return FAILURE;
4210
4211       e = ar->start[i];
4212
4213       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4214         switch (e->rank)
4215           {
4216           case 0:
4217             ar->dimen_type[i] = DIMEN_ELEMENT;
4218             break;
4219
4220           case 1:
4221             ar->dimen_type[i] = DIMEN_VECTOR;
4222             if (e->expr_type == EXPR_VARIABLE
4223                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4224               ar->start[i] = gfc_get_parentheses (e);
4225             break;
4226
4227           default:
4228             gfc_error ("Array index at %L is an array of rank %d",
4229                        &ar->c_where[i], e->rank);
4230             return FAILURE;
4231           }
4232     }
4233
4234   if (ar->type == AR_FULL && ar->as->rank == 0)
4235     ar->type = AR_ELEMENT;
4236
4237   /* If the reference type is unknown, figure out what kind it is.  */
4238
4239   if (ar->type == AR_UNKNOWN)
4240     {
4241       ar->type = AR_ELEMENT;
4242       for (i = 0; i < ar->dimen; i++)
4243         if (ar->dimen_type[i] == DIMEN_RANGE
4244             || ar->dimen_type[i] == DIMEN_VECTOR)
4245           {
4246             ar->type = AR_SECTION;
4247             break;
4248           }
4249     }
4250
4251   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4252     return FAILURE;
4253
4254   return SUCCESS;
4255 }
4256
4257
4258 static gfc_try
4259 resolve_substring (gfc_ref *ref)
4260 {
4261   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4262
4263   if (ref->u.ss.start != NULL)
4264     {
4265       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4266         return FAILURE;
4267
4268       if (ref->u.ss.start->ts.type != BT_INTEGER)
4269         {
4270           gfc_error ("Substring start index at %L must be of type INTEGER",
4271                      &ref->u.ss.start->where);
4272           return FAILURE;
4273         }
4274
4275       if (ref->u.ss.start->rank != 0)
4276         {
4277           gfc_error ("Substring start index at %L must be scalar",
4278                      &ref->u.ss.start->where);
4279           return FAILURE;
4280         }
4281
4282       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4283           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4284               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4285         {
4286           gfc_error ("Substring start index at %L is less than one",
4287                      &ref->u.ss.start->where);
4288           return FAILURE;
4289         }
4290     }
4291
4292   if (ref->u.ss.end != NULL)
4293     {
4294       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4295         return FAILURE;
4296
4297       if (ref->u.ss.end->ts.type != BT_INTEGER)
4298         {
4299           gfc_error ("Substring end index at %L must be of type INTEGER",
4300                      &ref->u.ss.end->where);
4301           return FAILURE;
4302         }
4303
4304       if (ref->u.ss.end->rank != 0)
4305         {
4306           gfc_error ("Substring end index at %L must be scalar",
4307                      &ref->u.ss.end->where);
4308           return FAILURE;
4309         }
4310
4311       if (ref->u.ss.length != NULL
4312           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4313           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4314               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4315         {
4316           gfc_error ("Substring end index at %L exceeds the string length",
4317                      &ref->u.ss.start->where);
4318           return FAILURE;
4319         }
4320
4321       if (compare_bound_mpz_t (ref->u.ss.end,
4322                                gfc_integer_kinds[k].huge) == CMP_GT
4323           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4324               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4325         {
4326           gfc_error ("Substring end index at %L is too large",
4327                      &ref->u.ss.end->where);
4328           return FAILURE;
4329         }
4330     }
4331
4332   return SUCCESS;
4333 }
4334
4335
4336 /* This function supplies missing substring charlens.  */
4337
4338 void
4339 gfc_resolve_substring_charlen (gfc_expr *e)
4340 {
4341   gfc_ref *char_ref;
4342   gfc_expr *start, *end;
4343
4344   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4345     if (char_ref->type == REF_SUBSTRING)
4346       break;
4347
4348   if (!char_ref)
4349     return;
4350
4351   gcc_assert (char_ref->next == NULL);
4352
4353   if (e->ts.u.cl)
4354     {
4355       if (e->ts.u.cl->length)
4356         gfc_free_expr (e->ts.u.cl->length);
4357       else if (e->expr_type == EXPR_VARIABLE
4358                  && e->symtree->n.sym->attr.dummy)
4359         return;
4360     }
4361
4362   e->ts.type = BT_CHARACTER;
4363   e->ts.kind = gfc_default_character_kind;
4364
4365   if (!e->ts.u.cl)
4366     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4367
4368   if (char_ref->u.ss.start)
4369     start = gfc_copy_expr (char_ref->u.ss.start);
4370   else
4371     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4372
4373   if (char_ref->u.ss.end)
4374     end = gfc_copy_expr (char_ref->u.ss.end);
4375   else if (e->expr_type == EXPR_VARIABLE)
4376     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4377   else
4378     end = NULL;
4379
4380   if (!start || !end)
4381     return;
4382
4383   /* Length = (end - start +1).  */
4384   e->ts.u.cl->length = gfc_subtract (end, start);
4385   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4386                                 gfc_get_int_expr (gfc_default_integer_kind,
4387                                                   NULL, 1));
4388
4389   e->ts.u.cl->length->ts.type = BT_INTEGER;
4390   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4391
4392   /* Make sure that the length is simplified.  */
4393   gfc_simplify_expr (e->ts.u.cl->length, 1);
4394   gfc_resolve_expr (e->ts.u.cl->length);
4395 }
4396
4397
4398 /* Resolve subtype references.  */
4399
4400 static gfc_try
4401 resolve_ref (gfc_expr *expr)
4402 {
4403   int current_part_dimension, n_components, seen_part_dimension;
4404   gfc_ref *ref;
4405
4406   for (ref = expr->ref; ref; ref = ref->next)
4407     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4408       {
4409         find_array_spec (expr);
4410         break;
4411       }
4412
4413   for (ref = expr->ref; ref; ref = ref->next)
4414     switch (ref->type)
4415       {
4416       case REF_ARRAY:
4417         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4418           return FAILURE;
4419         break;
4420
4421       case REF_COMPONENT:
4422         break;
4423
4424       case REF_SUBSTRING:
4425         resolve_substring (ref);
4426         break;
4427       }
4428
4429   /* Check constraints on part references.  */
4430
4431   current_part_dimension = 0;
4432   seen_part_dimension = 0;
4433   n_components = 0;
4434
4435   for (ref = expr->ref; ref; ref = ref->next)
4436     {
4437       switch (ref->type)
4438         {
4439         case REF_ARRAY:
4440           switch (ref->u.ar.type)
4441             {
4442             case AR_FULL:
4443               /* Coarray scalar.  */
4444               if (ref->u.ar.as->rank == 0)
4445                 {
4446                   current_part_dimension = 0;
4447                   break;
4448                 }
4449               /* Fall through.  */
4450             case AR_SECTION:
4451               current_part_dimension = 1;
4452               break;
4453
4454             case AR_ELEMENT:
4455               current_part_dimension = 0;
4456               break;
4457
4458             case AR_UNKNOWN:
4459               gfc_internal_error ("resolve_ref(): Bad array reference");
4460             }
4461
4462           break;
4463
4464         case REF_COMPONENT:
4465           if (current_part_dimension || seen_part_dimension)
4466             {
4467               /* F03:C614.  */
4468               if (ref->u.c.component->attr.pointer
4469                   || ref->u.c.component->attr.proc_pointer)
4470                 {
4471                   gfc_error ("Component to the right of a part reference "
4472                              "with nonzero rank must not have the POINTER "
4473                              "attribute at %L", &expr->where);
4474                   return FAILURE;
4475                 }
4476               else if (ref->u.c.component->attr.allocatable)
4477                 {
4478                   gfc_error ("Component to the right of a part reference "
4479                              "with nonzero rank must not have the ALLOCATABLE "
4480                              "attribute at %L", &expr->where);
4481                   return FAILURE;
4482                 }
4483             }
4484
4485           n_components++;
4486           break;
4487
4488         case REF_SUBSTRING:
4489           break;
4490         }
4491
4492       if (((ref->type == REF_COMPONENT && n_components > 1)
4493            || ref->next == NULL)
4494           && current_part_dimension
4495           && seen_part_dimension)
4496         {
4497           gfc_error ("Two or more part references with nonzero rank must "
4498                      "not be specified at %L", &expr->where);
4499           return FAILURE;
4500         }
4501
4502       if (ref->type == REF_COMPONENT)
4503         {
4504           if (current_part_dimension)
4505             seen_part_dimension = 1;
4506
4507           /* reset to make sure */
4508           current_part_dimension = 0;
4509         }
4510     }
4511
4512   return SUCCESS;
4513 }
4514
4515
4516 /* Given an expression, determine its shape.  This is easier than it sounds.
4517    Leaves the shape array NULL if it is not possible to determine the shape.  */
4518
4519 static void
4520 expression_shape (gfc_expr *e)
4521 {
4522   mpz_t array[GFC_MAX_DIMENSIONS];
4523   int i;
4524
4525   if (e->rank == 0 || e->shape != NULL)
4526     return;
4527
4528   for (i = 0; i < e->rank; i++)
4529     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4530       goto fail;
4531
4532   e->shape = gfc_get_shape (e->rank);
4533
4534   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4535
4536   return;
4537
4538 fail:
4539   for (i--; i >= 0; i--)
4540     mpz_clear (array[i]);
4541 }
4542
4543
4544 /* Given a variable expression node, compute the rank of the expression by
4545    examining the base symbol and any reference structures it may have.  */
4546
4547 static void
4548 expression_rank (gfc_expr *e)
4549 {
4550   gfc_ref *ref;
4551   int i, rank;
4552
4553   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4554      could lead to serious confusion...  */
4555   gcc_assert (e->expr_type != EXPR_COMPCALL);
4556
4557   if (e->ref == NULL)
4558     {
4559       if (e->expr_type == EXPR_ARRAY)
4560         goto done;
4561       /* Constructors can have a rank different from one via RESHAPE().  */
4562
4563       if (e->symtree == NULL)
4564         {
4565           e->rank = 0;
4566           goto done;
4567         }
4568
4569       e->rank = (e->symtree->n.sym->as == NULL)
4570                 ? 0 : e->symtree->n.sym->as->rank;
4571       goto done;
4572     }
4573
4574   rank = 0;
4575
4576   for (ref = e->ref; ref; ref = ref->next)
4577     {
4578       if (ref->type != REF_ARRAY)
4579         continue;
4580
4581       if (ref->u.ar.type == AR_FULL)
4582         {
4583           rank = ref->u.ar.as->rank;
4584           break;
4585         }
4586
4587       if (ref->u.ar.type == AR_SECTION)
4588         {
4589           /* Figure out the rank of the section.  */
4590           if (rank != 0)
4591             gfc_internal_error ("expression_rank(): Two array specs");
4592
4593           for (i = 0; i < ref->u.ar.dimen; i++)
4594             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4595                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4596               rank++;
4597
4598           break;
4599         }
4600     }
4601
4602   e->rank = rank;
4603
4604 done:
4605   expression_shape (e);
4606 }
4607
4608
4609 /* Resolve a variable expression.  */
4610
4611 static gfc_try
4612 resolve_variable (gfc_expr *e)
4613 {
4614   gfc_symbol *sym;
4615   gfc_try t;
4616
4617   t = SUCCESS;
4618
4619   if (e->symtree == NULL)
4620     return FAILURE;
4621
4622   if (e->ref && resolve_ref (e) == FAILURE)
4623     return FAILURE;
4624
4625   sym = e->symtree->n.sym;
4626   if (sym->attr.flavor == FL_PROCEDURE
4627       && (!sym->attr.function
4628           || (sym->attr.function && sym->result
4629               && sym->result->attr.proc_pointer
4630               && !sym->result->attr.function)))
4631     {
4632       e->ts.type = BT_PROCEDURE;
4633       goto resolve_procedure;
4634     }
4635
4636   if (sym->ts.type != BT_UNKNOWN)
4637     gfc_variable_attr (e, &e->ts);
4638   else
4639     {
4640       /* Must be a simple variable reference.  */
4641       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
4642         return FAILURE;
4643       e->ts = sym->ts;
4644     }
4645
4646   if (check_assumed_size_reference (sym, e))
4647     return FAILURE;
4648
4649   /* Deal with forward references to entries during resolve_code, to
4650      satisfy, at least partially, 12.5.2.5.  */
4651   if (gfc_current_ns->entries
4652       && current_entry_id == sym->entry_id
4653       && cs_base
4654       && cs_base->current
4655       && cs_base->current->op != EXEC_ENTRY)
4656     {
4657       gfc_entry_list *entry;
4658       gfc_formal_arglist *formal;
4659       int n;
4660       bool seen;
4661
4662       /* If the symbol is a dummy...  */
4663       if (sym->attr.dummy && sym->ns == gfc_current_ns)
4664         {
4665           entry = gfc_current_ns->entries;
4666           seen = false;
4667
4668           /* ...test if the symbol is a parameter of previous entries.  */
4669           for (; entry && entry->id <= current_entry_id; entry = entry->next)
4670             for (formal = entry->sym->formal; formal; formal = formal->next)
4671               {
4672                 if (formal->sym && sym->name == formal->sym->name)
4673                   seen = true;
4674               }
4675
4676           /*  If it has not been seen as a dummy, this is an error.  */
4677           if (!seen)
4678             {
4679               if (specification_expr)
4680                 gfc_error ("Variable '%s', used in a specification expression"
4681                            ", is referenced at %L before the ENTRY statement "
4682                            "in which it is a parameter",
4683                            sym->name, &cs_base->current->loc);
4684               else
4685                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
4686                            "statement in which it is a parameter",
4687                            sym->name, &cs_base->current->loc);
4688               t = FAILURE;
4689             }
4690         }
4691
4692       /* Now do the same check on the specification expressions.  */
4693       specification_expr = 1;
4694       if (sym->ts.type == BT_CHARACTER
4695           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
4696         t = FAILURE;
4697
4698       if (sym->as)
4699         for (n = 0; n < sym->as->rank; n++)
4700           {
4701              specification_expr = 1;
4702              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
4703                t = FAILURE;
4704              specification_expr = 1;
4705              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
4706                t = FAILURE;
4707           }
4708       specification_expr = 0;
4709
4710       if (t == SUCCESS)
4711         /* Update the symbol's entry level.  */
4712         sym->entry_id = current_entry_id + 1;
4713     }
4714
4715 resolve_procedure:
4716   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
4717     t = FAILURE;
4718
4719   /* F2008, C617 and C1229.  */
4720   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
4721       && gfc_is_coindexed (e))
4722     {
4723       gfc_ref *ref, *ref2 = NULL;
4724
4725       if (e->ts.type == BT_CLASS)
4726         {
4727           gfc_error ("Polymorphic subobject of coindexed object at %L",
4728                      &e->where);
4729           t = FAILURE;
4730         }
4731
4732       for (ref = e->ref; ref; ref = ref->next)
4733         {
4734           if (ref->type == REF_COMPONENT)
4735             ref2 = ref;
4736           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
4737             break;
4738         }
4739
4740       for ( ; ref; ref = ref->next)
4741         if (ref->type == REF_COMPONENT)
4742           break;
4743
4744       /* Expression itself is coindexed object.  */
4745       if (ref == NULL)
4746         {
4747           gfc_component *c;
4748           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
4749           for ( ; c; c = c->next)
4750             if (c->attr.allocatable && c->ts.type == BT_CLASS)
4751               {
4752                 gfc_error ("Coindexed object with polymorphic allocatable "
4753                          "subcomponent at %L", &e->where);
4754                 t = FAILURE;
4755                 break;
4756               }
4757         }
4758     }
4759
4760   return t;
4761 }
4762
4763
4764 /* Checks to see that the correct symbol has been host associated.
4765    The only situation where this arises is that in which a twice
4766    contained function is parsed after the host association is made.
4767    Therefore, on detecting this, change the symbol in the expression
4768    and convert the array reference into an actual arglist if the old
4769    symbol is a variable.  */
4770 static bool
4771 check_host_association (gfc_expr *e)
4772 {
4773   gfc_symbol *sym, *old_sym;
4774   gfc_symtree *st;
4775   int n;
4776   gfc_ref *ref;
4777   gfc_actual_arglist *arg, *tail = NULL;
4778   bool retval = e->expr_type == EXPR_FUNCTION;
4779
4780   /*  If the expression is the result of substitution in
4781       interface.c(gfc_extend_expr) because there is no way in
4782       which the host association can be wrong.  */
4783   if (e->symtree == NULL
4784         || e->symtree->n.sym == NULL
4785         || e->user_operator)
4786     return retval;
4787
4788   old_sym = e->symtree->n.sym;
4789
4790   if (gfc_current_ns->parent
4791         && old_sym->ns != gfc_current_ns)
4792     {
4793       /* Use the 'USE' name so that renamed module symbols are
4794          correctly handled.  */
4795       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
4796
4797       if (sym && old_sym != sym
4798               && sym->ts.type == old_sym->ts.type
4799               && sym->attr.flavor == FL_PROCEDURE
4800               && sym->attr.contained)
4801         {
4802           /* Clear the shape, since it might not be valid.  */
4803           if (e->shape != NULL)
4804             {
4805               for (n = 0; n < e->rank; n++)
4806                 mpz_clear (e->shape[n]);
4807
4808               gfc_free (e->shape);
4809             }
4810
4811           /* Give the expression the right symtree!  */
4812           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
4813           gcc_assert (st != NULL);
4814
4815           if (old_sym->attr.flavor == FL_PROCEDURE
4816                 || e->expr_type == EXPR_FUNCTION)
4817             {
4818               /* Original was function so point to the new symbol, since
4819                  the actual argument list is already attached to the
4820                  expression. */
4821               e->value.function.esym = NULL;
4822               e->symtree = st;
4823             }
4824           else
4825             {
4826               /* Original was variable so convert array references into
4827                  an actual arglist. This does not need any checking now
4828                  since gfc_resolve_function will take care of it.  */
4829               e->value.function.actual = NULL;
4830               e->expr_type = EXPR_FUNCTION;
4831               e->symtree = st;
4832
4833               /* Ambiguity will not arise if the array reference is not
4834                  the last reference.  */
4835               for (ref = e->ref; ref; ref = ref->next)
4836                 if (ref->type == REF_ARRAY && ref->next == NULL)
4837                   break;
4838
4839               gcc_assert (ref->type == REF_ARRAY);
4840
4841               /* Grab the start expressions from the array ref and
4842                  copy them into actual arguments.  */
4843               for (n = 0; n < ref->u.ar.dimen; n++)
4844                 {
4845                   arg = gfc_get_actual_arglist ();
4846                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
4847                   if (e->value.function.actual == NULL)
4848                     tail = e->value.function.actual = arg;
4849                   else
4850                     {
4851                       tail->next = arg;
4852                       tail = arg;
4853                     }
4854                 }
4855
4856               /* Dump the reference list and set the rank.  */
4857               gfc_free_ref_list (e->ref);
4858               e->ref = NULL;
4859               e->rank = sym->as ? sym->as->rank : 0;
4860             }
4861
4862           gfc_resolve_expr (e);
4863           sym->refs++;
4864         }
4865     }
4866   /* This might have changed!  */
4867   return e->expr_type == EXPR_FUNCTION;
4868 }
4869
4870
4871 static void
4872 gfc_resolve_character_operator (gfc_expr *e)
4873 {
4874   gfc_expr *op1 = e->value.op.op1;
4875   gfc_expr *op2 = e->value.op.op2;
4876   gfc_expr *e1 = NULL;
4877   gfc_expr *e2 = NULL;
4878
4879   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
4880
4881   if (op1->ts.u.cl && op1->ts.u.cl->length)
4882     e1 = gfc_copy_expr (op1->ts.u.cl->length);
4883   else if (op1->expr_type == EXPR_CONSTANT)
4884     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
4885                            op1->value.character.length);
4886
4887   if (op2->ts.u.cl && op2->ts.u.cl->length)
4888     e2 = gfc_copy_expr (op2->ts.u.cl->length);
4889   else if (op2->expr_type == EXPR_CONSTANT)
4890     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
4891                            op2->value.character.length);
4892
4893   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4894
4895   if (!e1 || !e2)
4896     return;
4897
4898   e->ts.u.cl->length = gfc_add (e1, e2);
4899   e->ts.u.cl->length->ts.type = BT_INTEGER;
4900   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4901   gfc_simplify_expr (e->ts.u.cl->length, 0);
4902   gfc_resolve_expr (e->ts.u.cl->length);
4903
4904   return;
4905 }
4906
4907
4908 /*  Ensure that an character expression has a charlen and, if possible, a
4909     length expression.  */
4910
4911 static void
4912 fixup_charlen (gfc_expr *e)
4913 {
4914   /* The cases fall through so that changes in expression type and the need
4915      for multiple fixes are picked up.  In all circumstances, a charlen should
4916      be available for the middle end to hang a backend_decl on.  */
4917   switch (e->expr_type)
4918     {
4919     case EXPR_OP:
4920       gfc_resolve_character_operator (e);
4921
4922     case EXPR_ARRAY:
4923       if (e->expr_type == EXPR_ARRAY)
4924         gfc_resolve_character_array_constructor (e);
4925
4926     case EXPR_SUBSTRING:
4927       if (!e->ts.u.cl && e->ref)
4928         gfc_resolve_substring_charlen (e);
4929
4930     default:
4931       if (!e->ts.u.cl)
4932         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4933
4934       break;
4935     }
4936 }
4937
4938
4939 /* Update an actual argument to include the passed-object for type-bound
4940    procedures at the right position.  */
4941
4942 static gfc_actual_arglist*
4943 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
4944                      const char *name)
4945 {
4946   gcc_assert (argpos > 0);
4947
4948   if (argpos == 1)
4949     {
4950       gfc_actual_arglist* result;
4951
4952       result = gfc_get_actual_arglist ();
4953       result->expr = po;
4954       result->next = lst;
4955       if (name)
4956         result->name = name;
4957
4958       return result;
4959     }
4960
4961   if (lst)
4962     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
4963   else
4964     lst = update_arglist_pass (NULL, po, argpos - 1, name);
4965   return lst;
4966 }
4967
4968
4969 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
4970
4971 static gfc_expr*
4972 extract_compcall_passed_object (gfc_expr* e)
4973 {
4974   gfc_expr* po;
4975
4976   gcc_assert (e->expr_type == EXPR_COMPCALL);
4977
4978   if (e->value.compcall.base_object)
4979     po = gfc_copy_expr (e->value.compcall.base_object);
4980   else
4981     {
4982       po = gfc_get_expr ();
4983       po->expr_type = EXPR_VARIABLE;
4984       po->symtree = e->symtree;
4985       po->ref = gfc_copy_ref (e->ref);
4986       po->where = e->where;
4987     }
4988
4989   if (gfc_resolve_expr (po) == FAILURE)
4990     return NULL;
4991
4992   return po;
4993 }
4994
4995
4996 /* Update the arglist of an EXPR_COMPCALL expression to include the
4997    passed-object.  */
4998
4999 static gfc_try
5000 update_compcall_arglist (gfc_expr* e)
5001 {
5002   gfc_expr* po;
5003   gfc_typebound_proc* tbp;
5004
5005   tbp = e->value.compcall.tbp;
5006
5007   if (tbp->error)
5008     return FAILURE;
5009
5010   po = extract_compcall_passed_object (e);
5011   if (!po)
5012     return FAILURE;
5013
5014   if (tbp->nopass || e->value.compcall.ignore_pass)
5015     {
5016       gfc_free_expr (po);
5017       return SUCCESS;
5018     }
5019
5020   gcc_assert (tbp->pass_arg_num > 0);
5021   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5022                                                   tbp->pass_arg_num,
5023                                                   tbp->pass_arg);
5024
5025   return SUCCESS;
5026 }
5027
5028
5029 /* Extract the passed object from a PPC call (a copy of it).  */
5030
5031 static gfc_expr*
5032 extract_ppc_passed_object (gfc_expr *e)
5033 {
5034   gfc_expr *po;
5035   gfc_ref **ref;
5036
5037   po = gfc_get_expr ();
5038   po->expr_type = EXPR_VARIABLE;
5039   po->symtree = e->symtree;
5040   po->ref = gfc_copy_ref (e->ref);
5041   po->where = e->where;
5042
5043   /* Remove PPC reference.  */
5044   ref = &po->ref;
5045   while ((*ref)->next)
5046     ref = &(*ref)->next;
5047   gfc_free_ref_list (*ref);
5048   *ref = NULL;
5049
5050   if (gfc_resolve_expr (po) == FAILURE)
5051     return NULL;
5052
5053   return po;
5054 }
5055
5056
5057 /* Update the actual arglist of a procedure pointer component to include the
5058    passed-object.  */
5059
5060 static gfc_try
5061 update_ppc_arglist (gfc_expr* e)
5062 {
5063   gfc_expr* po;
5064   gfc_component *ppc;
5065   gfc_typebound_proc* tb;
5066
5067   if (!gfc_is_proc_ptr_comp (e, &ppc))
5068     return FAILURE;
5069
5070   tb = ppc->tb;
5071
5072   if (tb->error)
5073     return FAILURE;
5074   else if (tb->nopass)
5075     return SUCCESS;
5076
5077   po = extract_ppc_passed_object (e);
5078   if (!po)
5079     return FAILURE;
5080
5081   if (po->rank > 0)
5082     {
5083       gfc_error ("Passed-object at %L must be scalar", &e->where);
5084       return FAILURE;
5085     }
5086
5087   gcc_assert (tb->pass_arg_num > 0);
5088   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5089                                                   tb->pass_arg_num,
5090                                                   tb->pass_arg);
5091
5092   return SUCCESS;
5093 }
5094
5095
5096 /* Check that the object a TBP is called on is valid, i.e. it must not be
5097    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5098
5099 static gfc_try
5100 check_typebound_baseobject (gfc_expr* e)
5101 {
5102   gfc_expr* base;
5103
5104   base = extract_compcall_passed_object (e);
5105   if (!base)
5106     return FAILURE;
5107
5108   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5109
5110   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5111     {
5112       gfc_error ("Base object for type-bound procedure call at %L is of"
5113                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5114       return FAILURE;
5115     }
5116
5117   /* If the procedure called is NOPASS, the base object must be scalar.  */
5118   if (e->value.compcall.tbp->nopass && base->rank > 0)
5119     {
5120       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5121                  " be scalar", &e->where);
5122       return FAILURE;
5123     }
5124
5125   /* FIXME: Remove once PR 41177 (this problem) is fixed completely.  */
5126   if (base->rank > 0)
5127     {
5128       gfc_error ("Non-scalar base object at %L currently not implemented",
5129                  &e->where);
5130       return FAILURE;
5131     }
5132
5133   return SUCCESS;
5134 }
5135
5136
5137 /* Resolve a call to a type-bound procedure, either function or subroutine,
5138    statically from the data in an EXPR_COMPCALL expression.  The adapted
5139    arglist and the target-procedure symtree are returned.  */
5140
5141 static gfc_try
5142 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5143                           gfc_actual_arglist** actual)
5144 {
5145   gcc_assert (e->expr_type == EXPR_COMPCALL);
5146   gcc_assert (!e->value.compcall.tbp->is_generic);
5147
5148   /* Update the actual arglist for PASS.  */
5149   if (update_compcall_arglist (e) == FAILURE)
5150     return FAILURE;
5151
5152   *actual = e->value.compcall.actual;
5153   *target = e->value.compcall.tbp->u.specific;
5154
5155   gfc_free_ref_list (e->ref);
5156   e->ref = NULL;
5157   e->value.compcall.actual = NULL;
5158
5159   return SUCCESS;
5160 }
5161
5162
5163 /* Get the ultimate declared type from an expression.  In addition,
5164    return the last class/derived type reference and the copy of the
5165    reference list.  */
5166 static gfc_symbol*
5167 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5168                         gfc_expr *e)
5169 {
5170   gfc_symbol *declared;
5171   gfc_ref *ref;
5172
5173   declared = NULL;
5174   if (class_ref)
5175     *class_ref = NULL;
5176   if (new_ref)
5177     *new_ref = gfc_copy_ref (e->ref);
5178
5179   for (ref = e->ref; ref; ref = ref->next)
5180     {
5181       if (ref->type != REF_COMPONENT)
5182         continue;
5183
5184       if (ref->u.c.component->ts.type == BT_CLASS
5185             || ref->u.c.component->ts.type == BT_DERIVED)
5186         {
5187           declared = ref->u.c.component->ts.u.derived;
5188           if (class_ref)
5189             *class_ref = ref;
5190         }
5191     }
5192
5193   if (declared == NULL)
5194     declared = e->symtree->n.sym->ts.u.derived;
5195
5196   return declared;
5197 }
5198
5199
5200 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5201    which of the specific bindings (if any) matches the arglist and transform
5202    the expression into a call of that binding.  */
5203
5204 static gfc_try
5205 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5206 {
5207   gfc_typebound_proc* genproc;
5208   const char* genname;
5209   gfc_symtree *st;
5210   gfc_symbol *derived;
5211
5212   gcc_assert (e->expr_type == EXPR_COMPCALL);
5213   genname = e->value.compcall.name;
5214   genproc = e->value.compcall.tbp;
5215
5216   if (!genproc->is_generic)
5217     return SUCCESS;
5218
5219   /* Try the bindings on this type and in the inheritance hierarchy.  */
5220   for (; genproc; genproc = genproc->overridden)
5221     {
5222       gfc_tbp_generic* g;
5223
5224       gcc_assert (genproc->is_generic);
5225       for (g = genproc->u.generic; g; g = g->next)
5226         {
5227           gfc_symbol* target;
5228           gfc_actual_arglist* args;
5229           bool matches;
5230
5231           gcc_assert (g->specific);
5232
5233           if (g->specific->error)
5234             continue;
5235
5236           target = g->specific->u.specific->n.sym;
5237
5238           /* Get the right arglist by handling PASS/NOPASS.  */
5239           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5240           if (!g->specific->nopass)
5241             {
5242               gfc_expr* po;
5243               po = extract_compcall_passed_object (e);
5244               if (!po)
5245                 return FAILURE;
5246
5247               gcc_assert (g->specific->pass_arg_num > 0);
5248               gcc_assert (!g->specific->error);
5249               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5250                                           g->specific->pass_arg);
5251             }
5252           resolve_actual_arglist (args, target->attr.proc,
5253                                   is_external_proc (target) && !target->formal);
5254
5255           /* Check if this arglist matches the formal.  */
5256           matches = gfc_arglist_matches_symbol (&args, target);
5257
5258           /* Clean up and break out of the loop if we've found it.  */
5259           gfc_free_actual_arglist (args);
5260           if (matches)
5261             {
5262               e->value.compcall.tbp = g->specific;
5263               /* Pass along the name for CLASS methods, where the vtab
5264                  procedure pointer component has to be referenced.  */
5265               if (name)
5266                 *name = g->specific_st->name;
5267               goto success;
5268             }
5269         }
5270     }
5271
5272   /* Nothing matching found!  */
5273   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5274              " '%s' at %L", genname, &e->where);
5275   return FAILURE;
5276
5277 success:
5278   /* Make sure that we have the right specific instance for the name.  */
5279   genname = e->value.compcall.tbp->u.specific->name;
5280
5281   /* Is the symtree name a "unique name".  */
5282   if (*genname == '@')
5283     genname = e->value.compcall.tbp->u.specific->n.sym->name;
5284
5285   derived = get_declared_from_expr (NULL, NULL, e);
5286
5287   st = gfc_find_typebound_proc (derived, NULL, genname, false, &e->where);
5288   if (st)
5289     e->value.compcall.tbp = st->n.tb;
5290
5291   return SUCCESS;
5292 }
5293
5294
5295 /* Resolve a call to a type-bound subroutine.  */
5296
5297 static gfc_try
5298 resolve_typebound_call (gfc_code* c, const char **name)
5299 {
5300   gfc_actual_arglist* newactual;
5301   gfc_symtree* target;
5302
5303   /* Check that's really a SUBROUTINE.  */
5304   if (!c->expr1->value.compcall.tbp->subroutine)
5305     {
5306       gfc_error ("'%s' at %L should be a SUBROUTINE",
5307                  c->expr1->value.compcall.name, &c->loc);
5308       return FAILURE;
5309     }
5310
5311   if (check_typebound_baseobject (c->expr1) == FAILURE)
5312     return FAILURE;
5313
5314   /* Pass along the name for CLASS methods, where the vtab
5315      procedure pointer component has to be referenced.  */
5316   if (name)
5317     *name = c->expr1->value.compcall.name;
5318
5319   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5320     return FAILURE;
5321
5322   /* Transform into an ordinary EXEC_CALL for now.  */
5323
5324   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5325     return FAILURE;
5326
5327   c->ext.actual = newactual;
5328   c->symtree = target;
5329   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5330
5331   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5332
5333   gfc_free_expr (c->expr1);
5334   c->expr1 = gfc_get_expr ();
5335   c->expr1->expr_type = EXPR_FUNCTION;
5336   c->expr1->symtree = target;
5337   c->expr1->where = c->loc;
5338
5339   return resolve_call (c);
5340 }
5341
5342
5343 /* Resolve a component-call expression.  */
5344 static gfc_try
5345 resolve_compcall (gfc_expr* e, const char **name)
5346 {
5347   gfc_actual_arglist* newactual;
5348   gfc_symtree* target;
5349
5350   /* Check that's really a FUNCTION.  */
5351   if (!e->value.compcall.tbp->function)
5352     {
5353       gfc_error ("'%s' at %L should be a FUNCTION",
5354                  e->value.compcall.name, &e->where);
5355       return FAILURE;
5356     }
5357
5358   /* These must not be assign-calls!  */
5359   gcc_assert (!e->value.compcall.assign);
5360
5361   if (check_typebound_baseobject (e) == FAILURE)
5362     return FAILURE;
5363
5364   /* Pass along the name for CLASS methods, where the vtab
5365      procedure pointer component has to be referenced.  */
5366   if (name)
5367     *name = e->value.compcall.name;
5368
5369   if (resolve_typebound_generic_call (e, name) == FAILURE)
5370     return FAILURE;
5371   gcc_assert (!e->value.compcall.tbp->is_generic);
5372
5373   /* Take the rank from the function's symbol.  */
5374   if (e->value.compcall.tbp->u.specific->n.sym->as)
5375     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5376
5377   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5378      arglist to the TBP's binding target.  */
5379
5380   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5381     return FAILURE;
5382
5383   e->value.function.actual = newactual;
5384   e->value.function.name = NULL;
5385   e->value.function.esym = target->n.sym;
5386   e->value.function.isym = NULL;
5387   e->symtree = target;
5388   e->ts = target->n.sym->ts;
5389   e->expr_type = EXPR_FUNCTION;
5390
5391   /* Resolution is not necessary if this is a class subroutine; this
5392      function only has to identify the specific proc. Resolution of
5393      the call will be done next in resolve_typebound_call.  */
5394   return gfc_resolve_expr (e);
5395 }
5396
5397
5398
5399 /* Resolve a typebound function, or 'method'. First separate all
5400    the non-CLASS references by calling resolve_compcall directly.  */
5401
5402 static gfc_try
5403 resolve_typebound_function (gfc_expr* e)
5404 {
5405   gfc_symbol *declared;
5406   gfc_component *c;
5407   gfc_ref *new_ref;
5408   gfc_ref *class_ref;
5409   gfc_symtree *st;
5410   const char *name;
5411   const char *genname;
5412   gfc_typespec ts;
5413
5414   st = e->symtree;
5415   if (st == NULL)
5416     return resolve_compcall (e, NULL);
5417
5418   if (resolve_ref (e) == FAILURE)
5419     return FAILURE;
5420
5421   /* Get the CLASS declared type.  */
5422   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5423
5424   /* Weed out cases of the ultimate component being a derived type.  */
5425   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5426          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5427     {
5428       gfc_free_ref_list (new_ref);
5429       return resolve_compcall (e, NULL);
5430     }
5431
5432   c = gfc_find_component (declared, "$data", true, true);
5433   declared = c->ts.u.derived;
5434
5435   /* Keep the generic name so that the vtab reference can be made.  */
5436   genname = NULL; 
5437   if (e->value.compcall.tbp->is_generic)
5438     genname = e->value.compcall.name;
5439
5440   /* Treat the call as if it is a typebound procedure, in order to roll
5441      out the correct name for the specific function.  */
5442   resolve_compcall (e, &name);
5443   ts = e->ts;
5444
5445   /* Then convert the expression to a procedure pointer component call.  */
5446   e->value.function.esym = NULL;
5447   e->symtree = st;
5448
5449   if (new_ref)  
5450     e->ref = new_ref;
5451
5452   /* '$vptr' points to the vtab, which contains the procedure pointers.  */
5453   gfc_add_component_ref (e, "$vptr");
5454   if (genname)
5455     {
5456       /* A generic procedure needs the subsidiary vtabs and vtypes for
5457          the specific procedures to have been build.  */
5458       gfc_symbol *vtab;
5459       vtab = gfc_find_derived_vtab (declared, true);
5460       gcc_assert (vtab);
5461       gfc_add_component_ref (e, genname);
5462     }
5463   gfc_add_component_ref (e, name);
5464
5465   /* Recover the typespec for the expression.  This is really only
5466      necessary for generic procedures, where the additional call
5467      to gfc_add_component_ref seems to throw the collection of the
5468      correct typespec.  */
5469   e->ts = ts;
5470   return SUCCESS;
5471 }
5472
5473 /* Resolve a typebound subroutine, or 'method'. First separate all
5474    the non-CLASS references by calling resolve_typebound_call
5475    directly.  */
5476
5477 static gfc_try
5478 resolve_typebound_subroutine (gfc_code *code)
5479 {
5480   gfc_symbol *declared;
5481   gfc_component *c;
5482   gfc_ref *new_ref;
5483   gfc_ref *class_ref;
5484   gfc_symtree *st;
5485   const char *genname;
5486   const char *name;
5487   gfc_typespec ts;
5488
5489   st = code->expr1->symtree;
5490   if (st == NULL)
5491     return resolve_typebound_call (code, NULL);
5492
5493   if (resolve_ref (code->expr1) == FAILURE)
5494     return FAILURE;
5495
5496   /* Get the CLASS declared type.  */
5497   declared = get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5498
5499   /* Weed out cases of the ultimate component being a derived type.  */
5500   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5501          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5502     {
5503       gfc_free_ref_list (new_ref);
5504       return resolve_typebound_call (code, NULL);
5505     } 
5506
5507   c = gfc_find_component (declared, "$data", true, true);
5508   declared = c->ts.u.derived;
5509
5510   /* Keep the generic name so that the vtab reference can be made.  */
5511   genname = NULL; 
5512   if (code->expr1->value.compcall.tbp->is_generic)
5513     genname = code->expr1->value.compcall.name;
5514
5515   resolve_typebound_call (code, &name);
5516   ts = code->expr1->ts;
5517
5518   /* Then convert the expression to a procedure pointer component call.  */
5519   code->expr1->value.function.esym = NULL;
5520   code->expr1->symtree = st;
5521
5522   if (new_ref)
5523     code->expr1->ref = new_ref;
5524
5525   /* '$vptr' points to the vtab, which contains the procedure pointers.  */
5526   gfc_add_component_ref (code->expr1, "$vptr");
5527   if (genname)
5528     {
5529       /* A generic procedure needs the subsidiary vtabs and vtypes for
5530          the specific procedures to have been build.  */
5531       gfc_symbol *vtab;
5532       vtab = gfc_find_derived_vtab (declared, true);
5533       gcc_assert (vtab);
5534       gfc_add_component_ref (code->expr1, genname);
5535     }
5536   gfc_add_component_ref (code->expr1, name);
5537
5538   /* Recover the typespec for the expression.  This is really only
5539      necessary for generic procedures, where the additional call
5540      to gfc_add_component_ref seems to throw the collection of the
5541      correct typespec.  */
5542   code->expr1->ts = ts;
5543   return SUCCESS;
5544 }
5545
5546
5547 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5548
5549 static gfc_try
5550 resolve_ppc_call (gfc_code* c)
5551 {
5552   gfc_component *comp;
5553   bool b;
5554
5555   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5556   gcc_assert (b);
5557
5558   c->resolved_sym = c->expr1->symtree->n.sym;
5559   c->expr1->expr_type = EXPR_VARIABLE;
5560
5561   if (!comp->attr.subroutine)
5562     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5563
5564   if (resolve_ref (c->expr1) == FAILURE)
5565     return FAILURE;
5566
5567   if (update_ppc_arglist (c->expr1) == FAILURE)
5568     return FAILURE;
5569
5570   c->ext.actual = c->expr1->value.compcall.actual;
5571
5572   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5573                               comp->formal == NULL) == FAILURE)
5574     return FAILURE;
5575
5576   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
5577
5578   return SUCCESS;
5579 }
5580
5581
5582 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
5583
5584 static gfc_try
5585 resolve_expr_ppc (gfc_expr* e)
5586 {
5587   gfc_component *comp;
5588   bool b;
5589
5590   b = gfc_is_proc_ptr_comp (e, &comp);
5591   gcc_assert (b);
5592
5593   /* Convert to EXPR_FUNCTION.  */
5594   e->expr_type = EXPR_FUNCTION;
5595   e->value.function.isym = NULL;
5596   e->value.function.actual = e->value.compcall.actual;
5597   e->ts = comp->ts;
5598   if (comp->as != NULL)
5599     e->rank = comp->as->rank;
5600
5601   if (!comp->attr.function)
5602     gfc_add_function (&comp->attr, comp->name, &e->where);
5603
5604   if (resolve_ref (e) == FAILURE)
5605     return FAILURE;
5606
5607   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
5608                               comp->formal == NULL) == FAILURE)
5609     return FAILURE;
5610
5611   if (update_ppc_arglist (e) == FAILURE)
5612     return FAILURE;
5613
5614   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
5615
5616   return SUCCESS;
5617 }
5618
5619
5620 static bool
5621 gfc_is_expandable_expr (gfc_expr *e)
5622 {
5623   gfc_constructor *con;
5624
5625   if (e->expr_type == EXPR_ARRAY)
5626     {
5627       /* Traverse the constructor looking for variables that are flavor
5628          parameter.  Parameters must be expanded since they are fully used at
5629          compile time.  */
5630       con = gfc_constructor_first (e->value.constructor);
5631       for (; con; con = gfc_constructor_next (con))
5632         {
5633           if (con->expr->expr_type == EXPR_VARIABLE
5634               && con->expr->symtree
5635               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
5636               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
5637             return true;
5638           if (con->expr->expr_type == EXPR_ARRAY
5639               && gfc_is_expandable_expr (con->expr))
5640             return true;
5641         }
5642     }
5643
5644   return false;
5645 }
5646
5647 /* Resolve an expression.  That is, make sure that types of operands agree
5648    with their operators, intrinsic operators are converted to function calls
5649    for overloaded types and unresolved function references are resolved.  */
5650
5651 gfc_try
5652 gfc_resolve_expr (gfc_expr *e)
5653 {
5654   gfc_try t;
5655   bool inquiry_save;
5656
5657   if (e == NULL)
5658     return SUCCESS;
5659
5660   /* inquiry_argument only applies to variables.  */
5661   inquiry_save = inquiry_argument;
5662   if (e->expr_type != EXPR_VARIABLE)
5663     inquiry_argument = false;
5664
5665   switch (e->expr_type)
5666     {
5667     case EXPR_OP:
5668       t = resolve_operator (e);
5669       break;
5670
5671     case EXPR_FUNCTION:
5672     case EXPR_VARIABLE:
5673
5674       if (check_host_association (e))
5675         t = resolve_function (e);
5676       else
5677         {
5678           t = resolve_variable (e);
5679           if (t == SUCCESS)
5680             expression_rank (e);
5681         }
5682
5683       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
5684           && e->ref->type != REF_SUBSTRING)
5685         gfc_resolve_substring_charlen (e);
5686
5687       break;
5688
5689     case EXPR_COMPCALL:
5690       t = resolve_typebound_function (e);
5691       break;
5692
5693     case EXPR_SUBSTRING:
5694       t = resolve_ref (e);
5695       break;
5696
5697     case EXPR_CONSTANT:
5698     case EXPR_NULL:
5699       t = SUCCESS;
5700       break;
5701
5702     case EXPR_PPC:
5703       t = resolve_expr_ppc (e);
5704       break;
5705
5706     case EXPR_ARRAY:
5707       t = FAILURE;
5708       if (resolve_ref (e) == FAILURE)
5709         break;
5710
5711       t = gfc_resolve_array_constructor (e);
5712       /* Also try to expand a constructor.  */
5713       if (t == SUCCESS)
5714         {
5715           expression_rank (e);
5716           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
5717             gfc_expand_constructor (e);
5718         }
5719
5720       /* This provides the opportunity for the length of constructors with
5721          character valued function elements to propagate the string length
5722          to the expression.  */
5723       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
5724         {
5725           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
5726              here rather then add a duplicate test for it above.  */ 
5727           gfc_expand_constructor (e);
5728           t = gfc_resolve_character_array_constructor (e);
5729         }
5730
5731       break;
5732
5733     case EXPR_STRUCTURE:
5734       t = resolve_ref (e);
5735       if (t == FAILURE)
5736         break;
5737
5738       t = resolve_structure_cons (e);
5739       if (t == FAILURE)
5740         break;
5741
5742       t = gfc_simplify_expr (e, 0);
5743       break;
5744
5745     default:
5746       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
5747     }
5748
5749   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
5750     fixup_charlen (e);
5751
5752   inquiry_argument = inquiry_save;
5753
5754   return t;
5755 }
5756
5757
5758 /* Resolve an expression from an iterator.  They must be scalar and have
5759    INTEGER or (optionally) REAL type.  */
5760
5761 static gfc_try
5762 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
5763                            const char *name_msgid)
5764 {
5765   if (gfc_resolve_expr (expr) == FAILURE)
5766     return FAILURE;
5767
5768   if (expr->rank != 0)
5769     {
5770       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
5771       return FAILURE;
5772     }
5773
5774   if (expr->ts.type != BT_INTEGER)
5775     {
5776       if (expr->ts.type == BT_REAL)
5777         {
5778           if (real_ok)
5779             return gfc_notify_std (GFC_STD_F95_DEL,
5780                                    "Deleted feature: %s at %L must be integer",
5781                                    _(name_msgid), &expr->where);
5782           else
5783             {
5784               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
5785                          &expr->where);
5786               return FAILURE;
5787             }
5788         }
5789       else
5790         {
5791           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
5792           return FAILURE;
5793         }
5794     }
5795   return SUCCESS;
5796 }
5797
5798
5799 /* Resolve the expressions in an iterator structure.  If REAL_OK is
5800    false allow only INTEGER type iterators, otherwise allow REAL types.  */
5801
5802 gfc_try
5803 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
5804 {
5805   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
5806       == FAILURE)
5807     return FAILURE;
5808
5809   if (gfc_pure (NULL) && gfc_impure_variable (iter->var->symtree->n.sym))
5810     {
5811       gfc_error ("Cannot assign to loop variable in PURE procedure at %L",
5812                  &iter->var->where);
5813       return FAILURE;
5814     }
5815
5816   if (gfc_resolve_iterator_expr (iter->start, real_ok,
5817                                  "Start expression in DO loop") == FAILURE)
5818     return FAILURE;
5819
5820   if (gfc_resolve_iterator_expr (iter->end, real_ok,
5821                                  "End expression in DO loop") == FAILURE)
5822     return FAILURE;
5823
5824   if (gfc_resolve_iterator_expr (iter->step, real_ok,
5825                                  "Step expression in DO loop") == FAILURE)
5826     return FAILURE;
5827
5828   if (iter->step->expr_type == EXPR_CONSTANT)
5829     {
5830       if ((iter->step->ts.type == BT_INTEGER
5831            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
5832           || (iter->step->ts.type == BT_REAL
5833               && mpfr_sgn (iter->step->value.real) == 0))
5834         {
5835           gfc_error ("Step expression in DO loop at %L cannot be zero",
5836                      &iter->step->where);
5837           return FAILURE;
5838         }
5839     }
5840
5841   /* Convert start, end, and step to the same type as var.  */
5842   if (iter->start->ts.kind != iter->var->ts.kind
5843       || iter->start->ts.type != iter->var->ts.type)
5844     gfc_convert_type (iter->start, &iter->var->ts, 2);
5845
5846   if (iter->end->ts.kind != iter->var->ts.kind
5847       || iter->end->ts.type != iter->var->ts.type)
5848     gfc_convert_type (iter->end, &iter->var->ts, 2);
5849
5850   if (iter->step->ts.kind != iter->var->ts.kind
5851       || iter->step->ts.type != iter->var->ts.type)
5852     gfc_convert_type (iter->step, &iter->var->ts, 2);
5853
5854   if (iter->start->expr_type == EXPR_CONSTANT
5855       && iter->end->expr_type == EXPR_CONSTANT
5856       && iter->step->expr_type == EXPR_CONSTANT)
5857     {
5858       int sgn, cmp;
5859       if (iter->start->ts.type == BT_INTEGER)
5860         {
5861           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
5862           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
5863         }
5864       else
5865         {
5866           sgn = mpfr_sgn (iter->step->value.real);
5867           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
5868         }
5869       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
5870         gfc_warning ("DO loop at %L will be executed zero times",
5871                      &iter->step->where);
5872     }
5873
5874   return SUCCESS;
5875 }
5876
5877
5878 /* Traversal function for find_forall_index.  f == 2 signals that
5879    that variable itself is not to be checked - only the references.  */
5880
5881 static bool
5882 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
5883 {
5884   if (expr->expr_type != EXPR_VARIABLE)
5885     return false;
5886   
5887   /* A scalar assignment  */
5888   if (!expr->ref || *f == 1)
5889     {
5890       if (expr->symtree->n.sym == sym)
5891         return true;
5892       else
5893         return false;
5894     }
5895
5896   if (*f == 2)
5897     *f = 1;
5898   return false;
5899 }
5900
5901
5902 /* Check whether the FORALL index appears in the expression or not.
5903    Returns SUCCESS if SYM is found in EXPR.  */
5904
5905 gfc_try
5906 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
5907 {
5908   if (gfc_traverse_expr (expr, sym, forall_index, f))
5909     return SUCCESS;
5910   else
5911     return FAILURE;
5912 }
5913
5914
5915 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
5916    to be a scalar INTEGER variable.  The subscripts and stride are scalar
5917    INTEGERs, and if stride is a constant it must be nonzero.
5918    Furthermore "A subscript or stride in a forall-triplet-spec shall
5919    not contain a reference to any index-name in the
5920    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
5921
5922 static void
5923 resolve_forall_iterators (gfc_forall_iterator *it)
5924 {
5925   gfc_forall_iterator *iter, *iter2;
5926
5927   for (iter = it; iter; iter = iter->next)
5928     {
5929       if (gfc_resolve_expr (iter->var) == SUCCESS
5930           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
5931         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
5932                    &iter->var->where);
5933
5934       if (gfc_resolve_expr (iter->start) == SUCCESS
5935           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
5936         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
5937                    &iter->start->where);
5938       if (iter->var->ts.kind != iter->start->ts.kind)
5939         gfc_convert_type (iter->start, &iter->var->ts, 2);
5940
5941       if (gfc_resolve_expr (iter->end) == SUCCESS
5942           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
5943         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
5944                    &iter->end->where);
5945       if (iter->var->ts.kind != iter->end->ts.kind)
5946         gfc_convert_type (iter->end, &iter->var->ts, 2);
5947
5948       if (gfc_resolve_expr (iter->stride) == SUCCESS)
5949         {
5950           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
5951             gfc_error ("FORALL stride expression at %L must be a scalar %s",
5952                        &iter->stride->where, "INTEGER");
5953
5954           if (iter->stride->expr_type == EXPR_CONSTANT
5955               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
5956             gfc_error ("FORALL stride expression at %L cannot be zero",
5957                        &iter->stride->where);
5958         }
5959       if (iter->var->ts.kind != iter->stride->ts.kind)
5960         gfc_convert_type (iter->stride, &iter->var->ts, 2);
5961     }
5962
5963   for (iter = it; iter; iter = iter->next)
5964     for (iter2 = iter; iter2; iter2 = iter2->next)
5965       {
5966         if (find_forall_index (iter2->start,
5967                                iter->var->symtree->n.sym, 0) == SUCCESS
5968             || find_forall_index (iter2->end,
5969                                   iter->var->symtree->n.sym, 0) == SUCCESS
5970             || find_forall_index (iter2->stride,
5971                                   iter->var->symtree->n.sym, 0) == SUCCESS)
5972           gfc_error ("FORALL index '%s' may not appear in triplet "
5973                      "specification at %L", iter->var->symtree->name,
5974                      &iter2->start->where);
5975       }
5976 }
5977
5978
5979 /* Given a pointer to a symbol that is a derived type, see if it's
5980    inaccessible, i.e. if it's defined in another module and the components are
5981    PRIVATE.  The search is recursive if necessary.  Returns zero if no
5982    inaccessible components are found, nonzero otherwise.  */
5983
5984 static int
5985 derived_inaccessible (gfc_symbol *sym)
5986 {
5987   gfc_component *c;
5988
5989   if (sym->attr.use_assoc && sym->attr.private_comp)
5990     return 1;
5991
5992   for (c = sym->components; c; c = c->next)
5993     {
5994         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
5995           return 1;
5996     }
5997
5998   return 0;
5999 }
6000
6001
6002 /* Resolve the argument of a deallocate expression.  The expression must be
6003    a pointer or a full array.  */
6004
6005 static gfc_try
6006 resolve_deallocate_expr (gfc_expr *e)
6007 {
6008   symbol_attribute attr;
6009   int allocatable, pointer, check_intent_in;
6010   gfc_ref *ref;
6011   gfc_symbol *sym;
6012   gfc_component *c;
6013
6014   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
6015   check_intent_in = 1;
6016
6017   if (gfc_resolve_expr (e) == FAILURE)
6018     return FAILURE;
6019
6020   if (e->expr_type != EXPR_VARIABLE)
6021     goto bad;
6022
6023   sym = e->symtree->n.sym;
6024
6025   if (sym->ts.type == BT_CLASS)
6026     {
6027       allocatable = CLASS_DATA (sym)->attr.allocatable;
6028       pointer = CLASS_DATA (sym)->attr.pointer;
6029     }
6030   else
6031     {
6032       allocatable = sym->attr.allocatable;
6033       pointer = sym->attr.pointer;
6034     }
6035   for (ref = e->ref; ref; ref = ref->next)
6036     {
6037       if (pointer)
6038         check_intent_in = 0;
6039
6040       switch (ref->type)
6041         {
6042         case REF_ARRAY:
6043           if (ref->u.ar.type != AR_FULL)
6044             allocatable = 0;
6045           break;
6046
6047         case REF_COMPONENT:
6048           c = ref->u.c.component;
6049           if (c->ts.type == BT_CLASS)
6050             {
6051               allocatable = CLASS_DATA (c)->attr.allocatable;
6052               pointer = CLASS_DATA (c)->attr.pointer;
6053             }
6054           else
6055             {
6056               allocatable = c->attr.allocatable;
6057               pointer = c->attr.pointer;
6058             }
6059           break;
6060
6061         case REF_SUBSTRING:
6062           allocatable = 0;
6063           break;
6064         }
6065     }
6066
6067   attr = gfc_expr_attr (e);
6068
6069   if (allocatable == 0 && attr.pointer == 0)
6070     {
6071     bad:
6072       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6073                  &e->where);
6074       return FAILURE;
6075     }
6076
6077   if (check_intent_in && sym->attr.intent == INTENT_IN)
6078     {
6079       gfc_error ("Cannot deallocate INTENT(IN) variable '%s' at %L",
6080                  sym->name, &e->where);
6081       return FAILURE;
6082     }
6083
6084   if (e->ts.type == BT_CLASS)
6085     {
6086       /* Only deallocate the DATA component.  */
6087       gfc_add_component_ref (e, "$data");
6088     }
6089
6090   return SUCCESS;
6091 }
6092
6093
6094 /* Returns true if the expression e contains a reference to the symbol sym.  */
6095 static bool
6096 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6097 {
6098   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6099     return true;
6100
6101   return false;
6102 }
6103
6104 bool
6105 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6106 {
6107   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6108 }
6109
6110
6111 /* Given the expression node e for an allocatable/pointer of derived type to be
6112    allocated, get the expression node to be initialized afterwards (needed for
6113    derived types with default initializers, and derived types with allocatable
6114    components that need nullification.)  */
6115
6116 gfc_expr *
6117 gfc_expr_to_initialize (gfc_expr *e)
6118 {
6119   gfc_expr *result;
6120   gfc_ref *ref;
6121   int i;
6122
6123   result = gfc_copy_expr (e);
6124
6125   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6126   for (ref = result->ref; ref; ref = ref->next)
6127     if (ref->type == REF_ARRAY && ref->next == NULL)
6128       {
6129         ref->u.ar.type = AR_FULL;
6130
6131         for (i = 0; i < ref->u.ar.dimen; i++)
6132           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6133
6134         result->rank = ref->u.ar.dimen;
6135         break;
6136       }
6137
6138   return result;
6139 }
6140
6141
6142 /* Used in resolve_allocate_expr to check that a allocation-object and
6143    a source-expr are conformable.  This does not catch all possible 
6144    cases; in particular a runtime checking is needed.  */
6145
6146 static gfc_try
6147 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6148 {
6149   /* First compare rank.  */
6150   if (e2->ref && e1->rank != e2->ref->u.ar.as->rank)
6151     {
6152       gfc_error ("Source-expr at %L must be scalar or have the "
6153                  "same rank as the allocate-object at %L",
6154                  &e1->where, &e2->where);
6155       return FAILURE;
6156     }
6157
6158   if (e1->shape)
6159     {
6160       int i;
6161       mpz_t s;
6162
6163       mpz_init (s);
6164
6165       for (i = 0; i < e1->rank; i++)
6166         {
6167           if (e2->ref->u.ar.end[i])
6168             {
6169               mpz_set (s, e2->ref->u.ar.end[i]->value.integer);
6170               mpz_sub (s, s, e2->ref->u.ar.start[i]->value.integer);
6171               mpz_add_ui (s, s, 1);
6172             }
6173           else
6174             {
6175               mpz_set (s, e2->ref->u.ar.start[i]->value.integer);
6176             }
6177
6178           if (mpz_cmp (e1->shape[i], s) != 0)
6179             {
6180               gfc_error ("Source-expr at %L and allocate-object at %L must "
6181                          "have the same shape", &e1->where, &e2->where);
6182               mpz_clear (s);
6183               return FAILURE;
6184             }
6185         }
6186
6187       mpz_clear (s);
6188     }
6189
6190   return SUCCESS;
6191 }
6192
6193
6194 /* Resolve the expression in an ALLOCATE statement, doing the additional
6195    checks to see whether the expression is OK or not.  The expression must
6196    have a trailing array reference that gives the size of the array.  */
6197
6198 static gfc_try
6199 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6200 {
6201   int i, pointer, allocatable, dimension, check_intent_in, is_abstract;
6202   int codimension;
6203   symbol_attribute attr;
6204   gfc_ref *ref, *ref2;
6205   gfc_array_ref *ar;
6206   gfc_symbol *sym = NULL;
6207   gfc_alloc *a;
6208   gfc_component *c;
6209   gfc_expr *init_e;
6210
6211   /* Check INTENT(IN), unless the object is a sub-component of a pointer.  */
6212   check_intent_in = 1;
6213
6214   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6215      checking of coarrays.  */
6216   for (ref = e->ref; ref; ref = ref->next)
6217     if (ref->next == NULL)
6218       break;
6219
6220   if (ref && ref->type == REF_ARRAY)
6221     ref->u.ar.in_allocate = true;
6222
6223   if (gfc_resolve_expr (e) == FAILURE)
6224     goto failure;
6225
6226   /* Make sure the expression is allocatable or a pointer.  If it is
6227      pointer, the next-to-last reference must be a pointer.  */
6228
6229   ref2 = NULL;
6230   if (e->symtree)
6231     sym = e->symtree->n.sym;
6232
6233   /* Check whether ultimate component is abstract and CLASS.  */
6234   is_abstract = 0;
6235
6236   if (e->expr_type != EXPR_VARIABLE)
6237     {
6238       allocatable = 0;
6239       attr = gfc_expr_attr (e);
6240       pointer = attr.pointer;
6241       dimension = attr.dimension;
6242       codimension = attr.codimension;
6243     }
6244   else
6245     {
6246       if (sym->ts.type == BT_CLASS)
6247         {
6248           allocatable = CLASS_DATA (sym)->attr.allocatable;
6249           pointer = CLASS_DATA (sym)->attr.pointer;
6250           dimension = CLASS_DATA (sym)->attr.dimension;
6251           codimension = CLASS_DATA (sym)->attr.codimension;
6252           is_abstract = CLASS_DATA (sym)->attr.abstract;
6253         }
6254       else
6255         {
6256           allocatable = sym->attr.allocatable;
6257           pointer = sym->attr.pointer;
6258           dimension = sym->attr.dimension;
6259           codimension = sym->attr.codimension;
6260         }
6261
6262       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6263         {
6264           if (pointer)
6265             check_intent_in = 0;
6266
6267           switch (ref->type)
6268             {
6269               case REF_ARRAY:
6270                 if (ref->next != NULL)
6271                   pointer = 0;
6272                 break;
6273
6274               case REF_COMPONENT:
6275                 /* F2008, C644.  */
6276                 if (gfc_is_coindexed (e))
6277                   {
6278                     gfc_error ("Coindexed allocatable object at %L",
6279                                &e->where);
6280                     goto failure;
6281                   }
6282
6283                 c = ref->u.c.component;
6284                 if (c->ts.type == BT_CLASS)
6285                   {
6286                     allocatable = CLASS_DATA (c)->attr.allocatable;
6287                     pointer = CLASS_DATA (c)->attr.pointer;
6288                     dimension = CLASS_DATA (c)->attr.dimension;
6289                     codimension = CLASS_DATA (c)->attr.codimension;
6290                     is_abstract = CLASS_DATA (c)->attr.abstract;
6291                   }
6292                 else
6293                   {
6294                     allocatable = c->attr.allocatable;
6295                     pointer = c->attr.pointer;
6296                     dimension = c->attr.dimension;
6297                     codimension = c->attr.codimension;
6298                     is_abstract = c->attr.abstract;
6299                   }
6300                 break;
6301
6302               case REF_SUBSTRING:
6303                 allocatable = 0;
6304                 pointer = 0;
6305                 break;
6306             }
6307         }
6308     }
6309
6310   if (allocatable == 0 && pointer == 0)
6311     {
6312       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6313                  &e->where);
6314       goto failure;
6315     }
6316
6317   /* Some checks for the SOURCE tag.  */
6318   if (code->expr3)
6319     {
6320       /* Check F03:C631.  */
6321       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6322         {
6323           gfc_error ("Type of entity at %L is type incompatible with "
6324                       "source-expr at %L", &e->where, &code->expr3->where);
6325           goto failure;
6326         }
6327
6328       /* Check F03:C632 and restriction following Note 6.18.  */
6329       if (code->expr3->rank > 0
6330           && conformable_arrays (code->expr3, e) == FAILURE)
6331         goto failure;
6332
6333       /* Check F03:C633.  */
6334       if (code->expr3->ts.kind != e->ts.kind)
6335         {
6336           gfc_error ("The allocate-object at %L and the source-expr at %L "
6337                       "shall have the same kind type parameter",
6338                       &e->where, &code->expr3->where);
6339           goto failure;
6340         }
6341     }
6342   else if (is_abstract&& code->ext.alloc.ts.type == BT_UNKNOWN)
6343     {
6344       gcc_assert (e->ts.type == BT_CLASS);
6345       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6346                  "type-spec or SOURCE=", sym->name, &e->where);
6347       goto failure;
6348     }
6349
6350   if (check_intent_in && sym->attr.intent == INTENT_IN)
6351     {
6352       gfc_error ("Cannot allocate INTENT(IN) variable '%s' at %L",
6353                  sym->name, &e->where);
6354       goto failure;
6355     }
6356     
6357   if (!code->expr3)
6358     {
6359       /* Add default initializer for those derived types that need them.  */
6360       if (e->ts.type == BT_DERIVED
6361           && (init_e = gfc_default_initializer (&e->ts)))
6362         {
6363           gfc_code *init_st = gfc_get_code ();
6364           init_st->loc = code->loc;
6365           init_st->op = EXEC_INIT_ASSIGN;
6366           init_st->expr1 = gfc_expr_to_initialize (e);
6367           init_st->expr2 = init_e;
6368           init_st->next = code->next;
6369           code->next = init_st;
6370         }
6371       else if (e->ts.type == BT_CLASS
6372                && ((code->ext.alloc.ts.type == BT_UNKNOWN
6373                     && (init_e = gfc_default_initializer (&CLASS_DATA (e)->ts)))
6374                    || (code->ext.alloc.ts.type == BT_DERIVED
6375                        && (init_e = gfc_default_initializer (&code->ext.alloc.ts)))))
6376         {
6377           gfc_code *init_st = gfc_get_code ();
6378           init_st->loc = code->loc;
6379           init_st->op = EXEC_INIT_ASSIGN;
6380           init_st->expr1 = gfc_expr_to_initialize (e);
6381           init_st->expr2 = init_e;
6382           init_st->next = code->next;
6383           code->next = init_st;
6384         }
6385     }
6386
6387   if (pointer || (dimension == 0 && codimension == 0))
6388     goto success;
6389
6390   /* Make sure the next-to-last reference node is an array specification.  */
6391
6392   if (ref2 == NULL || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
6393       || (dimension && ref2->u.ar.dimen == 0))
6394     {
6395       gfc_error ("Array specification required in ALLOCATE statement "
6396                  "at %L", &e->where);
6397       goto failure;
6398     }
6399
6400   /* Make sure that the array section reference makes sense in the
6401     context of an ALLOCATE specification.  */
6402
6403   ar = &ref2->u.ar;
6404
6405   if (codimension && ar->codimen == 0)
6406     {
6407       gfc_error ("Coarray specification required in ALLOCATE statement "
6408                  "at %L", &e->where);
6409       goto failure;
6410     }
6411
6412   for (i = 0; i < ar->dimen; i++)
6413     {
6414       if (ref2->u.ar.type == AR_ELEMENT)
6415         goto check_symbols;
6416
6417       switch (ar->dimen_type[i])
6418         {
6419         case DIMEN_ELEMENT:
6420           break;
6421
6422         case DIMEN_RANGE:
6423           if (ar->start[i] != NULL
6424               && ar->end[i] != NULL
6425               && ar->stride[i] == NULL)
6426             break;
6427
6428           /* Fall Through...  */
6429
6430         case DIMEN_UNKNOWN:
6431         case DIMEN_VECTOR:
6432         case DIMEN_STAR:
6433           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6434                      &e->where);
6435           goto failure;
6436         }
6437
6438 check_symbols:
6439       for (a = code->ext.alloc.list; a; a = a->next)
6440         {
6441           sym = a->expr->symtree->n.sym;
6442
6443           /* TODO - check derived type components.  */
6444           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6445             continue;
6446
6447           if ((ar->start[i] != NULL
6448                && gfc_find_sym_in_expr (sym, ar->start[i]))
6449               || (ar->end[i] != NULL
6450                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6451             {
6452               gfc_error ("'%s' must not appear in the array specification at "
6453                          "%L in the same ALLOCATE statement where it is "
6454                          "itself allocated", sym->name, &ar->where);
6455               goto failure;
6456             }
6457         }
6458     }
6459
6460   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
6461     {
6462       if (ar->dimen_type[i] == DIMEN_ELEMENT
6463           || ar->dimen_type[i] == DIMEN_RANGE)
6464         {
6465           if (i == (ar->dimen + ar->codimen - 1))
6466             {
6467               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
6468                          "statement at %L", &e->where);
6469               goto failure;
6470             }
6471           break;
6472         }
6473
6474       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
6475           && ar->stride[i] == NULL)
6476         break;
6477
6478       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
6479                  &e->where);
6480       goto failure;
6481     }
6482
6483   if (codimension && ar->as->rank == 0)
6484     {
6485       gfc_error ("Sorry, allocatable scalar coarrays are not yet supported "
6486                  "at %L", &e->where);
6487       goto failure;
6488     }
6489
6490 success:
6491   return SUCCESS;
6492
6493 failure:
6494   return FAILURE;
6495 }
6496
6497 static void
6498 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6499 {
6500   gfc_expr *stat, *errmsg, *pe, *qe;
6501   gfc_alloc *a, *p, *q;
6502
6503   stat = code->expr1 ? code->expr1 : NULL;
6504
6505   errmsg = code->expr2 ? code->expr2 : NULL;
6506
6507   /* Check the stat variable.  */
6508   if (stat)
6509     {
6510       if (stat->symtree->n.sym->attr.intent == INTENT_IN)
6511         gfc_error ("Stat-variable '%s' at %L cannot be INTENT(IN)",
6512                    stat->symtree->n.sym->name, &stat->where);
6513
6514       if (gfc_pure (NULL) && gfc_impure_variable (stat->symtree->n.sym))
6515         gfc_error ("Illegal stat-variable at %L for a PURE procedure",
6516                    &stat->where);
6517
6518       if ((stat->ts.type != BT_INTEGER
6519            && !(stat->ref && (stat->ref->type == REF_ARRAY
6520                               || stat->ref->type == REF_COMPONENT)))
6521           || stat->rank > 0)
6522         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6523                    "variable", &stat->where);
6524
6525       for (p = code->ext.alloc.list; p; p = p->next)
6526         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6527           gfc_error ("Stat-variable at %L shall not be %sd within "
6528                      "the same %s statement", &stat->where, fcn, fcn);
6529     }
6530
6531   /* Check the errmsg variable.  */
6532   if (errmsg)
6533     {
6534       if (!stat)
6535         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
6536                      &errmsg->where);
6537
6538       if (errmsg->symtree->n.sym->attr.intent == INTENT_IN)
6539         gfc_error ("Errmsg-variable '%s' at %L cannot be INTENT(IN)",
6540                    errmsg->symtree->n.sym->name, &errmsg->where);
6541
6542       if (gfc_pure (NULL) && gfc_impure_variable (errmsg->symtree->n.sym))
6543         gfc_error ("Illegal errmsg-variable at %L for a PURE procedure",
6544                    &errmsg->where);
6545
6546       if ((errmsg->ts.type != BT_CHARACTER
6547            && !(errmsg->ref
6548                 && (errmsg->ref->type == REF_ARRAY
6549                     || errmsg->ref->type == REF_COMPONENT)))
6550           || errmsg->rank > 0 )
6551         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
6552                    "variable", &errmsg->where);
6553
6554       for (p = code->ext.alloc.list; p; p = p->next)
6555         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
6556           gfc_error ("Errmsg-variable at %L shall not be %sd within "
6557                      "the same %s statement", &errmsg->where, fcn, fcn);
6558     }
6559
6560   /* Check that an allocate-object appears only once in the statement.  
6561      FIXME: Checking derived types is disabled.  */
6562   for (p = code->ext.alloc.list; p; p = p->next)
6563     {
6564       pe = p->expr;
6565       if ((pe->ref && pe->ref->type != REF_COMPONENT)
6566            && (pe->symtree->n.sym->ts.type != BT_DERIVED))
6567         {
6568           for (q = p->next; q; q = q->next)
6569             {
6570               qe = q->expr;
6571               if ((qe->ref && qe->ref->type != REF_COMPONENT)
6572                   && (qe->symtree->n.sym->ts.type != BT_DERIVED)
6573                   && (pe->symtree->n.sym->name == qe->symtree->n.sym->name))
6574                 gfc_error ("Allocate-object at %L also appears at %L",
6575                            &pe->where, &qe->where);
6576             }
6577         }
6578     }
6579
6580   if (strcmp (fcn, "ALLOCATE") == 0)
6581     {
6582       for (a = code->ext.alloc.list; a; a = a->next)
6583         resolve_allocate_expr (a->expr, code);
6584     }
6585   else
6586     {
6587       for (a = code->ext.alloc.list; a; a = a->next)
6588         resolve_deallocate_expr (a->expr);
6589     }
6590 }
6591
6592
6593 /************ SELECT CASE resolution subroutines ************/
6594
6595 /* Callback function for our mergesort variant.  Determines interval
6596    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
6597    op1 > op2.  Assumes we're not dealing with the default case.  
6598    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
6599    There are nine situations to check.  */
6600
6601 static int
6602 compare_cases (const gfc_case *op1, const gfc_case *op2)
6603 {
6604   int retval;
6605
6606   if (op1->low == NULL) /* op1 = (:L)  */
6607     {
6608       /* op2 = (:N), so overlap.  */
6609       retval = 0;
6610       /* op2 = (M:) or (M:N),  L < M  */
6611       if (op2->low != NULL
6612           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6613         retval = -1;
6614     }
6615   else if (op1->high == NULL) /* op1 = (K:)  */
6616     {
6617       /* op2 = (M:), so overlap.  */
6618       retval = 0;
6619       /* op2 = (:N) or (M:N), K > N  */
6620       if (op2->high != NULL
6621           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6622         retval = 1;
6623     }
6624   else /* op1 = (K:L)  */
6625     {
6626       if (op2->low == NULL)       /* op2 = (:N), K > N  */
6627         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6628                  ? 1 : 0;
6629       else if (op2->high == NULL) /* op2 = (M:), L < M  */
6630         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6631                  ? -1 : 0;
6632       else                      /* op2 = (M:N)  */
6633         {
6634           retval =  0;
6635           /* L < M  */
6636           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
6637             retval =  -1;
6638           /* K > N  */
6639           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
6640             retval =  1;
6641         }
6642     }
6643
6644   return retval;
6645 }
6646
6647
6648 /* Merge-sort a double linked case list, detecting overlap in the
6649    process.  LIST is the head of the double linked case list before it
6650    is sorted.  Returns the head of the sorted list if we don't see any
6651    overlap, or NULL otherwise.  */
6652
6653 static gfc_case *
6654 check_case_overlap (gfc_case *list)
6655 {
6656   gfc_case *p, *q, *e, *tail;
6657   int insize, nmerges, psize, qsize, cmp, overlap_seen;
6658
6659   /* If the passed list was empty, return immediately.  */
6660   if (!list)
6661     return NULL;
6662
6663   overlap_seen = 0;
6664   insize = 1;
6665
6666   /* Loop unconditionally.  The only exit from this loop is a return
6667      statement, when we've finished sorting the case list.  */
6668   for (;;)
6669     {
6670       p = list;
6671       list = NULL;
6672       tail = NULL;
6673
6674       /* Count the number of merges we do in this pass.  */
6675       nmerges = 0;
6676
6677       /* Loop while there exists a merge to be done.  */
6678       while (p)
6679         {
6680           int i;
6681
6682           /* Count this merge.  */
6683           nmerges++;
6684
6685           /* Cut the list in two pieces by stepping INSIZE places
6686              forward in the list, starting from P.  */
6687           psize = 0;
6688           q = p;
6689           for (i = 0; i < insize; i++)
6690             {
6691               psize++;
6692               q = q->right;
6693               if (!q)
6694                 break;
6695             }
6696           qsize = insize;
6697
6698           /* Now we have two lists.  Merge them!  */
6699           while (psize > 0 || (qsize > 0 && q != NULL))
6700             {
6701               /* See from which the next case to merge comes from.  */
6702               if (psize == 0)
6703                 {
6704                   /* P is empty so the next case must come from Q.  */
6705                   e = q;
6706                   q = q->right;
6707                   qsize--;
6708                 }
6709               else if (qsize == 0 || q == NULL)
6710                 {
6711                   /* Q is empty.  */
6712                   e = p;
6713                   p = p->right;
6714                   psize--;
6715                 }
6716               else
6717                 {
6718                   cmp = compare_cases (p, q);
6719                   if (cmp < 0)
6720                     {
6721                       /* The whole case range for P is less than the
6722                          one for Q.  */
6723                       e = p;
6724                       p = p->right;
6725                       psize--;
6726                     }
6727                   else if (cmp > 0)
6728                     {
6729                       /* The whole case range for Q is greater than
6730                          the case range for P.  */
6731                       e = q;
6732                       q = q->right;
6733                       qsize--;
6734                     }
6735                   else
6736                     {
6737                       /* The cases overlap, or they are the same
6738                          element in the list.  Either way, we must
6739                          issue an error and get the next case from P.  */
6740                       /* FIXME: Sort P and Q by line number.  */
6741                       gfc_error ("CASE label at %L overlaps with CASE "
6742                                  "label at %L", &p->where, &q->where);
6743                       overlap_seen = 1;
6744                       e = p;
6745                       p = p->right;
6746                       psize--;
6747                     }
6748                 }
6749
6750                 /* Add the next element to the merged list.  */
6751               if (tail)
6752                 tail->right = e;
6753               else
6754                 list = e;
6755               e->left = tail;
6756               tail = e;
6757             }
6758
6759           /* P has now stepped INSIZE places along, and so has Q.  So
6760              they're the same.  */
6761           p = q;
6762         }
6763       tail->right = NULL;
6764
6765       /* If we have done only one merge or none at all, we've
6766          finished sorting the cases.  */
6767       if (nmerges <= 1)
6768         {
6769           if (!overlap_seen)
6770             return list;
6771           else
6772             return NULL;
6773         }
6774
6775       /* Otherwise repeat, merging lists twice the size.  */
6776       insize *= 2;
6777     }
6778 }
6779
6780
6781 /* Check to see if an expression is suitable for use in a CASE statement.
6782    Makes sure that all case expressions are scalar constants of the same
6783    type.  Return FAILURE if anything is wrong.  */
6784
6785 static gfc_try
6786 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
6787 {
6788   if (e == NULL) return SUCCESS;
6789
6790   if (e->ts.type != case_expr->ts.type)
6791     {
6792       gfc_error ("Expression in CASE statement at %L must be of type %s",
6793                  &e->where, gfc_basic_typename (case_expr->ts.type));
6794       return FAILURE;
6795     }
6796
6797   /* C805 (R808) For a given case-construct, each case-value shall be of
6798      the same type as case-expr.  For character type, length differences
6799      are allowed, but the kind type parameters shall be the same.  */
6800
6801   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
6802     {
6803       gfc_error ("Expression in CASE statement at %L must be of kind %d",
6804                  &e->where, case_expr->ts.kind);
6805       return FAILURE;
6806     }
6807
6808   /* Convert the case value kind to that of case expression kind,
6809      if needed */
6810
6811   if (e->ts.kind != case_expr->ts.kind)
6812     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
6813
6814   if (e->rank != 0)
6815     {
6816       gfc_error ("Expression in CASE statement at %L must be scalar",
6817                  &e->where);
6818       return FAILURE;
6819     }
6820
6821   return SUCCESS;
6822 }
6823
6824
6825 /* Given a completely parsed select statement, we:
6826
6827      - Validate all expressions and code within the SELECT.
6828      - Make sure that the selection expression is not of the wrong type.
6829      - Make sure that no case ranges overlap.
6830      - Eliminate unreachable cases and unreachable code resulting from
6831        removing case labels.
6832
6833    The standard does allow unreachable cases, e.g. CASE (5:3).  But
6834    they are a hassle for code generation, and to prevent that, we just
6835    cut them out here.  This is not necessary for overlapping cases
6836    because they are illegal and we never even try to generate code.
6837
6838    We have the additional caveat that a SELECT construct could have
6839    been a computed GOTO in the source code. Fortunately we can fairly
6840    easily work around that here: The case_expr for a "real" SELECT CASE
6841    is in code->expr1, but for a computed GOTO it is in code->expr2. All
6842    we have to do is make sure that the case_expr is a scalar integer
6843    expression.  */
6844
6845 static void
6846 resolve_select (gfc_code *code)
6847 {
6848   gfc_code *body;
6849   gfc_expr *case_expr;
6850   gfc_case *cp, *default_case, *tail, *head;
6851   int seen_unreachable;
6852   int seen_logical;
6853   int ncases;
6854   bt type;
6855   gfc_try t;
6856
6857   if (code->expr1 == NULL)
6858     {
6859       /* This was actually a computed GOTO statement.  */
6860       case_expr = code->expr2;
6861       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
6862         gfc_error ("Selection expression in computed GOTO statement "
6863                    "at %L must be a scalar integer expression",
6864                    &case_expr->where);
6865
6866       /* Further checking is not necessary because this SELECT was built
6867          by the compiler, so it should always be OK.  Just move the
6868          case_expr from expr2 to expr so that we can handle computed
6869          GOTOs as normal SELECTs from here on.  */
6870       code->expr1 = code->expr2;
6871       code->expr2 = NULL;
6872       return;
6873     }
6874
6875   case_expr = code->expr1;
6876
6877   type = case_expr->ts.type;
6878   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
6879     {
6880       gfc_error ("Argument of SELECT statement at %L cannot be %s",
6881                  &case_expr->where, gfc_typename (&case_expr->ts));
6882
6883       /* Punt. Going on here just produce more garbage error messages.  */
6884       return;
6885     }
6886
6887   if (case_expr->rank != 0)
6888     {
6889       gfc_error ("Argument of SELECT statement at %L must be a scalar "
6890                  "expression", &case_expr->where);
6891
6892       /* Punt.  */
6893       return;
6894     }
6895
6896
6897   /* Raise a warning if an INTEGER case value exceeds the range of
6898      the case-expr. Later, all expressions will be promoted to the
6899      largest kind of all case-labels.  */
6900
6901   if (type == BT_INTEGER)
6902     for (body = code->block; body; body = body->block)
6903       for (cp = body->ext.case_list; cp; cp = cp->next)
6904         {
6905           if (cp->low
6906               && gfc_check_integer_range (cp->low->value.integer,
6907                                           case_expr->ts.kind) != ARITH_OK)
6908             gfc_warning ("Expression in CASE statement at %L is "
6909                          "not in the range of %s", &cp->low->where,
6910                          gfc_typename (&case_expr->ts));
6911
6912           if (cp->high
6913               && cp->low != cp->high
6914               && gfc_check_integer_range (cp->high->value.integer,
6915                                           case_expr->ts.kind) != ARITH_OK)
6916             gfc_warning ("Expression in CASE statement at %L is "
6917                          "not in the range of %s", &cp->high->where,
6918                          gfc_typename (&case_expr->ts));
6919         }
6920
6921   /* PR 19168 has a long discussion concerning a mismatch of the kinds
6922      of the SELECT CASE expression and its CASE values.  Walk the lists
6923      of case values, and if we find a mismatch, promote case_expr to
6924      the appropriate kind.  */
6925
6926   if (type == BT_LOGICAL || type == BT_INTEGER)
6927     {
6928       for (body = code->block; body; body = body->block)
6929         {
6930           /* Walk the case label list.  */
6931           for (cp = body->ext.case_list; cp; cp = cp->next)
6932             {
6933               /* Intercept the DEFAULT case.  It does not have a kind.  */
6934               if (cp->low == NULL && cp->high == NULL)
6935                 continue;
6936
6937               /* Unreachable case ranges are discarded, so ignore.  */
6938               if (cp->low != NULL && cp->high != NULL
6939                   && cp->low != cp->high
6940                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
6941                 continue;
6942
6943               if (cp->low != NULL
6944                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
6945                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
6946
6947               if (cp->high != NULL
6948                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
6949                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
6950             }
6951          }
6952     }
6953
6954   /* Assume there is no DEFAULT case.  */
6955   default_case = NULL;
6956   head = tail = NULL;
6957   ncases = 0;
6958   seen_logical = 0;
6959
6960   for (body = code->block; body; body = body->block)
6961     {
6962       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
6963       t = SUCCESS;
6964       seen_unreachable = 0;
6965
6966       /* Walk the case label list, making sure that all case labels
6967          are legal.  */
6968       for (cp = body->ext.case_list; cp; cp = cp->next)
6969         {
6970           /* Count the number of cases in the whole construct.  */
6971           ncases++;
6972
6973           /* Intercept the DEFAULT case.  */
6974           if (cp->low == NULL && cp->high == NULL)
6975             {
6976               if (default_case != NULL)
6977                 {
6978                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
6979                              "by a second DEFAULT CASE at %L",
6980                              &default_case->where, &cp->where);
6981                   t = FAILURE;
6982                   break;
6983                 }
6984               else
6985                 {
6986                   default_case = cp;
6987                   continue;
6988                 }
6989             }
6990
6991           /* Deal with single value cases and case ranges.  Errors are
6992              issued from the validation function.  */
6993           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
6994               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
6995             {
6996               t = FAILURE;
6997               break;
6998             }
6999
7000           if (type == BT_LOGICAL
7001               && ((cp->low == NULL || cp->high == NULL)
7002                   || cp->low != cp->high))
7003             {
7004               gfc_error ("Logical range in CASE statement at %L is not "
7005                          "allowed", &cp->low->where);
7006               t = FAILURE;
7007               break;
7008             }
7009
7010           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7011             {
7012               int value;
7013               value = cp->low->value.logical == 0 ? 2 : 1;
7014               if (value & seen_logical)
7015                 {
7016                   gfc_error ("Constant logical value in CASE statement "
7017                              "is repeated at %L",
7018                              &cp->low->where);
7019                   t = FAILURE;
7020                   break;
7021                 }
7022               seen_logical |= value;
7023             }
7024
7025           if (cp->low != NULL && cp->high != NULL
7026               && cp->low != cp->high
7027               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7028             {
7029               if (gfc_option.warn_surprising)
7030                 gfc_warning ("Range specification at %L can never "
7031                              "be matched", &cp->where);
7032
7033               cp->unreachable = 1;
7034               seen_unreachable = 1;
7035             }
7036           else
7037             {
7038               /* If the case range can be matched, it can also overlap with
7039                  other cases.  To make sure it does not, we put it in a
7040                  double linked list here.  We sort that with a merge sort
7041                  later on to detect any overlapping cases.  */
7042               if (!head)
7043                 {
7044                   head = tail = cp;
7045                   head->right = head->left = NULL;
7046                 }
7047               else
7048                 {
7049                   tail->right = cp;
7050                   tail->right->left = tail;
7051                   tail = tail->right;
7052                   tail->right = NULL;
7053                 }
7054             }
7055         }
7056
7057       /* It there was a failure in the previous case label, give up
7058          for this case label list.  Continue with the next block.  */
7059       if (t == FAILURE)
7060         continue;
7061
7062       /* See if any case labels that are unreachable have been seen.
7063          If so, we eliminate them.  This is a bit of a kludge because
7064          the case lists for a single case statement (label) is a
7065          single forward linked lists.  */
7066       if (seen_unreachable)
7067       {
7068         /* Advance until the first case in the list is reachable.  */
7069         while (body->ext.case_list != NULL
7070                && body->ext.case_list->unreachable)
7071           {
7072             gfc_case *n = body->ext.case_list;
7073             body->ext.case_list = body->ext.case_list->next;
7074             n->next = NULL;
7075             gfc_free_case_list (n);
7076           }
7077
7078         /* Strip all other unreachable cases.  */
7079         if (body->ext.case_list)
7080           {
7081             for (cp = body->ext.case_list; cp->next; cp = cp->next)
7082               {
7083                 if (cp->next->unreachable)
7084                   {
7085                     gfc_case *n = cp->next;
7086                     cp->next = cp->next->next;
7087                     n->next = NULL;
7088                     gfc_free_case_list (n);
7089                   }
7090               }
7091           }
7092       }
7093     }
7094
7095   /* See if there were overlapping cases.  If the check returns NULL,
7096      there was overlap.  In that case we don't do anything.  If head
7097      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7098      then used during code generation for SELECT CASE constructs with
7099      a case expression of a CHARACTER type.  */
7100   if (head)
7101     {
7102       head = check_case_overlap (head);
7103
7104       /* Prepend the default_case if it is there.  */
7105       if (head != NULL && default_case)
7106         {
7107           default_case->left = NULL;
7108           default_case->right = head;
7109           head->left = default_case;
7110         }
7111     }
7112
7113   /* Eliminate dead blocks that may be the result if we've seen
7114      unreachable case labels for a block.  */
7115   for (body = code; body && body->block; body = body->block)
7116     {
7117       if (body->block->ext.case_list == NULL)
7118         {
7119           /* Cut the unreachable block from the code chain.  */
7120           gfc_code *c = body->block;
7121           body->block = c->block;
7122
7123           /* Kill the dead block, but not the blocks below it.  */
7124           c->block = NULL;
7125           gfc_free_statements (c);
7126         }
7127     }
7128
7129   /* More than two cases is legal but insane for logical selects.
7130      Issue a warning for it.  */
7131   if (gfc_option.warn_surprising && type == BT_LOGICAL
7132       && ncases > 2)
7133     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7134                  &code->loc);
7135 }
7136
7137
7138 /* Check if a derived type is extensible.  */
7139
7140 bool
7141 gfc_type_is_extensible (gfc_symbol *sym)
7142 {
7143   return !(sym->attr.is_bind_c || sym->attr.sequence);
7144 }
7145
7146
7147 /* Resolve a SELECT TYPE statement.  */
7148
7149 static void
7150 resolve_select_type (gfc_code *code)
7151 {
7152   gfc_symbol *selector_type;
7153   gfc_code *body, *new_st, *if_st, *tail;
7154   gfc_code *class_is = NULL, *default_case = NULL;
7155   gfc_case *c;
7156   gfc_symtree *st;
7157   char name[GFC_MAX_SYMBOL_LEN];
7158   gfc_namespace *ns;
7159   int error = 0;
7160
7161   ns = code->ext.ns;
7162   gfc_resolve (ns);
7163
7164   /* Check for F03:C813.  */
7165   if (code->expr1->ts.type != BT_CLASS
7166       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
7167     {
7168       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
7169                  "at %L", &code->loc);
7170       return;
7171     }
7172
7173   if (code->expr2)
7174     {
7175       if (code->expr1->symtree->n.sym->attr.untyped)
7176         code->expr1->symtree->n.sym->ts = code->expr2->ts;
7177       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
7178     }
7179   else
7180     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
7181
7182   /* Loop over TYPE IS / CLASS IS cases.  */
7183   for (body = code->block; body; body = body->block)
7184     {
7185       c = body->ext.case_list;
7186
7187       /* Check F03:C815.  */
7188       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7189           && !gfc_type_is_extensible (c->ts.u.derived))
7190         {
7191           gfc_error ("Derived type '%s' at %L must be extensible",
7192                      c->ts.u.derived->name, &c->where);
7193           error++;
7194           continue;
7195         }
7196
7197       /* Check F03:C816.  */
7198       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7199           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
7200         {
7201           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
7202                      c->ts.u.derived->name, &c->where, selector_type->name);
7203           error++;
7204           continue;
7205         }
7206
7207       /* Intercept the DEFAULT case.  */
7208       if (c->ts.type == BT_UNKNOWN)
7209         {
7210           /* Check F03:C818.  */
7211           if (default_case)
7212             {
7213               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7214                          "by a second DEFAULT CASE at %L",
7215                          &default_case->ext.case_list->where, &c->where);
7216               error++;
7217               continue;
7218             }
7219           else
7220             default_case = body;
7221         }
7222     }
7223     
7224   if (error>0)
7225     return;
7226
7227   if (code->expr2)
7228     {
7229       /* Insert assignment for selector variable.  */
7230       new_st = gfc_get_code ();
7231       new_st->op = EXEC_ASSIGN;
7232       new_st->expr1 = gfc_copy_expr (code->expr1);
7233       new_st->expr2 = gfc_copy_expr (code->expr2);
7234       ns->code = new_st;
7235     }
7236
7237   /* Put SELECT TYPE statement inside a BLOCK.  */
7238   new_st = gfc_get_code ();
7239   new_st->op = code->op;
7240   new_st->expr1 = code->expr1;
7241   new_st->expr2 = code->expr2;
7242   new_st->block = code->block;
7243   if (!ns->code)
7244     ns->code = new_st;
7245   else
7246     ns->code->next = new_st;
7247   code->op = EXEC_BLOCK;
7248   code->expr1 = code->expr2 =  NULL;
7249   code->block = NULL;
7250
7251   code = new_st;
7252
7253   /* Transform to EXEC_SELECT.  */
7254   code->op = EXEC_SELECT;
7255   gfc_add_component_ref (code->expr1, "$vptr");
7256   gfc_add_component_ref (code->expr1, "$hash");
7257
7258   /* Loop over TYPE IS / CLASS IS cases.  */
7259   for (body = code->block; body; body = body->block)
7260     {
7261       c = body->ext.case_list;
7262
7263       if (c->ts.type == BT_DERIVED)
7264         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
7265                                              c->ts.u.derived->hash_value);
7266
7267       else if (c->ts.type == BT_UNKNOWN)
7268         continue;
7269
7270       /* Assign temporary to selector.  */
7271       if (c->ts.type == BT_CLASS)
7272         sprintf (name, "tmp$class$%s", c->ts.u.derived->name);
7273       else
7274         sprintf (name, "tmp$type$%s", c->ts.u.derived->name);
7275       st = gfc_find_symtree (ns->sym_root, name);
7276       new_st = gfc_get_code ();
7277       new_st->expr1 = gfc_get_variable_expr (st);
7278       new_st->expr2 = gfc_get_variable_expr (code->expr1->symtree);
7279       if (c->ts.type == BT_DERIVED)
7280         {
7281           new_st->op = EXEC_POINTER_ASSIGN;
7282           gfc_add_component_ref (new_st->expr2, "$data");
7283         }
7284       else
7285         new_st->op = EXEC_POINTER_ASSIGN;
7286       new_st->next = body->next;
7287       body->next = new_st;
7288     }
7289     
7290   /* Take out CLASS IS cases for separate treatment.  */
7291   body = code;
7292   while (body && body->block)
7293     {
7294       if (body->block->ext.case_list->ts.type == BT_CLASS)
7295         {
7296           /* Add to class_is list.  */
7297           if (class_is == NULL)
7298             { 
7299               class_is = body->block;
7300               tail = class_is;
7301             }
7302           else
7303             {
7304               for (tail = class_is; tail->block; tail = tail->block) ;
7305               tail->block = body->block;
7306               tail = tail->block;
7307             }
7308           /* Remove from EXEC_SELECT list.  */
7309           body->block = body->block->block;
7310           tail->block = NULL;
7311         }
7312       else
7313         body = body->block;
7314     }
7315
7316   if (class_is)
7317     {
7318       gfc_symbol *vtab;
7319       
7320       if (!default_case)
7321         {
7322           /* Add a default case to hold the CLASS IS cases.  */
7323           for (tail = code; tail->block; tail = tail->block) ;
7324           tail->block = gfc_get_code ();
7325           tail = tail->block;
7326           tail->op = EXEC_SELECT_TYPE;
7327           tail->ext.case_list = gfc_get_case ();
7328           tail->ext.case_list->ts.type = BT_UNKNOWN;
7329           tail->next = NULL;
7330           default_case = tail;
7331         }
7332
7333       /* More than one CLASS IS block?  */
7334       if (class_is->block)
7335         {
7336           gfc_code **c1,*c2;
7337           bool swapped;
7338           /* Sort CLASS IS blocks by extension level.  */
7339           do
7340             {
7341               swapped = false;
7342               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
7343                 {
7344                   c2 = (*c1)->block;
7345                   /* F03:C817 (check for doubles).  */
7346                   if ((*c1)->ext.case_list->ts.u.derived->hash_value
7347                       == c2->ext.case_list->ts.u.derived->hash_value)
7348                     {
7349                       gfc_error ("Double CLASS IS block in SELECT TYPE "
7350                                  "statement at %L", &c2->ext.case_list->where);
7351                       return;
7352                     }
7353                   if ((*c1)->ext.case_list->ts.u.derived->attr.extension
7354                       < c2->ext.case_list->ts.u.derived->attr.extension)
7355                     {
7356                       /* Swap.  */
7357                       (*c1)->block = c2->block;
7358                       c2->block = *c1;
7359                       *c1 = c2;
7360                       swapped = true;
7361                     }
7362                 }
7363             }
7364           while (swapped);
7365         }
7366         
7367       /* Generate IF chain.  */
7368       if_st = gfc_get_code ();
7369       if_st->op = EXEC_IF;
7370       new_st = if_st;
7371       for (body = class_is; body; body = body->block)
7372         {
7373           new_st->block = gfc_get_code ();
7374           new_st = new_st->block;
7375           new_st->op = EXEC_IF;
7376           /* Set up IF condition: Call _gfortran_is_extension_of.  */
7377           new_st->expr1 = gfc_get_expr ();
7378           new_st->expr1->expr_type = EXPR_FUNCTION;
7379           new_st->expr1->ts.type = BT_LOGICAL;
7380           new_st->expr1->ts.kind = 4;
7381           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
7382           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
7383           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
7384           /* Set up arguments.  */
7385           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
7386           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
7387           gfc_add_component_ref (new_st->expr1->value.function.actual->expr, "$vptr");
7388           vtab = gfc_find_derived_vtab (body->ext.case_list->ts.u.derived, true);
7389           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
7390           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
7391           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
7392           new_st->next = body->next;
7393         }
7394         if (default_case->next)
7395           {
7396             new_st->block = gfc_get_code ();
7397             new_st = new_st->block;
7398             new_st->op = EXEC_IF;
7399             new_st->next = default_case->next;
7400           }
7401           
7402         /* Replace CLASS DEFAULT code by the IF chain.  */
7403         default_case->next = if_st;
7404     }
7405
7406   resolve_select (code);
7407
7408 }
7409
7410
7411 /* Resolve a transfer statement. This is making sure that:
7412    -- a derived type being transferred has only non-pointer components
7413    -- a derived type being transferred doesn't have private components, unless 
7414       it's being transferred from the module where the type was defined
7415    -- we're not trying to transfer a whole assumed size array.  */
7416
7417 static void
7418 resolve_transfer (gfc_code *code)
7419 {
7420   gfc_typespec *ts;
7421   gfc_symbol *sym;
7422   gfc_ref *ref;
7423   gfc_expr *exp;
7424
7425   exp = code->expr1;
7426
7427   if (exp->expr_type != EXPR_VARIABLE && exp->expr_type != EXPR_FUNCTION)
7428     return;
7429
7430   sym = exp->symtree->n.sym;
7431   ts = &sym->ts;
7432
7433   /* Go to actual component transferred.  */
7434   for (ref = code->expr1->ref; ref; ref = ref->next)
7435     if (ref->type == REF_COMPONENT)
7436       ts = &ref->u.c.component->ts;
7437
7438   if (ts->type == BT_DERIVED)
7439     {
7440       /* Check that transferred derived type doesn't contain POINTER
7441          components.  */
7442       if (ts->u.derived->attr.pointer_comp)
7443         {
7444           gfc_error ("Data transfer element at %L cannot have "
7445                      "POINTER components", &code->loc);
7446           return;
7447         }
7448
7449       if (ts->u.derived->attr.alloc_comp)
7450         {
7451           gfc_error ("Data transfer element at %L cannot have "
7452                      "ALLOCATABLE components", &code->loc);
7453           return;
7454         }
7455
7456       if (derived_inaccessible (ts->u.derived))
7457         {
7458           gfc_error ("Data transfer element at %L cannot have "
7459                      "PRIVATE components",&code->loc);
7460           return;
7461         }
7462     }
7463
7464   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
7465       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
7466     {
7467       gfc_error ("Data transfer element at %L cannot be a full reference to "
7468                  "an assumed-size array", &code->loc);
7469       return;
7470     }
7471 }
7472
7473
7474 /*********** Toplevel code resolution subroutines ***********/
7475
7476 /* Find the set of labels that are reachable from this block.  We also
7477    record the last statement in each block.  */
7478      
7479 static void
7480 find_reachable_labels (gfc_code *block)
7481 {
7482   gfc_code *c;
7483
7484   if (!block)
7485     return;
7486
7487   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
7488
7489   /* Collect labels in this block.  We don't keep those corresponding
7490      to END {IF|SELECT}, these are checked in resolve_branch by going
7491      up through the code_stack.  */
7492   for (c = block; c; c = c->next)
7493     {
7494       if (c->here && c->op != EXEC_END_BLOCK)
7495         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
7496     }
7497
7498   /* Merge with labels from parent block.  */
7499   if (cs_base->prev)
7500     {
7501       gcc_assert (cs_base->prev->reachable_labels);
7502       bitmap_ior_into (cs_base->reachable_labels,
7503                        cs_base->prev->reachable_labels);
7504     }
7505 }
7506
7507
7508 static void
7509 resolve_sync (gfc_code *code)
7510 {
7511   /* Check imageset. The * case matches expr1 == NULL.  */
7512   if (code->expr1)
7513     {
7514       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
7515         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
7516                    "INTEGER expression", &code->expr1->where);
7517       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
7518           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
7519         gfc_error ("Imageset argument at %L must between 1 and num_images()",
7520                    &code->expr1->where);
7521       else if (code->expr1->expr_type == EXPR_ARRAY
7522                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
7523         {
7524            gfc_constructor *cons;
7525            cons = gfc_constructor_first (code->expr1->value.constructor);
7526            for (; cons; cons = gfc_constructor_next (cons))
7527              if (cons->expr->expr_type == EXPR_CONSTANT
7528                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
7529                gfc_error ("Imageset argument at %L must between 1 and "
7530                           "num_images()", &cons->expr->where);
7531         }
7532     }
7533
7534   /* Check STAT.  */
7535   if (code->expr2
7536       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
7537           || code->expr2->expr_type != EXPR_VARIABLE))
7538     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
7539                &code->expr2->where);
7540
7541   /* Check ERRMSG.  */
7542   if (code->expr3
7543       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
7544           || code->expr3->expr_type != EXPR_VARIABLE))
7545     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
7546                &code->expr3->where);
7547 }
7548
7549
7550 /* Given a branch to a label, see if the branch is conforming.
7551    The code node describes where the branch is located.  */
7552
7553 static void
7554 resolve_branch (gfc_st_label *label, gfc_code *code)
7555 {
7556   code_stack *stack;
7557
7558   if (label == NULL)
7559     return;
7560
7561   /* Step one: is this a valid branching target?  */
7562
7563   if (label->defined == ST_LABEL_UNKNOWN)
7564     {
7565       gfc_error ("Label %d referenced at %L is never defined", label->value,
7566                  &label->where);
7567       return;
7568     }
7569
7570   if (label->defined != ST_LABEL_TARGET)
7571     {
7572       gfc_error ("Statement at %L is not a valid branch target statement "
7573                  "for the branch statement at %L", &label->where, &code->loc);
7574       return;
7575     }
7576
7577   /* Step two: make sure this branch is not a branch to itself ;-)  */
7578
7579   if (code->here == label)
7580     {
7581       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
7582       return;
7583     }
7584
7585   /* Step three:  See if the label is in the same block as the
7586      branching statement.  The hard work has been done by setting up
7587      the bitmap reachable_labels.  */
7588
7589   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
7590     {
7591       /* Check now whether there is a CRITICAL construct; if so, check
7592          whether the label is still visible outside of the CRITICAL block,
7593          which is invalid.  */
7594       for (stack = cs_base; stack; stack = stack->prev)
7595         if (stack->current->op == EXEC_CRITICAL
7596             && bitmap_bit_p (stack->reachable_labels, label->value))
7597           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
7598                       " at %L", &code->loc, &label->where);
7599
7600       return;
7601     }
7602
7603   /* Step four:  If we haven't found the label in the bitmap, it may
7604     still be the label of the END of the enclosing block, in which
7605     case we find it by going up the code_stack.  */
7606
7607   for (stack = cs_base; stack; stack = stack->prev)
7608     {
7609       if (stack->current->next && stack->current->next->here == label)
7610         break;
7611       if (stack->current->op == EXEC_CRITICAL)
7612         {
7613           /* Note: A label at END CRITICAL does not leave the CRITICAL
7614              construct as END CRITICAL is still part of it.  */
7615           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
7616                       " at %L", &code->loc, &label->where);
7617           return;
7618         }
7619     }
7620
7621   if (stack)
7622     {
7623       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
7624       return;
7625     }
7626
7627   /* The label is not in an enclosing block, so illegal.  This was
7628      allowed in Fortran 66, so we allow it as extension.  No
7629      further checks are necessary in this case.  */
7630   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
7631                   "as the GOTO statement at %L", &label->where,
7632                   &code->loc);
7633   return;
7634 }
7635
7636
7637 /* Check whether EXPR1 has the same shape as EXPR2.  */
7638
7639 static gfc_try
7640 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
7641 {
7642   mpz_t shape[GFC_MAX_DIMENSIONS];
7643   mpz_t shape2[GFC_MAX_DIMENSIONS];
7644   gfc_try result = FAILURE;
7645   int i;
7646
7647   /* Compare the rank.  */
7648   if (expr1->rank != expr2->rank)
7649     return result;
7650
7651   /* Compare the size of each dimension.  */
7652   for (i=0; i<expr1->rank; i++)
7653     {
7654       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
7655         goto ignore;
7656
7657       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
7658         goto ignore;
7659
7660       if (mpz_cmp (shape[i], shape2[i]))
7661         goto over;
7662     }
7663
7664   /* When either of the two expression is an assumed size array, we
7665      ignore the comparison of dimension sizes.  */
7666 ignore:
7667   result = SUCCESS;
7668
7669 over:
7670   for (i--; i >= 0; i--)
7671     {
7672       mpz_clear (shape[i]);
7673       mpz_clear (shape2[i]);
7674     }
7675   return result;
7676 }
7677
7678
7679 /* Check whether a WHERE assignment target or a WHERE mask expression
7680    has the same shape as the outmost WHERE mask expression.  */
7681
7682 static void
7683 resolve_where (gfc_code *code, gfc_expr *mask)
7684 {
7685   gfc_code *cblock;
7686   gfc_code *cnext;
7687   gfc_expr *e = NULL;
7688
7689   cblock = code->block;
7690
7691   /* Store the first WHERE mask-expr of the WHERE statement or construct.
7692      In case of nested WHERE, only the outmost one is stored.  */
7693   if (mask == NULL) /* outmost WHERE */
7694     e = cblock->expr1;
7695   else /* inner WHERE */
7696     e = mask;
7697
7698   while (cblock)
7699     {
7700       if (cblock->expr1)
7701         {
7702           /* Check if the mask-expr has a consistent shape with the
7703              outmost WHERE mask-expr.  */
7704           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
7705             gfc_error ("WHERE mask at %L has inconsistent shape",
7706                        &cblock->expr1->where);
7707          }
7708
7709       /* the assignment statement of a WHERE statement, or the first
7710          statement in where-body-construct of a WHERE construct */
7711       cnext = cblock->next;
7712       while (cnext)
7713         {
7714           switch (cnext->op)
7715             {
7716             /* WHERE assignment statement */
7717             case EXEC_ASSIGN:
7718
7719               /* Check shape consistent for WHERE assignment target.  */
7720               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
7721                gfc_error ("WHERE assignment target at %L has "
7722                           "inconsistent shape", &cnext->expr1->where);
7723               break;
7724
7725   
7726             case EXEC_ASSIGN_CALL:
7727               resolve_call (cnext);
7728               if (!cnext->resolved_sym->attr.elemental)
7729                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7730                           &cnext->ext.actual->expr->where);
7731               break;
7732
7733             /* WHERE or WHERE construct is part of a where-body-construct */
7734             case EXEC_WHERE:
7735               resolve_where (cnext, e);
7736               break;
7737
7738             default:
7739               gfc_error ("Unsupported statement inside WHERE at %L",
7740                          &cnext->loc);
7741             }
7742          /* the next statement within the same where-body-construct */
7743          cnext = cnext->next;
7744        }
7745     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7746     cblock = cblock->block;
7747   }
7748 }
7749
7750
7751 /* Resolve assignment in FORALL construct.
7752    NVAR is the number of FORALL index variables, and VAR_EXPR records the
7753    FORALL index variables.  */
7754
7755 static void
7756 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
7757 {
7758   int n;
7759
7760   for (n = 0; n < nvar; n++)
7761     {
7762       gfc_symbol *forall_index;
7763
7764       forall_index = var_expr[n]->symtree->n.sym;
7765
7766       /* Check whether the assignment target is one of the FORALL index
7767          variable.  */
7768       if ((code->expr1->expr_type == EXPR_VARIABLE)
7769           && (code->expr1->symtree->n.sym == forall_index))
7770         gfc_error ("Assignment to a FORALL index variable at %L",
7771                    &code->expr1->where);
7772       else
7773         {
7774           /* If one of the FORALL index variables doesn't appear in the
7775              assignment variable, then there could be a many-to-one
7776              assignment.  Emit a warning rather than an error because the
7777              mask could be resolving this problem.  */
7778           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
7779             gfc_warning ("The FORALL with index '%s' is not used on the "
7780                          "left side of the assignment at %L and so might "
7781                          "cause multiple assignment to this object",
7782                          var_expr[n]->symtree->name, &code->expr1->where);
7783         }
7784     }
7785 }
7786
7787
7788 /* Resolve WHERE statement in FORALL construct.  */
7789
7790 static void
7791 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
7792                                   gfc_expr **var_expr)
7793 {
7794   gfc_code *cblock;
7795   gfc_code *cnext;
7796
7797   cblock = code->block;
7798   while (cblock)
7799     {
7800       /* the assignment statement of a WHERE statement, or the first
7801          statement in where-body-construct of a WHERE construct */
7802       cnext = cblock->next;
7803       while (cnext)
7804         {
7805           switch (cnext->op)
7806             {
7807             /* WHERE assignment statement */
7808             case EXEC_ASSIGN:
7809               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
7810               break;
7811   
7812             /* WHERE operator assignment statement */
7813             case EXEC_ASSIGN_CALL:
7814               resolve_call (cnext);
7815               if (!cnext->resolved_sym->attr.elemental)
7816                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
7817                           &cnext->ext.actual->expr->where);
7818               break;
7819
7820             /* WHERE or WHERE construct is part of a where-body-construct */
7821             case EXEC_WHERE:
7822               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
7823               break;
7824
7825             default:
7826               gfc_error ("Unsupported statement inside WHERE at %L",
7827                          &cnext->loc);
7828             }
7829           /* the next statement within the same where-body-construct */
7830           cnext = cnext->next;
7831         }
7832       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
7833       cblock = cblock->block;
7834     }
7835 }
7836
7837
7838 /* Traverse the FORALL body to check whether the following errors exist:
7839    1. For assignment, check if a many-to-one assignment happens.
7840    2. For WHERE statement, check the WHERE body to see if there is any
7841       many-to-one assignment.  */
7842
7843 static void
7844 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
7845 {
7846   gfc_code *c;
7847
7848   c = code->block->next;
7849   while (c)
7850     {
7851       switch (c->op)
7852         {
7853         case EXEC_ASSIGN:
7854         case EXEC_POINTER_ASSIGN:
7855           gfc_resolve_assign_in_forall (c, nvar, var_expr);
7856           break;
7857
7858         case EXEC_ASSIGN_CALL:
7859           resolve_call (c);
7860           break;
7861
7862         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
7863            there is no need to handle it here.  */
7864         case EXEC_FORALL:
7865           break;
7866         case EXEC_WHERE:
7867           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
7868           break;
7869         default:
7870           break;
7871         }
7872       /* The next statement in the FORALL body.  */
7873       c = c->next;
7874     }
7875 }
7876
7877
7878 /* Counts the number of iterators needed inside a forall construct, including
7879    nested forall constructs. This is used to allocate the needed memory 
7880    in gfc_resolve_forall.  */
7881
7882 static int 
7883 gfc_count_forall_iterators (gfc_code *code)
7884 {
7885   int max_iters, sub_iters, current_iters;
7886   gfc_forall_iterator *fa;
7887
7888   gcc_assert(code->op == EXEC_FORALL);
7889   max_iters = 0;
7890   current_iters = 0;
7891
7892   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7893     current_iters ++;
7894   
7895   code = code->block->next;
7896
7897   while (code)
7898     {          
7899       if (code->op == EXEC_FORALL)
7900         {
7901           sub_iters = gfc_count_forall_iterators (code);
7902           if (sub_iters > max_iters)
7903             max_iters = sub_iters;
7904         }
7905       code = code->next;
7906     }
7907
7908   return current_iters + max_iters;
7909 }
7910
7911
7912 /* Given a FORALL construct, first resolve the FORALL iterator, then call
7913    gfc_resolve_forall_body to resolve the FORALL body.  */
7914
7915 static void
7916 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
7917 {
7918   static gfc_expr **var_expr;
7919   static int total_var = 0;
7920   static int nvar = 0;
7921   int old_nvar, tmp;
7922   gfc_forall_iterator *fa;
7923   int i;
7924
7925   old_nvar = nvar;
7926
7927   /* Start to resolve a FORALL construct   */
7928   if (forall_save == 0)
7929     {
7930       /* Count the total number of FORALL index in the nested FORALL
7931          construct in order to allocate the VAR_EXPR with proper size.  */
7932       total_var = gfc_count_forall_iterators (code);
7933
7934       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
7935       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
7936     }
7937
7938   /* The information about FORALL iterator, including FORALL index start, end
7939      and stride. The FORALL index can not appear in start, end or stride.  */
7940   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
7941     {
7942       /* Check if any outer FORALL index name is the same as the current
7943          one.  */
7944       for (i = 0; i < nvar; i++)
7945         {
7946           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
7947             {
7948               gfc_error ("An outer FORALL construct already has an index "
7949                          "with this name %L", &fa->var->where);
7950             }
7951         }
7952
7953       /* Record the current FORALL index.  */
7954       var_expr[nvar] = gfc_copy_expr (fa->var);
7955
7956       nvar++;
7957
7958       /* No memory leak.  */
7959       gcc_assert (nvar <= total_var);
7960     }
7961
7962   /* Resolve the FORALL body.  */
7963   gfc_resolve_forall_body (code, nvar, var_expr);
7964
7965   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
7966   gfc_resolve_blocks (code->block, ns);
7967
7968   tmp = nvar;
7969   nvar = old_nvar;
7970   /* Free only the VAR_EXPRs allocated in this frame.  */
7971   for (i = nvar; i < tmp; i++)
7972      gfc_free_expr (var_expr[i]);
7973
7974   if (nvar == 0)
7975     {
7976       /* We are in the outermost FORALL construct.  */
7977       gcc_assert (forall_save == 0);
7978
7979       /* VAR_EXPR is not needed any more.  */
7980       gfc_free (var_expr);
7981       total_var = 0;
7982     }
7983 }
7984
7985
7986 /* Resolve a BLOCK construct statement.  */
7987
7988 static void
7989 resolve_block_construct (gfc_code* code)
7990 {
7991   /* Eventually, we may want to do some checks here or handle special stuff.
7992      But so far the only thing we can do is resolving the local namespace.  */
7993
7994   gfc_resolve (code->ext.ns);
7995 }
7996
7997
7998 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
7999    DO code nodes.  */
8000
8001 static void resolve_code (gfc_code *, gfc_namespace *);
8002
8003 void
8004 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8005 {
8006   gfc_try t;
8007
8008   for (; b; b = b->block)
8009     {
8010       t = gfc_resolve_expr (b->expr1);
8011       if (gfc_resolve_expr (b->expr2) == FAILURE)
8012         t = FAILURE;
8013
8014       switch (b->op)
8015         {
8016         case EXEC_IF:
8017           if (t == SUCCESS && b->expr1 != NULL
8018               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8019             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8020                        &b->expr1->where);
8021           break;
8022
8023         case EXEC_WHERE:
8024           if (t == SUCCESS
8025               && b->expr1 != NULL
8026               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8027             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8028                        &b->expr1->where);
8029           break;
8030
8031         case EXEC_GOTO:
8032           resolve_branch (b->label1, b);
8033           break;
8034
8035         case EXEC_BLOCK:
8036           resolve_block_construct (b);
8037           break;
8038
8039         case EXEC_SELECT:
8040         case EXEC_SELECT_TYPE:
8041         case EXEC_FORALL:
8042         case EXEC_DO:
8043         case EXEC_DO_WHILE:
8044         case EXEC_CRITICAL:
8045         case EXEC_READ:
8046         case EXEC_WRITE:
8047         case EXEC_IOLENGTH:
8048         case EXEC_WAIT:
8049           break;
8050
8051         case EXEC_OMP_ATOMIC:
8052         case EXEC_OMP_CRITICAL:
8053         case EXEC_OMP_DO:
8054         case EXEC_OMP_MASTER:
8055         case EXEC_OMP_ORDERED:
8056         case EXEC_OMP_PARALLEL:
8057         case EXEC_OMP_PARALLEL_DO:
8058         case EXEC_OMP_PARALLEL_SECTIONS:
8059         case EXEC_OMP_PARALLEL_WORKSHARE:
8060         case EXEC_OMP_SECTIONS:
8061         case EXEC_OMP_SINGLE:
8062         case EXEC_OMP_TASK:
8063         case EXEC_OMP_TASKWAIT:
8064         case EXEC_OMP_WORKSHARE:
8065           break;
8066
8067         default:
8068           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
8069         }
8070
8071       resolve_code (b->next, ns);
8072     }
8073 }
8074
8075
8076 /* Does everything to resolve an ordinary assignment.  Returns true
8077    if this is an interface assignment.  */
8078 static bool
8079 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
8080 {
8081   bool rval = false;
8082   gfc_expr *lhs;
8083   gfc_expr *rhs;
8084   int llen = 0;
8085   int rlen = 0;
8086   int n;
8087   gfc_ref *ref;
8088
8089   if (gfc_extend_assign (code, ns) == SUCCESS)
8090     {
8091       gfc_expr** rhsptr;
8092
8093       if (code->op == EXEC_ASSIGN_CALL)
8094         {
8095           lhs = code->ext.actual->expr;
8096           rhsptr = &code->ext.actual->next->expr;
8097         }
8098       else
8099         {
8100           gfc_actual_arglist* args;
8101           gfc_typebound_proc* tbp;
8102
8103           gcc_assert (code->op == EXEC_COMPCALL);
8104
8105           args = code->expr1->value.compcall.actual;
8106           lhs = args->expr;
8107           rhsptr = &args->next->expr;
8108
8109           tbp = code->expr1->value.compcall.tbp;
8110           gcc_assert (!tbp->is_generic);
8111         }
8112
8113       /* Make a temporary rhs when there is a default initializer
8114          and rhs is the same symbol as the lhs.  */
8115       if ((*rhsptr)->expr_type == EXPR_VARIABLE
8116             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
8117             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
8118             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
8119         *rhsptr = gfc_get_parentheses (*rhsptr);
8120
8121       return true;
8122     }
8123
8124   lhs = code->expr1;
8125   rhs = code->expr2;
8126
8127   if (rhs->is_boz
8128       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
8129                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
8130                          &code->loc) == FAILURE)
8131     return false;
8132
8133   /* Handle the case of a BOZ literal on the RHS.  */
8134   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
8135     {
8136       int rc;
8137       if (gfc_option.warn_surprising)
8138         gfc_warning ("BOZ literal at %L is bitwise transferred "
8139                      "non-integer symbol '%s'", &code->loc,
8140                      lhs->symtree->n.sym->name);
8141
8142       if (!gfc_convert_boz (rhs, &lhs->ts))
8143         return false;
8144       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
8145         {
8146           if (rc == ARITH_UNDERFLOW)
8147             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
8148                        ". This check can be disabled with the option "
8149                        "-fno-range-check", &rhs->where);
8150           else if (rc == ARITH_OVERFLOW)
8151             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
8152                        ". This check can be disabled with the option "
8153                        "-fno-range-check", &rhs->where);
8154           else if (rc == ARITH_NAN)
8155             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
8156                        ". This check can be disabled with the option "
8157                        "-fno-range-check", &rhs->where);
8158           return false;
8159         }
8160     }
8161
8162
8163   if (lhs->ts.type == BT_CHARACTER
8164         && gfc_option.warn_character_truncation)
8165     {
8166       if (lhs->ts.u.cl != NULL
8167             && lhs->ts.u.cl->length != NULL
8168             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8169         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
8170
8171       if (rhs->expr_type == EXPR_CONSTANT)
8172         rlen = rhs->value.character.length;
8173
8174       else if (rhs->ts.u.cl != NULL
8175                  && rhs->ts.u.cl->length != NULL
8176                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8177         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
8178
8179       if (rlen && llen && rlen > llen)
8180         gfc_warning_now ("CHARACTER expression will be truncated "
8181                          "in assignment (%d/%d) at %L",
8182                          llen, rlen, &code->loc);
8183     }
8184
8185   /* Ensure that a vector index expression for the lvalue is evaluated
8186      to a temporary if the lvalue symbol is referenced in it.  */
8187   if (lhs->rank)
8188     {
8189       for (ref = lhs->ref; ref; ref= ref->next)
8190         if (ref->type == REF_ARRAY)
8191           {
8192             for (n = 0; n < ref->u.ar.dimen; n++)
8193               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
8194                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
8195                                            ref->u.ar.start[n]))
8196                 ref->u.ar.start[n]
8197                         = gfc_get_parentheses (ref->u.ar.start[n]);
8198           }
8199     }
8200
8201   if (gfc_pure (NULL))
8202     {
8203       if (gfc_impure_variable (lhs->symtree->n.sym))
8204         {
8205           gfc_error ("Cannot assign to variable '%s' in PURE "
8206                      "procedure at %L",
8207                       lhs->symtree->n.sym->name,
8208                       &lhs->where);
8209           return rval;
8210         }
8211
8212       if (lhs->ts.type == BT_DERIVED
8213             && lhs->expr_type == EXPR_VARIABLE
8214             && lhs->ts.u.derived->attr.pointer_comp
8215             && rhs->expr_type == EXPR_VARIABLE
8216             && (gfc_impure_variable (rhs->symtree->n.sym)
8217                 || gfc_is_coindexed (rhs)))
8218         {
8219           /* F2008, C1283.  */
8220           if (gfc_is_coindexed (rhs))
8221             gfc_error ("Coindexed expression at %L is assigned to "
8222                         "a derived type variable with a POINTER "
8223                         "component in a PURE procedure",
8224                         &rhs->where);
8225           else
8226             gfc_error ("The impure variable at %L is assigned to "
8227                         "a derived type variable with a POINTER "
8228                         "component in a PURE procedure (12.6)",
8229                         &rhs->where);
8230           return rval;
8231         }
8232
8233       /* Fortran 2008, C1283.  */
8234       if (gfc_is_coindexed (lhs))
8235         {
8236           gfc_error ("Assignment to coindexed variable at %L in a PURE "
8237                      "procedure", &rhs->where);
8238           return rval;
8239         }
8240     }
8241
8242   /* F03:7.4.1.2.  */
8243   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
8244      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
8245   if (lhs->ts.type == BT_CLASS)
8246     {
8247       gfc_error ("Variable must not be polymorphic in assignment at %L",
8248                  &lhs->where);
8249       return false;
8250     }
8251
8252   /* F2008, Section 7.2.1.2.  */
8253   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
8254     {
8255       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
8256                  "component in assignment at %L", &lhs->where);
8257       return false;
8258     }
8259
8260   gfc_check_assign (lhs, rhs, 1);
8261   return false;
8262 }
8263
8264
8265 /* Given a block of code, recursively resolve everything pointed to by this
8266    code block.  */
8267
8268 static void
8269 resolve_code (gfc_code *code, gfc_namespace *ns)
8270 {
8271   int omp_workshare_save;
8272   int forall_save;
8273   code_stack frame;
8274   gfc_try t;
8275
8276   frame.prev = cs_base;
8277   frame.head = code;
8278   cs_base = &frame;
8279
8280   find_reachable_labels (code);
8281
8282   for (; code; code = code->next)
8283     {
8284       frame.current = code;
8285       forall_save = forall_flag;
8286
8287       if (code->op == EXEC_FORALL)
8288         {
8289           forall_flag = 1;
8290           gfc_resolve_forall (code, ns, forall_save);
8291           forall_flag = 2;
8292         }
8293       else if (code->block)
8294         {
8295           omp_workshare_save = -1;
8296           switch (code->op)
8297             {
8298             case EXEC_OMP_PARALLEL_WORKSHARE:
8299               omp_workshare_save = omp_workshare_flag;
8300               omp_workshare_flag = 1;
8301               gfc_resolve_omp_parallel_blocks (code, ns);
8302               break;
8303             case EXEC_OMP_PARALLEL:
8304             case EXEC_OMP_PARALLEL_DO:
8305             case EXEC_OMP_PARALLEL_SECTIONS:
8306             case EXEC_OMP_TASK:
8307               omp_workshare_save = omp_workshare_flag;
8308               omp_workshare_flag = 0;
8309               gfc_resolve_omp_parallel_blocks (code, ns);
8310               break;
8311             case EXEC_OMP_DO:
8312               gfc_resolve_omp_do_blocks (code, ns);
8313               break;
8314             case EXEC_SELECT_TYPE:
8315               gfc_current_ns = code->ext.ns;
8316               gfc_resolve_blocks (code->block, gfc_current_ns);
8317               gfc_current_ns = ns;
8318               break;
8319             case EXEC_OMP_WORKSHARE:
8320               omp_workshare_save = omp_workshare_flag;
8321               omp_workshare_flag = 1;
8322               /* FALLTHROUGH */
8323             default:
8324               gfc_resolve_blocks (code->block, ns);
8325               break;
8326             }
8327
8328           if (omp_workshare_save != -1)
8329             omp_workshare_flag = omp_workshare_save;
8330         }
8331
8332       t = SUCCESS;
8333       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
8334         t = gfc_resolve_expr (code->expr1);
8335       forall_flag = forall_save;
8336
8337       if (gfc_resolve_expr (code->expr2) == FAILURE)
8338         t = FAILURE;
8339
8340       if (code->op == EXEC_ALLOCATE
8341           && gfc_resolve_expr (code->expr3) == FAILURE)
8342         t = FAILURE;
8343
8344       switch (code->op)
8345         {
8346         case EXEC_NOP:
8347         case EXEC_END_BLOCK:
8348         case EXEC_CYCLE:
8349         case EXEC_PAUSE:
8350         case EXEC_STOP:
8351         case EXEC_ERROR_STOP:
8352         case EXEC_EXIT:
8353         case EXEC_CONTINUE:
8354         case EXEC_DT_END:
8355         case EXEC_ASSIGN_CALL:
8356         case EXEC_CRITICAL:
8357           break;
8358
8359         case EXEC_SYNC_ALL:
8360         case EXEC_SYNC_IMAGES:
8361         case EXEC_SYNC_MEMORY:
8362           resolve_sync (code);
8363           break;
8364
8365         case EXEC_ENTRY:
8366           /* Keep track of which entry we are up to.  */
8367           current_entry_id = code->ext.entry->id;
8368           break;
8369
8370         case EXEC_WHERE:
8371           resolve_where (code, NULL);
8372           break;
8373
8374         case EXEC_GOTO:
8375           if (code->expr1 != NULL)
8376             {
8377               if (code->expr1->ts.type != BT_INTEGER)
8378                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
8379                            "INTEGER variable", &code->expr1->where);
8380               else if (code->expr1->symtree->n.sym->attr.assign != 1)
8381                 gfc_error ("Variable '%s' has not been assigned a target "
8382                            "label at %L", code->expr1->symtree->n.sym->name,
8383                            &code->expr1->where);
8384             }
8385           else
8386             resolve_branch (code->label1, code);
8387           break;
8388
8389         case EXEC_RETURN:
8390           if (code->expr1 != NULL
8391                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
8392             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
8393                        "INTEGER return specifier", &code->expr1->where);
8394           break;
8395
8396         case EXEC_INIT_ASSIGN:
8397         case EXEC_END_PROCEDURE:
8398           break;
8399
8400         case EXEC_ASSIGN:
8401           if (t == FAILURE)
8402             break;
8403
8404           if (resolve_ordinary_assign (code, ns))
8405             {
8406               if (code->op == EXEC_COMPCALL)
8407                 goto compcall;
8408               else
8409                 goto call;
8410             }
8411           break;
8412
8413         case EXEC_LABEL_ASSIGN:
8414           if (code->label1->defined == ST_LABEL_UNKNOWN)
8415             gfc_error ("Label %d referenced at %L is never defined",
8416                        code->label1->value, &code->label1->where);
8417           if (t == SUCCESS
8418               && (code->expr1->expr_type != EXPR_VARIABLE
8419                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
8420                   || code->expr1->symtree->n.sym->ts.kind
8421                      != gfc_default_integer_kind
8422                   || code->expr1->symtree->n.sym->as != NULL))
8423             gfc_error ("ASSIGN statement at %L requires a scalar "
8424                        "default INTEGER variable", &code->expr1->where);
8425           break;
8426
8427         case EXEC_POINTER_ASSIGN:
8428           if (t == FAILURE)
8429             break;
8430
8431           gfc_check_pointer_assign (code->expr1, code->expr2);
8432           break;
8433
8434         case EXEC_ARITHMETIC_IF:
8435           if (t == SUCCESS
8436               && code->expr1->ts.type != BT_INTEGER
8437               && code->expr1->ts.type != BT_REAL)
8438             gfc_error ("Arithmetic IF statement at %L requires a numeric "
8439                        "expression", &code->expr1->where);
8440
8441           resolve_branch (code->label1, code);
8442           resolve_branch (code->label2, code);
8443           resolve_branch (code->label3, code);
8444           break;
8445
8446         case EXEC_IF:
8447           if (t == SUCCESS && code->expr1 != NULL
8448               && (code->expr1->ts.type != BT_LOGICAL
8449                   || code->expr1->rank != 0))
8450             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8451                        &code->expr1->where);
8452           break;
8453
8454         case EXEC_CALL:
8455         call:
8456           resolve_call (code);
8457           break;
8458
8459         case EXEC_COMPCALL:
8460         compcall:
8461           resolve_typebound_subroutine (code);
8462           break;
8463
8464         case EXEC_CALL_PPC:
8465           resolve_ppc_call (code);
8466           break;
8467
8468         case EXEC_SELECT:
8469           /* Select is complicated. Also, a SELECT construct could be
8470              a transformed computed GOTO.  */
8471           resolve_select (code);
8472           break;
8473
8474         case EXEC_SELECT_TYPE:
8475           resolve_select_type (code);
8476           break;
8477
8478         case EXEC_BLOCK:
8479           gfc_resolve (code->ext.ns);
8480           break;
8481
8482         case EXEC_DO:
8483           if (code->ext.iterator != NULL)
8484             {
8485               gfc_iterator *iter = code->ext.iterator;
8486               if (gfc_resolve_iterator (iter, true) != FAILURE)
8487                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
8488             }
8489           break;
8490
8491         case EXEC_DO_WHILE:
8492           if (code->expr1 == NULL)
8493             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
8494           if (t == SUCCESS
8495               && (code->expr1->rank != 0
8496                   || code->expr1->ts.type != BT_LOGICAL))
8497             gfc_error ("Exit condition of DO WHILE loop at %L must be "
8498                        "a scalar LOGICAL expression", &code->expr1->where);
8499           break;
8500
8501         case EXEC_ALLOCATE:
8502           if (t == SUCCESS)
8503             resolve_allocate_deallocate (code, "ALLOCATE");
8504
8505           break;
8506
8507         case EXEC_DEALLOCATE:
8508           if (t == SUCCESS)
8509             resolve_allocate_deallocate (code, "DEALLOCATE");
8510
8511           break;
8512
8513         case EXEC_OPEN:
8514           if (gfc_resolve_open (code->ext.open) == FAILURE)
8515             break;
8516
8517           resolve_branch (code->ext.open->err, code);
8518           break;
8519
8520         case EXEC_CLOSE:
8521           if (gfc_resolve_close (code->ext.close) == FAILURE)
8522             break;
8523
8524           resolve_branch (code->ext.close->err, code);
8525           break;
8526
8527         case EXEC_BACKSPACE:
8528         case EXEC_ENDFILE:
8529         case EXEC_REWIND:
8530         case EXEC_FLUSH:
8531           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
8532             break;
8533
8534           resolve_branch (code->ext.filepos->err, code);
8535           break;
8536
8537         case EXEC_INQUIRE:
8538           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8539               break;
8540
8541           resolve_branch (code->ext.inquire->err, code);
8542           break;
8543
8544         case EXEC_IOLENGTH:
8545           gcc_assert (code->ext.inquire != NULL);
8546           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
8547             break;
8548
8549           resolve_branch (code->ext.inquire->err, code);
8550           break;
8551
8552         case EXEC_WAIT:
8553           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
8554             break;
8555
8556           resolve_branch (code->ext.wait->err, code);
8557           resolve_branch (code->ext.wait->end, code);
8558           resolve_branch (code->ext.wait->eor, code);
8559           break;
8560
8561         case EXEC_READ:
8562         case EXEC_WRITE:
8563           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
8564             break;
8565
8566           resolve_branch (code->ext.dt->err, code);
8567           resolve_branch (code->ext.dt->end, code);
8568           resolve_branch (code->ext.dt->eor, code);
8569           break;
8570
8571         case EXEC_TRANSFER:
8572           resolve_transfer (code);
8573           break;
8574
8575         case EXEC_FORALL:
8576           resolve_forall_iterators (code->ext.forall_iterator);
8577
8578           if (code->expr1 != NULL && code->expr1->ts.type != BT_LOGICAL)
8579             gfc_error ("FORALL mask clause at %L requires a LOGICAL "
8580                        "expression", &code->expr1->where);
8581           break;
8582
8583         case EXEC_OMP_ATOMIC:
8584         case EXEC_OMP_BARRIER:
8585         case EXEC_OMP_CRITICAL:
8586         case EXEC_OMP_FLUSH:
8587         case EXEC_OMP_DO:
8588         case EXEC_OMP_MASTER:
8589         case EXEC_OMP_ORDERED:
8590         case EXEC_OMP_SECTIONS:
8591         case EXEC_OMP_SINGLE:
8592         case EXEC_OMP_TASKWAIT:
8593         case EXEC_OMP_WORKSHARE:
8594           gfc_resolve_omp_directive (code, ns);
8595           break;
8596
8597         case EXEC_OMP_PARALLEL:
8598         case EXEC_OMP_PARALLEL_DO:
8599         case EXEC_OMP_PARALLEL_SECTIONS:
8600         case EXEC_OMP_PARALLEL_WORKSHARE:
8601         case EXEC_OMP_TASK:
8602           omp_workshare_save = omp_workshare_flag;
8603           omp_workshare_flag = 0;
8604           gfc_resolve_omp_directive (code, ns);
8605           omp_workshare_flag = omp_workshare_save;
8606           break;
8607
8608         default:
8609           gfc_internal_error ("resolve_code(): Bad statement code");
8610         }
8611     }
8612
8613   cs_base = frame.prev;
8614 }
8615
8616
8617 /* Resolve initial values and make sure they are compatible with
8618    the variable.  */
8619
8620 static void
8621 resolve_values (gfc_symbol *sym)
8622 {
8623   if (sym->value == NULL)
8624     return;
8625
8626   if (gfc_resolve_expr (sym->value) == FAILURE)
8627     return;
8628
8629   gfc_check_assign_symbol (sym, sym->value);
8630 }
8631
8632
8633 /* Verify the binding labels for common blocks that are BIND(C).  The label
8634    for a BIND(C) common block must be identical in all scoping units in which
8635    the common block is declared.  Further, the binding label can not collide
8636    with any other global entity in the program.  */
8637
8638 static void
8639 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
8640 {
8641   if (comm_block_tree->n.common->is_bind_c == 1)
8642     {
8643       gfc_gsymbol *binding_label_gsym;
8644       gfc_gsymbol *comm_name_gsym;
8645
8646       /* See if a global symbol exists by the common block's name.  It may
8647          be NULL if the common block is use-associated.  */
8648       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
8649                                          comm_block_tree->n.common->name);
8650       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
8651         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
8652                    "with the global entity '%s' at %L",
8653                    comm_block_tree->n.common->binding_label,
8654                    comm_block_tree->n.common->name,
8655                    &(comm_block_tree->n.common->where),
8656                    comm_name_gsym->name, &(comm_name_gsym->where));
8657       else if (comm_name_gsym != NULL
8658                && strcmp (comm_name_gsym->name,
8659                           comm_block_tree->n.common->name) == 0)
8660         {
8661           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
8662              as expected.  */
8663           if (comm_name_gsym->binding_label == NULL)
8664             /* No binding label for common block stored yet; save this one.  */
8665             comm_name_gsym->binding_label =
8666               comm_block_tree->n.common->binding_label;
8667           else
8668             if (strcmp (comm_name_gsym->binding_label,
8669                         comm_block_tree->n.common->binding_label) != 0)
8670               {
8671                 /* Common block names match but binding labels do not.  */
8672                 gfc_error ("Binding label '%s' for common block '%s' at %L "
8673                            "does not match the binding label '%s' for common "
8674                            "block '%s' at %L",
8675                            comm_block_tree->n.common->binding_label,
8676                            comm_block_tree->n.common->name,
8677                            &(comm_block_tree->n.common->where),
8678                            comm_name_gsym->binding_label,
8679                            comm_name_gsym->name,
8680                            &(comm_name_gsym->where));
8681                 return;
8682               }
8683         }
8684
8685       /* There is no binding label (NAME="") so we have nothing further to
8686          check and nothing to add as a global symbol for the label.  */
8687       if (comm_block_tree->n.common->binding_label[0] == '\0' )
8688         return;
8689       
8690       binding_label_gsym =
8691         gfc_find_gsymbol (gfc_gsym_root,
8692                           comm_block_tree->n.common->binding_label);
8693       if (binding_label_gsym == NULL)
8694         {
8695           /* Need to make a global symbol for the binding label to prevent
8696              it from colliding with another.  */
8697           binding_label_gsym =
8698             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
8699           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
8700           binding_label_gsym->type = GSYM_COMMON;
8701         }
8702       else
8703         {
8704           /* If comm_name_gsym is NULL, the name common block is use
8705              associated and the name could be colliding.  */
8706           if (binding_label_gsym->type != GSYM_COMMON)
8707             gfc_error ("Binding label '%s' for common block '%s' at %L "
8708                        "collides with the global entity '%s' at %L",
8709                        comm_block_tree->n.common->binding_label,
8710                        comm_block_tree->n.common->name,
8711                        &(comm_block_tree->n.common->where),
8712                        binding_label_gsym->name,
8713                        &(binding_label_gsym->where));
8714           else if (comm_name_gsym != NULL
8715                    && (strcmp (binding_label_gsym->name,
8716                                comm_name_gsym->binding_label) != 0)
8717                    && (strcmp (binding_label_gsym->sym_name,
8718                                comm_name_gsym->name) != 0))
8719             gfc_error ("Binding label '%s' for common block '%s' at %L "
8720                        "collides with global entity '%s' at %L",
8721                        binding_label_gsym->name, binding_label_gsym->sym_name,
8722                        &(comm_block_tree->n.common->where),
8723                        comm_name_gsym->name, &(comm_name_gsym->where));
8724         }
8725     }
8726   
8727   return;
8728 }
8729
8730
8731 /* Verify any BIND(C) derived types in the namespace so we can report errors
8732    for them once, rather than for each variable declared of that type.  */
8733
8734 static void
8735 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
8736 {
8737   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
8738       && derived_sym->attr.is_bind_c == 1)
8739     verify_bind_c_derived_type (derived_sym);
8740   
8741   return;
8742 }
8743
8744
8745 /* Verify that any binding labels used in a given namespace do not collide 
8746    with the names or binding labels of any global symbols.  */
8747
8748 static void
8749 gfc_verify_binding_labels (gfc_symbol *sym)
8750 {
8751   int has_error = 0;
8752   
8753   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
8754       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
8755     {
8756       gfc_gsymbol *bind_c_sym;
8757
8758       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
8759       if (bind_c_sym != NULL 
8760           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
8761         {
8762           if (sym->attr.if_source == IFSRC_DECL 
8763               && (bind_c_sym->type != GSYM_SUBROUTINE 
8764                   && bind_c_sym->type != GSYM_FUNCTION) 
8765               && ((sym->attr.contained == 1 
8766                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
8767                   || (sym->attr.use_assoc == 1 
8768                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
8769             {
8770               /* Make sure global procedures don't collide with anything.  */
8771               gfc_error ("Binding label '%s' at %L collides with the global "
8772                          "entity '%s' at %L", sym->binding_label,
8773                          &(sym->declared_at), bind_c_sym->name,
8774                          &(bind_c_sym->where));
8775               has_error = 1;
8776             }
8777           else if (sym->attr.contained == 0 
8778                    && (sym->attr.if_source == IFSRC_IFBODY 
8779                        && sym->attr.flavor == FL_PROCEDURE) 
8780                    && (bind_c_sym->sym_name != NULL 
8781                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
8782             {
8783               /* Make sure procedures in interface bodies don't collide.  */
8784               gfc_error ("Binding label '%s' in interface body at %L collides "
8785                          "with the global entity '%s' at %L",
8786                          sym->binding_label,
8787                          &(sym->declared_at), bind_c_sym->name,
8788                          &(bind_c_sym->where));
8789               has_error = 1;
8790             }
8791           else if (sym->attr.contained == 0 
8792                    && sym->attr.if_source == IFSRC_UNKNOWN)
8793             if ((sym->attr.use_assoc && bind_c_sym->mod_name
8794                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
8795                 || sym->attr.use_assoc == 0)
8796               {
8797                 gfc_error ("Binding label '%s' at %L collides with global "
8798                            "entity '%s' at %L", sym->binding_label,
8799                            &(sym->declared_at), bind_c_sym->name,
8800                            &(bind_c_sym->where));
8801                 has_error = 1;
8802               }
8803
8804           if (has_error != 0)
8805             /* Clear the binding label to prevent checking multiple times.  */
8806             sym->binding_label[0] = '\0';
8807         }
8808       else if (bind_c_sym == NULL)
8809         {
8810           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
8811           bind_c_sym->where = sym->declared_at;
8812           bind_c_sym->sym_name = sym->name;
8813
8814           if (sym->attr.use_assoc == 1)
8815             bind_c_sym->mod_name = sym->module;
8816           else
8817             if (sym->ns->proc_name != NULL)
8818               bind_c_sym->mod_name = sym->ns->proc_name->name;
8819
8820           if (sym->attr.contained == 0)
8821             {
8822               if (sym->attr.subroutine)
8823                 bind_c_sym->type = GSYM_SUBROUTINE;
8824               else if (sym->attr.function)
8825                 bind_c_sym->type = GSYM_FUNCTION;
8826             }
8827         }
8828     }
8829   return;
8830 }
8831
8832
8833 /* Resolve an index expression.  */
8834
8835 static gfc_try
8836 resolve_index_expr (gfc_expr *e)
8837 {
8838   if (gfc_resolve_expr (e) == FAILURE)
8839     return FAILURE;
8840
8841   if (gfc_simplify_expr (e, 0) == FAILURE)
8842     return FAILURE;
8843
8844   if (gfc_specification_expr (e) == FAILURE)
8845     return FAILURE;
8846
8847   return SUCCESS;
8848 }
8849
8850 /* Resolve a charlen structure.  */
8851
8852 static gfc_try
8853 resolve_charlen (gfc_charlen *cl)
8854 {
8855   int i, k;
8856
8857   if (cl->resolved)
8858     return SUCCESS;
8859
8860   cl->resolved = 1;
8861
8862   specification_expr = 1;
8863
8864   if (resolve_index_expr (cl->length) == FAILURE)
8865     {
8866       specification_expr = 0;
8867       return FAILURE;
8868     }
8869
8870   /* "If the character length parameter value evaluates to a negative
8871      value, the length of character entities declared is zero."  */
8872   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
8873     {
8874       if (gfc_option.warn_surprising)
8875         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
8876                          " the length has been set to zero",
8877                          &cl->length->where, i);
8878       gfc_replace_expr (cl->length,
8879                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
8880     }
8881
8882   /* Check that the character length is not too large.  */
8883   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
8884   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
8885       && cl->length->ts.type == BT_INTEGER
8886       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
8887     {
8888       gfc_error ("String length at %L is too large", &cl->length->where);
8889       return FAILURE;
8890     }
8891
8892   return SUCCESS;
8893 }
8894
8895
8896 /* Test for non-constant shape arrays.  */
8897
8898 static bool
8899 is_non_constant_shape_array (gfc_symbol *sym)
8900 {
8901   gfc_expr *e;
8902   int i;
8903   bool not_constant;
8904
8905   not_constant = false;
8906   if (sym->as != NULL)
8907     {
8908       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
8909          has not been simplified; parameter array references.  Do the
8910          simplification now.  */
8911       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
8912         {
8913           e = sym->as->lower[i];
8914           if (e && (resolve_index_expr (e) == FAILURE
8915                     || !gfc_is_constant_expr (e)))
8916             not_constant = true;
8917           e = sym->as->upper[i];
8918           if (e && (resolve_index_expr (e) == FAILURE
8919                     || !gfc_is_constant_expr (e)))
8920             not_constant = true;
8921         }
8922     }
8923   return not_constant;
8924 }
8925
8926 /* Given a symbol and an initialization expression, add code to initialize
8927    the symbol to the function entry.  */
8928 static void
8929 build_init_assign (gfc_symbol *sym, gfc_expr *init)
8930 {
8931   gfc_expr *lval;
8932   gfc_code *init_st;
8933   gfc_namespace *ns = sym->ns;
8934
8935   /* Search for the function namespace if this is a contained
8936      function without an explicit result.  */
8937   if (sym->attr.function && sym == sym->result
8938       && sym->name != sym->ns->proc_name->name)
8939     {
8940       ns = ns->contained;
8941       for (;ns; ns = ns->sibling)
8942         if (strcmp (ns->proc_name->name, sym->name) == 0)
8943           break;
8944     }
8945
8946   if (ns == NULL)
8947     {
8948       gfc_free_expr (init);
8949       return;
8950     }
8951
8952   /* Build an l-value expression for the result.  */
8953   lval = gfc_lval_expr_from_sym (sym);
8954
8955   /* Add the code at scope entry.  */
8956   init_st = gfc_get_code ();
8957   init_st->next = ns->code;
8958   ns->code = init_st;
8959
8960   /* Assign the default initializer to the l-value.  */
8961   init_st->loc = sym->declared_at;
8962   init_st->op = EXEC_INIT_ASSIGN;
8963   init_st->expr1 = lval;
8964   init_st->expr2 = init;
8965 }
8966
8967 /* Assign the default initializer to a derived type variable or result.  */
8968
8969 static void
8970 apply_default_init (gfc_symbol *sym)
8971 {
8972   gfc_expr *init = NULL;
8973
8974   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
8975     return;
8976
8977   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
8978     init = gfc_default_initializer (&sym->ts);
8979
8980   if (init == NULL)
8981     return;
8982
8983   build_init_assign (sym, init);
8984 }
8985
8986 /* Build an initializer for a local integer, real, complex, logical, or
8987    character variable, based on the command line flags finit-local-zero,
8988    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
8989    null if the symbol should not have a default initialization.  */
8990 static gfc_expr *
8991 build_default_init_expr (gfc_symbol *sym)
8992 {
8993   int char_len;
8994   gfc_expr *init_expr;
8995   int i;
8996
8997   /* These symbols should never have a default initialization.  */
8998   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
8999       || sym->attr.external
9000       || sym->attr.dummy
9001       || sym->attr.pointer
9002       || sym->attr.in_equivalence
9003       || sym->attr.in_common
9004       || sym->attr.data
9005       || sym->module
9006       || sym->attr.cray_pointee
9007       || sym->attr.cray_pointer)
9008     return NULL;
9009
9010   /* Now we'll try to build an initializer expression.  */
9011   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
9012                                      &sym->declared_at);
9013
9014   /* We will only initialize integers, reals, complex, logicals, and
9015      characters, and only if the corresponding command-line flags
9016      were set.  Otherwise, we free init_expr and return null.  */
9017   switch (sym->ts.type)
9018     {    
9019     case BT_INTEGER:
9020       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
9021         mpz_init_set_si (init_expr->value.integer, 
9022                          gfc_option.flag_init_integer_value);
9023       else
9024         {
9025           gfc_free_expr (init_expr);
9026           init_expr = NULL;
9027         }
9028       break;
9029
9030     case BT_REAL:
9031       mpfr_init (init_expr->value.real);
9032       switch (gfc_option.flag_init_real)
9033         {
9034         case GFC_INIT_REAL_SNAN:
9035           init_expr->is_snan = 1;
9036           /* Fall through.  */
9037         case GFC_INIT_REAL_NAN:
9038           mpfr_set_nan (init_expr->value.real);
9039           break;
9040
9041         case GFC_INIT_REAL_INF:
9042           mpfr_set_inf (init_expr->value.real, 1);
9043           break;
9044
9045         case GFC_INIT_REAL_NEG_INF:
9046           mpfr_set_inf (init_expr->value.real, -1);
9047           break;
9048
9049         case GFC_INIT_REAL_ZERO:
9050           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
9051           break;
9052
9053         default:
9054           gfc_free_expr (init_expr);
9055           init_expr = NULL;
9056           break;
9057         }
9058       break;
9059           
9060     case BT_COMPLEX:
9061       mpc_init2 (init_expr->value.complex, mpfr_get_default_prec());
9062       switch (gfc_option.flag_init_real)
9063         {
9064         case GFC_INIT_REAL_SNAN:
9065           init_expr->is_snan = 1;
9066           /* Fall through.  */
9067         case GFC_INIT_REAL_NAN:
9068           mpfr_set_nan (mpc_realref (init_expr->value.complex));
9069           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
9070           break;
9071
9072         case GFC_INIT_REAL_INF:
9073           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
9074           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
9075           break;
9076
9077         case GFC_INIT_REAL_NEG_INF:
9078           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
9079           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
9080           break;
9081
9082         case GFC_INIT_REAL_ZERO:
9083           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
9084           break;
9085
9086         default:
9087           gfc_free_expr (init_expr);
9088           init_expr = NULL;
9089           break;
9090         }
9091       break;
9092           
9093     case BT_LOGICAL:
9094       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
9095         init_expr->value.logical = 0;
9096       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
9097         init_expr->value.logical = 1;
9098       else
9099         {
9100           gfc_free_expr (init_expr);
9101           init_expr = NULL;
9102         }
9103       break;
9104           
9105     case BT_CHARACTER:
9106       /* For characters, the length must be constant in order to 
9107          create a default initializer.  */
9108       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
9109           && sym->ts.u.cl->length
9110           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9111         {
9112           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
9113           init_expr->value.character.length = char_len;
9114           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
9115           for (i = 0; i < char_len; i++)
9116             init_expr->value.character.string[i]
9117               = (unsigned char) gfc_option.flag_init_character_value;
9118         }
9119       else
9120         {
9121           gfc_free_expr (init_expr);
9122           init_expr = NULL;
9123         }
9124       break;
9125           
9126     default:
9127      gfc_free_expr (init_expr);
9128      init_expr = NULL;
9129     }
9130   return init_expr;
9131 }
9132
9133 /* Add an initialization expression to a local variable.  */
9134 static void
9135 apply_default_init_local (gfc_symbol *sym)
9136 {
9137   gfc_expr *init = NULL;
9138
9139   /* The symbol should be a variable or a function return value.  */
9140   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9141       || (sym->attr.function && sym->result != sym))
9142     return;
9143
9144   /* Try to build the initializer expression.  If we can't initialize
9145      this symbol, then init will be NULL.  */
9146   init = build_default_init_expr (sym);
9147   if (init == NULL)
9148     return;
9149
9150   /* For saved variables, we don't want to add an initializer at 
9151      function entry, so we just add a static initializer.  */
9152   if (sym->attr.save || sym->ns->save_all 
9153       || gfc_option.flag_max_stack_var_size == 0)
9154     {
9155       /* Don't clobber an existing initializer!  */
9156       gcc_assert (sym->value == NULL);
9157       sym->value = init;
9158       return;
9159     }
9160
9161   build_init_assign (sym, init);
9162 }
9163
9164 /* Resolution of common features of flavors variable and procedure.  */
9165
9166 static gfc_try
9167 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
9168 {
9169   /* Constraints on deferred shape variable.  */
9170   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
9171     {
9172       if (sym->attr.allocatable)
9173         {
9174           if (sym->attr.dimension)
9175             {
9176               gfc_error ("Allocatable array '%s' at %L must have "
9177                          "a deferred shape", sym->name, &sym->declared_at);
9178               return FAILURE;
9179             }
9180           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
9181                                    "may not be ALLOCATABLE", sym->name,
9182                                    &sym->declared_at) == FAILURE)
9183             return FAILURE;
9184         }
9185
9186       if (sym->attr.pointer && sym->attr.dimension)
9187         {
9188           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
9189                      sym->name, &sym->declared_at);
9190           return FAILURE;
9191         }
9192
9193     }
9194   else
9195     {
9196       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
9197           && !sym->attr.dummy && sym->ts.type != BT_CLASS)
9198         {
9199           gfc_error ("Array '%s' at %L cannot have a deferred shape",
9200                      sym->name, &sym->declared_at);
9201           return FAILURE;
9202          }
9203     }
9204
9205   /* Constraints on polymorphic variables.  */
9206   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
9207     {
9208       /* F03:C502.  */
9209       if (!gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
9210         {
9211           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
9212                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
9213                      &sym->declared_at);
9214           return FAILURE;
9215         }
9216
9217       /* F03:C509.  */
9218       /* Assume that use associated symbols were checked in the module ns.  */ 
9219       if (!sym->attr.class_ok && !sym->attr.use_assoc)
9220         {
9221           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
9222                      "or pointer", sym->name, &sym->declared_at);
9223           return FAILURE;
9224         }
9225     }
9226     
9227   return SUCCESS;
9228 }
9229
9230
9231 /* Additional checks for symbols with flavor variable and derived
9232    type.  To be called from resolve_fl_variable.  */
9233
9234 static gfc_try
9235 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
9236 {
9237   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
9238
9239   /* Check to see if a derived type is blocked from being host
9240      associated by the presence of another class I symbol in the same
9241      namespace.  14.6.1.3 of the standard and the discussion on
9242      comp.lang.fortran.  */
9243   if (sym->ns != sym->ts.u.derived->ns
9244       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
9245     {
9246       gfc_symbol *s;
9247       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
9248       if (s && s->attr.flavor != FL_DERIVED)
9249         {
9250           gfc_error ("The type '%s' cannot be host associated at %L "
9251                      "because it is blocked by an incompatible object "
9252                      "of the same name declared at %L",
9253                      sym->ts.u.derived->name, &sym->declared_at,
9254                      &s->declared_at);
9255           return FAILURE;
9256         }
9257     }
9258
9259   /* 4th constraint in section 11.3: "If an object of a type for which
9260      component-initialization is specified (R429) appears in the
9261      specification-part of a module and does not have the ALLOCATABLE
9262      or POINTER attribute, the object shall have the SAVE attribute."
9263
9264      The check for initializers is performed with
9265      gfc_has_default_initializer because gfc_default_initializer generates
9266      a hidden default for allocatable components.  */
9267   if (!(sym->value || no_init_flag) && sym->ns->proc_name
9268       && sym->ns->proc_name->attr.flavor == FL_MODULE
9269       && !sym->ns->save_all && !sym->attr.save
9270       && !sym->attr.pointer && !sym->attr.allocatable
9271       && gfc_has_default_initializer (sym->ts.u.derived)
9272       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
9273                          "module variable '%s' at %L, needed due to "
9274                          "the default initialization", sym->name,
9275                          &sym->declared_at) == FAILURE)
9276     return FAILURE;
9277
9278   /* Assign default initializer.  */
9279   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
9280       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
9281     {
9282       sym->value = gfc_default_initializer (&sym->ts);
9283     }
9284
9285   return SUCCESS;
9286 }
9287
9288
9289 /* Resolve symbols with flavor variable.  */
9290
9291 static gfc_try
9292 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
9293 {
9294   int no_init_flag, automatic_flag;
9295   gfc_expr *e;
9296   const char *auto_save_msg;
9297
9298   auto_save_msg = "Automatic object '%s' at %L cannot have the "
9299                   "SAVE attribute";
9300
9301   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9302     return FAILURE;
9303
9304   /* Set this flag to check that variables are parameters of all entries.
9305      This check is effected by the call to gfc_resolve_expr through
9306      is_non_constant_shape_array.  */
9307   specification_expr = 1;
9308
9309   if (sym->ns->proc_name
9310       && (sym->ns->proc_name->attr.flavor == FL_MODULE
9311           || sym->ns->proc_name->attr.is_main_program)
9312       && !sym->attr.use_assoc
9313       && !sym->attr.allocatable
9314       && !sym->attr.pointer
9315       && is_non_constant_shape_array (sym))
9316     {
9317       /* The shape of a main program or module array needs to be
9318          constant.  */
9319       gfc_error ("The module or main program array '%s' at %L must "
9320                  "have constant shape", sym->name, &sym->declared_at);
9321       specification_expr = 0;
9322       return FAILURE;
9323     }
9324
9325   if (sym->ts.type == BT_CHARACTER)
9326     {
9327       /* Make sure that character string variables with assumed length are
9328          dummy arguments.  */
9329       e = sym->ts.u.cl->length;
9330       if (e == NULL && !sym->attr.dummy && !sym->attr.result)
9331         {
9332           gfc_error ("Entity with assumed character length at %L must be a "
9333                      "dummy argument or a PARAMETER", &sym->declared_at);
9334           return FAILURE;
9335         }
9336
9337       if (e && sym->attr.save && !gfc_is_constant_expr (e))
9338         {
9339           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9340           return FAILURE;
9341         }
9342
9343       if (!gfc_is_constant_expr (e)
9344           && !(e->expr_type == EXPR_VARIABLE
9345                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
9346           && sym->ns->proc_name
9347           && (sym->ns->proc_name->attr.flavor == FL_MODULE
9348               || sym->ns->proc_name->attr.is_main_program)
9349           && !sym->attr.use_assoc)
9350         {
9351           gfc_error ("'%s' at %L must have constant character length "
9352                      "in this context", sym->name, &sym->declared_at);
9353           return FAILURE;
9354         }
9355     }
9356
9357   if (sym->value == NULL && sym->attr.referenced)
9358     apply_default_init_local (sym); /* Try to apply a default initialization.  */
9359
9360   /* Determine if the symbol may not have an initializer.  */
9361   no_init_flag = automatic_flag = 0;
9362   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
9363       || sym->attr.intrinsic || sym->attr.result)
9364     no_init_flag = 1;
9365   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
9366            && is_non_constant_shape_array (sym))
9367     {
9368       no_init_flag = automatic_flag = 1;
9369
9370       /* Also, they must not have the SAVE attribute.
9371          SAVE_IMPLICIT is checked below.  */
9372       if (sym->attr.save == SAVE_EXPLICIT)
9373         {
9374           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9375           return FAILURE;
9376         }
9377     }
9378
9379   /* Ensure that any initializer is simplified.  */
9380   if (sym->value)
9381     gfc_simplify_expr (sym->value, 1);
9382
9383   /* Reject illegal initializers.  */
9384   if (!sym->mark && sym->value)
9385     {
9386       if (sym->attr.allocatable)
9387         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
9388                    sym->name, &sym->declared_at);
9389       else if (sym->attr.external)
9390         gfc_error ("External '%s' at %L cannot have an initializer",
9391                    sym->name, &sym->declared_at);
9392       else if (sym->attr.dummy
9393         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
9394         gfc_error ("Dummy '%s' at %L cannot have an initializer",
9395                    sym->name, &sym->declared_at);
9396       else if (sym->attr.intrinsic)
9397         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
9398                    sym->name, &sym->declared_at);
9399       else if (sym->attr.result)
9400         gfc_error ("Function result '%s' at %L cannot have an initializer",
9401                    sym->name, &sym->declared_at);
9402       else if (automatic_flag)
9403         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
9404                    sym->name, &sym->declared_at);
9405       else
9406         goto no_init_error;
9407       return FAILURE;
9408     }
9409
9410 no_init_error:
9411   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
9412     return resolve_fl_variable_derived (sym, no_init_flag);
9413
9414   return SUCCESS;
9415 }
9416
9417
9418 /* Resolve a procedure.  */
9419
9420 static gfc_try
9421 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
9422 {
9423   gfc_formal_arglist *arg;
9424
9425   if (sym->attr.function
9426       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9427     return FAILURE;
9428
9429   if (sym->ts.type == BT_CHARACTER)
9430     {
9431       gfc_charlen *cl = sym->ts.u.cl;
9432
9433       if (cl && cl->length && gfc_is_constant_expr (cl->length)
9434              && resolve_charlen (cl) == FAILURE)
9435         return FAILURE;
9436
9437       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
9438           && sym->attr.proc == PROC_ST_FUNCTION)
9439         {
9440           gfc_error ("Character-valued statement function '%s' at %L must "
9441                      "have constant length", sym->name, &sym->declared_at);
9442           return FAILURE;
9443         }
9444     }
9445
9446   /* Ensure that derived type for are not of a private type.  Internal
9447      module procedures are excluded by 2.2.3.3 - i.e., they are not
9448      externally accessible and can access all the objects accessible in
9449      the host.  */
9450   if (!(sym->ns->parent
9451         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
9452       && gfc_check_access(sym->attr.access, sym->ns->default_access))
9453     {
9454       gfc_interface *iface;
9455
9456       for (arg = sym->formal; arg; arg = arg->next)
9457         {
9458           if (arg->sym
9459               && arg->sym->ts.type == BT_DERIVED
9460               && !arg->sym->ts.u.derived->attr.use_assoc
9461               && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9462                                     arg->sym->ts.u.derived->ns->default_access)
9463               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
9464                                  "PRIVATE type and cannot be a dummy argument"
9465                                  " of '%s', which is PUBLIC at %L",
9466                                  arg->sym->name, sym->name, &sym->declared_at)
9467                  == FAILURE)
9468             {
9469               /* Stop this message from recurring.  */
9470               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9471               return FAILURE;
9472             }
9473         }
9474
9475       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9476          PRIVATE to the containing module.  */
9477       for (iface = sym->generic; iface; iface = iface->next)
9478         {
9479           for (arg = iface->sym->formal; arg; arg = arg->next)
9480             {
9481               if (arg->sym
9482                   && arg->sym->ts.type == BT_DERIVED
9483                   && !arg->sym->ts.u.derived->attr.use_assoc
9484                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9485                                         arg->sym->ts.u.derived->ns->default_access)
9486                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9487                                      "'%s' in PUBLIC interface '%s' at %L "
9488                                      "takes dummy arguments of '%s' which is "
9489                                      "PRIVATE", iface->sym->name, sym->name,
9490                                      &iface->sym->declared_at,
9491                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9492                 {
9493                   /* Stop this message from recurring.  */
9494                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9495                   return FAILURE;
9496                 }
9497              }
9498         }
9499
9500       /* PUBLIC interfaces may expose PRIVATE procedures that take types
9501          PRIVATE to the containing module.  */
9502       for (iface = sym->generic; iface; iface = iface->next)
9503         {
9504           for (arg = iface->sym->formal; arg; arg = arg->next)
9505             {
9506               if (arg->sym
9507                   && arg->sym->ts.type == BT_DERIVED
9508                   && !arg->sym->ts.u.derived->attr.use_assoc
9509                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
9510                                         arg->sym->ts.u.derived->ns->default_access)
9511                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
9512                                      "'%s' in PUBLIC interface '%s' at %L "
9513                                      "takes dummy arguments of '%s' which is "
9514                                      "PRIVATE", iface->sym->name, sym->name,
9515                                      &iface->sym->declared_at,
9516                                      gfc_typename (&arg->sym->ts)) == FAILURE)
9517                 {
9518                   /* Stop this message from recurring.  */
9519                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
9520                   return FAILURE;
9521                 }
9522              }
9523         }
9524     }
9525
9526   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
9527       && !sym->attr.proc_pointer)
9528     {
9529       gfc_error ("Function '%s' at %L cannot have an initializer",
9530                  sym->name, &sym->declared_at);
9531       return FAILURE;
9532     }
9533
9534   /* An external symbol may not have an initializer because it is taken to be
9535      a procedure. Exception: Procedure Pointers.  */
9536   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
9537     {
9538       gfc_error ("External object '%s' at %L may not have an initializer",
9539                  sym->name, &sym->declared_at);
9540       return FAILURE;
9541     }
9542
9543   /* An elemental function is required to return a scalar 12.7.1  */
9544   if (sym->attr.elemental && sym->attr.function && sym->as)
9545     {
9546       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
9547                  "result", sym->name, &sym->declared_at);
9548       /* Reset so that the error only occurs once.  */
9549       sym->attr.elemental = 0;
9550       return FAILURE;
9551     }
9552
9553   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
9554      char-len-param shall not be array-valued, pointer-valued, recursive
9555      or pure.  ....snip... A character value of * may only be used in the
9556      following ways: (i) Dummy arg of procedure - dummy associates with
9557      actual length; (ii) To declare a named constant; or (iii) External
9558      function - but length must be declared in calling scoping unit.  */
9559   if (sym->attr.function
9560       && sym->ts.type == BT_CHARACTER
9561       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
9562     {
9563       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
9564           || (sym->attr.recursive) || (sym->attr.pure))
9565         {
9566           if (sym->as && sym->as->rank)
9567             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9568                        "array-valued", sym->name, &sym->declared_at);
9569
9570           if (sym->attr.pointer)
9571             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9572                        "pointer-valued", sym->name, &sym->declared_at);
9573
9574           if (sym->attr.pure)
9575             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9576                        "pure", sym->name, &sym->declared_at);
9577
9578           if (sym->attr.recursive)
9579             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
9580                        "recursive", sym->name, &sym->declared_at);
9581
9582           return FAILURE;
9583         }
9584
9585       /* Appendix B.2 of the standard.  Contained functions give an
9586          error anyway.  Fixed-form is likely to be F77/legacy.  */
9587       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
9588         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
9589                         "CHARACTER(*) function '%s' at %L",
9590                         sym->name, &sym->declared_at);
9591     }
9592
9593   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
9594     {
9595       gfc_formal_arglist *curr_arg;
9596       int has_non_interop_arg = 0;
9597
9598       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
9599                              sym->common_block) == FAILURE)
9600         {
9601           /* Clear these to prevent looking at them again if there was an
9602              error.  */
9603           sym->attr.is_bind_c = 0;
9604           sym->attr.is_c_interop = 0;
9605           sym->ts.is_c_interop = 0;
9606         }
9607       else
9608         {
9609           /* So far, no errors have been found.  */
9610           sym->attr.is_c_interop = 1;
9611           sym->ts.is_c_interop = 1;
9612         }
9613       
9614       curr_arg = sym->formal;
9615       while (curr_arg != NULL)
9616         {
9617           /* Skip implicitly typed dummy args here.  */
9618           if (curr_arg->sym->attr.implicit_type == 0)
9619             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
9620               /* If something is found to fail, record the fact so we
9621                  can mark the symbol for the procedure as not being
9622                  BIND(C) to try and prevent multiple errors being
9623                  reported.  */
9624               has_non_interop_arg = 1;
9625           
9626           curr_arg = curr_arg->next;
9627         }
9628
9629       /* See if any of the arguments were not interoperable and if so, clear
9630          the procedure symbol to prevent duplicate error messages.  */
9631       if (has_non_interop_arg != 0)
9632         {
9633           sym->attr.is_c_interop = 0;
9634           sym->ts.is_c_interop = 0;
9635           sym->attr.is_bind_c = 0;
9636         }
9637     }
9638   
9639   if (!sym->attr.proc_pointer)
9640     {
9641       if (sym->attr.save == SAVE_EXPLICIT)
9642         {
9643           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
9644                      "in '%s' at %L", sym->name, &sym->declared_at);
9645           return FAILURE;
9646         }
9647       if (sym->attr.intent)
9648         {
9649           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
9650                      "in '%s' at %L", sym->name, &sym->declared_at);
9651           return FAILURE;
9652         }
9653       if (sym->attr.subroutine && sym->attr.result)
9654         {
9655           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
9656                      "in '%s' at %L", sym->name, &sym->declared_at);
9657           return FAILURE;
9658         }
9659       if (sym->attr.external && sym->attr.function
9660           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
9661               || sym->attr.contained))
9662         {
9663           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
9664                      "in '%s' at %L", sym->name, &sym->declared_at);
9665           return FAILURE;
9666         }
9667       if (strcmp ("ppr@", sym->name) == 0)
9668         {
9669           gfc_error ("Procedure pointer result '%s' at %L "
9670                      "is missing the pointer attribute",
9671                      sym->ns->proc_name->name, &sym->declared_at);
9672           return FAILURE;
9673         }
9674     }
9675
9676   return SUCCESS;
9677 }
9678
9679
9680 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
9681    been defined and we now know their defined arguments, check that they fulfill
9682    the requirements of the standard for procedures used as finalizers.  */
9683
9684 static gfc_try
9685 gfc_resolve_finalizers (gfc_symbol* derived)
9686 {
9687   gfc_finalizer* list;
9688   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
9689   gfc_try result = SUCCESS;
9690   bool seen_scalar = false;
9691
9692   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
9693     return SUCCESS;
9694
9695   /* Walk over the list of finalizer-procedures, check them, and if any one
9696      does not fit in with the standard's definition, print an error and remove
9697      it from the list.  */
9698   prev_link = &derived->f2k_derived->finalizers;
9699   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
9700     {
9701       gfc_symbol* arg;
9702       gfc_finalizer* i;
9703       int my_rank;
9704
9705       /* Skip this finalizer if we already resolved it.  */
9706       if (list->proc_tree)
9707         {
9708           prev_link = &(list->next);
9709           continue;
9710         }
9711
9712       /* Check this exists and is a SUBROUTINE.  */
9713       if (!list->proc_sym->attr.subroutine)
9714         {
9715           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
9716                      list->proc_sym->name, &list->where);
9717           goto error;
9718         }
9719
9720       /* We should have exactly one argument.  */
9721       if (!list->proc_sym->formal || list->proc_sym->formal->next)
9722         {
9723           gfc_error ("FINAL procedure at %L must have exactly one argument",
9724                      &list->where);
9725           goto error;
9726         }
9727       arg = list->proc_sym->formal->sym;
9728
9729       /* This argument must be of our type.  */
9730       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
9731         {
9732           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
9733                      &arg->declared_at, derived->name);
9734           goto error;
9735         }
9736
9737       /* It must neither be a pointer nor allocatable nor optional.  */
9738       if (arg->attr.pointer)
9739         {
9740           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
9741                      &arg->declared_at);
9742           goto error;
9743         }
9744       if (arg->attr.allocatable)
9745         {
9746           gfc_error ("Argument of FINAL procedure at %L must not be"
9747                      " ALLOCATABLE", &arg->declared_at);
9748           goto error;
9749         }
9750       if (arg->attr.optional)
9751         {
9752           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
9753                      &arg->declared_at);
9754           goto error;
9755         }
9756
9757       /* It must not be INTENT(OUT).  */
9758       if (arg->attr.intent == INTENT_OUT)
9759         {
9760           gfc_error ("Argument of FINAL procedure at %L must not be"
9761                      " INTENT(OUT)", &arg->declared_at);
9762           goto error;
9763         }
9764
9765       /* Warn if the procedure is non-scalar and not assumed shape.  */
9766       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
9767           && arg->as->type != AS_ASSUMED_SHAPE)
9768         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
9769                      " shape argument", &arg->declared_at);
9770
9771       /* Check that it does not match in kind and rank with a FINAL procedure
9772          defined earlier.  To really loop over the *earlier* declarations,
9773          we need to walk the tail of the list as new ones were pushed at the
9774          front.  */
9775       /* TODO: Handle kind parameters once they are implemented.  */
9776       my_rank = (arg->as ? arg->as->rank : 0);
9777       for (i = list->next; i; i = i->next)
9778         {
9779           /* Argument list might be empty; that is an error signalled earlier,
9780              but we nevertheless continued resolving.  */
9781           if (i->proc_sym->formal)
9782             {
9783               gfc_symbol* i_arg = i->proc_sym->formal->sym;
9784               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
9785               if (i_rank == my_rank)
9786                 {
9787                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
9788                              " rank (%d) as '%s'",
9789                              list->proc_sym->name, &list->where, my_rank, 
9790                              i->proc_sym->name);
9791                   goto error;
9792                 }
9793             }
9794         }
9795
9796         /* Is this the/a scalar finalizer procedure?  */
9797         if (!arg->as || arg->as->rank == 0)
9798           seen_scalar = true;
9799
9800         /* Find the symtree for this procedure.  */
9801         gcc_assert (!list->proc_tree);
9802         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
9803
9804         prev_link = &list->next;
9805         continue;
9806
9807         /* Remove wrong nodes immediately from the list so we don't risk any
9808            troubles in the future when they might fail later expectations.  */
9809 error:
9810         result = FAILURE;
9811         i = list;
9812         *prev_link = list->next;
9813         gfc_free_finalizer (i);
9814     }
9815
9816   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
9817      were nodes in the list, must have been for arrays.  It is surely a good
9818      idea to have a scalar version there if there's something to finalize.  */
9819   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
9820     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
9821                  " defined at %L, suggest also scalar one",
9822                  derived->name, &derived->declared_at);
9823
9824   /* TODO:  Remove this error when finalization is finished.  */
9825   gfc_error ("Finalization at %L is not yet implemented",
9826              &derived->declared_at);
9827
9828   return result;
9829 }
9830
9831
9832 /* Check that it is ok for the typebound procedure proc to override the
9833    procedure old.  */
9834
9835 static gfc_try
9836 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
9837 {
9838   locus where;
9839   const gfc_symbol* proc_target;
9840   const gfc_symbol* old_target;
9841   unsigned proc_pass_arg, old_pass_arg, argpos;
9842   gfc_formal_arglist* proc_formal;
9843   gfc_formal_arglist* old_formal;
9844
9845   /* This procedure should only be called for non-GENERIC proc.  */
9846   gcc_assert (!proc->n.tb->is_generic);
9847
9848   /* If the overwritten procedure is GENERIC, this is an error.  */
9849   if (old->n.tb->is_generic)
9850     {
9851       gfc_error ("Can't overwrite GENERIC '%s' at %L",
9852                  old->name, &proc->n.tb->where);
9853       return FAILURE;
9854     }
9855
9856   where = proc->n.tb->where;
9857   proc_target = proc->n.tb->u.specific->n.sym;
9858   old_target = old->n.tb->u.specific->n.sym;
9859
9860   /* Check that overridden binding is not NON_OVERRIDABLE.  */
9861   if (old->n.tb->non_overridable)
9862     {
9863       gfc_error ("'%s' at %L overrides a procedure binding declared"
9864                  " NON_OVERRIDABLE", proc->name, &where);
9865       return FAILURE;
9866     }
9867
9868   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
9869   if (!old->n.tb->deferred && proc->n.tb->deferred)
9870     {
9871       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
9872                  " non-DEFERRED binding", proc->name, &where);
9873       return FAILURE;
9874     }
9875
9876   /* If the overridden binding is PURE, the overriding must be, too.  */
9877   if (old_target->attr.pure && !proc_target->attr.pure)
9878     {
9879       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
9880                  proc->name, &where);
9881       return FAILURE;
9882     }
9883
9884   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
9885      is not, the overriding must not be either.  */
9886   if (old_target->attr.elemental && !proc_target->attr.elemental)
9887     {
9888       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
9889                  " ELEMENTAL", proc->name, &where);
9890       return FAILURE;
9891     }
9892   if (!old_target->attr.elemental && proc_target->attr.elemental)
9893     {
9894       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
9895                  " be ELEMENTAL, either", proc->name, &where);
9896       return FAILURE;
9897     }
9898
9899   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
9900      SUBROUTINE.  */
9901   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
9902     {
9903       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
9904                  " SUBROUTINE", proc->name, &where);
9905       return FAILURE;
9906     }
9907
9908   /* If the overridden binding is a FUNCTION, the overriding must also be a
9909      FUNCTION and have the same characteristics.  */
9910   if (old_target->attr.function)
9911     {
9912       if (!proc_target->attr.function)
9913         {
9914           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
9915                      " FUNCTION", proc->name, &where);
9916           return FAILURE;
9917         }
9918
9919       /* FIXME:  Do more comprehensive checking (including, for instance, the
9920          rank and array-shape).  */
9921       gcc_assert (proc_target->result && old_target->result);
9922       if (!gfc_compare_types (&proc_target->result->ts,
9923                               &old_target->result->ts))
9924         {
9925           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
9926                      " matching result types", proc->name, &where);
9927           return FAILURE;
9928         }
9929     }
9930
9931   /* If the overridden binding is PUBLIC, the overriding one must not be
9932      PRIVATE.  */
9933   if (old->n.tb->access == ACCESS_PUBLIC
9934       && proc->n.tb->access == ACCESS_PRIVATE)
9935     {
9936       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
9937                  " PRIVATE", proc->name, &where);
9938       return FAILURE;
9939     }
9940
9941   /* Compare the formal argument lists of both procedures.  This is also abused
9942      to find the position of the passed-object dummy arguments of both
9943      bindings as at least the overridden one might not yet be resolved and we
9944      need those positions in the check below.  */
9945   proc_pass_arg = old_pass_arg = 0;
9946   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
9947     proc_pass_arg = 1;
9948   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
9949     old_pass_arg = 1;
9950   argpos = 1;
9951   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
9952        proc_formal && old_formal;
9953        proc_formal = proc_formal->next, old_formal = old_formal->next)
9954     {
9955       if (proc->n.tb->pass_arg
9956           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
9957         proc_pass_arg = argpos;
9958       if (old->n.tb->pass_arg
9959           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
9960         old_pass_arg = argpos;
9961
9962       /* Check that the names correspond.  */
9963       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
9964         {
9965           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
9966                      " to match the corresponding argument of the overridden"
9967                      " procedure", proc_formal->sym->name, proc->name, &where,
9968                      old_formal->sym->name);
9969           return FAILURE;
9970         }
9971
9972       /* Check that the types correspond if neither is the passed-object
9973          argument.  */
9974       /* FIXME:  Do more comprehensive testing here.  */
9975       if (proc_pass_arg != argpos && old_pass_arg != argpos
9976           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
9977         {
9978           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L "
9979                      "in respect to the overridden procedure",
9980                      proc_formal->sym->name, proc->name, &where);
9981           return FAILURE;
9982         }
9983
9984       ++argpos;
9985     }
9986   if (proc_formal || old_formal)
9987     {
9988       gfc_error ("'%s' at %L must have the same number of formal arguments as"
9989                  " the overridden procedure", proc->name, &where);
9990       return FAILURE;
9991     }
9992
9993   /* If the overridden binding is NOPASS, the overriding one must also be
9994      NOPASS.  */
9995   if (old->n.tb->nopass && !proc->n.tb->nopass)
9996     {
9997       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
9998                  " NOPASS", proc->name, &where);
9999       return FAILURE;
10000     }
10001
10002   /* If the overridden binding is PASS(x), the overriding one must also be
10003      PASS and the passed-object dummy arguments must correspond.  */
10004   if (!old->n.tb->nopass)
10005     {
10006       if (proc->n.tb->nopass)
10007         {
10008           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
10009                      " PASS", proc->name, &where);
10010           return FAILURE;
10011         }
10012
10013       if (proc_pass_arg != old_pass_arg)
10014         {
10015           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
10016                      " the same position as the passed-object dummy argument of"
10017                      " the overridden procedure", proc->name, &where);
10018           return FAILURE;
10019         }
10020     }
10021
10022   return SUCCESS;
10023 }
10024
10025
10026 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10027
10028 static gfc_try
10029 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10030                              const char* generic_name, locus where)
10031 {
10032   gfc_symbol* sym1;
10033   gfc_symbol* sym2;
10034
10035   gcc_assert (t1->specific && t2->specific);
10036   gcc_assert (!t1->specific->is_generic);
10037   gcc_assert (!t2->specific->is_generic);
10038
10039   sym1 = t1->specific->u.specific->n.sym;
10040   sym2 = t2->specific->u.specific->n.sym;
10041
10042   if (sym1 == sym2)
10043     return SUCCESS;
10044
10045   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10046   if (sym1->attr.subroutine != sym2->attr.subroutine
10047       || sym1->attr.function != sym2->attr.function)
10048     {
10049       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10050                  " GENERIC '%s' at %L",
10051                  sym1->name, sym2->name, generic_name, &where);
10052       return FAILURE;
10053     }
10054
10055   /* Compare the interfaces.  */
10056   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10057     {
10058       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10059                  sym1->name, sym2->name, generic_name, &where);
10060       return FAILURE;
10061     }
10062
10063   return SUCCESS;
10064 }
10065
10066
10067 /* Worker function for resolving a generic procedure binding; this is used to
10068    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10069
10070    The difference between those cases is finding possible inherited bindings
10071    that are overridden, as one has to look for them in tb_sym_root,
10072    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10073    the super-type and set p->overridden correctly.  */
10074
10075 static gfc_try
10076 resolve_tb_generic_targets (gfc_symbol* super_type,
10077                             gfc_typebound_proc* p, const char* name)
10078 {
10079   gfc_tbp_generic* target;
10080   gfc_symtree* first_target;
10081   gfc_symtree* inherited;
10082
10083   gcc_assert (p && p->is_generic);
10084
10085   /* Try to find the specific bindings for the symtrees in our target-list.  */
10086   gcc_assert (p->u.generic);
10087   for (target = p->u.generic; target; target = target->next)
10088     if (!target->specific)
10089       {
10090         gfc_typebound_proc* overridden_tbp;
10091         gfc_tbp_generic* g;
10092         const char* target_name;
10093
10094         target_name = target->specific_st->name;
10095
10096         /* Defined for this type directly.  */
10097         if (target->specific_st->n.tb)
10098           {
10099             target->specific = target->specific_st->n.tb;
10100             goto specific_found;
10101           }
10102
10103         /* Look for an inherited specific binding.  */
10104         if (super_type)
10105           {
10106             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10107                                                  true, NULL);
10108
10109             if (inherited)
10110               {
10111                 gcc_assert (inherited->n.tb);
10112                 target->specific = inherited->n.tb;
10113                 goto specific_found;
10114               }
10115           }
10116
10117         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10118                    " at %L", target_name, name, &p->where);
10119         return FAILURE;
10120
10121         /* Once we've found the specific binding, check it is not ambiguous with
10122            other specifics already found or inherited for the same GENERIC.  */
10123 specific_found:
10124         gcc_assert (target->specific);
10125
10126         /* This must really be a specific binding!  */
10127         if (target->specific->is_generic)
10128           {
10129             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
10130                        " '%s' is GENERIC, too", name, &p->where, target_name);
10131             return FAILURE;
10132           }
10133
10134         /* Check those already resolved on this type directly.  */
10135         for (g = p->u.generic; g; g = g->next)
10136           if (g != target && g->specific
10137               && check_generic_tbp_ambiguity (target, g, name, p->where)
10138                   == FAILURE)
10139             return FAILURE;
10140
10141         /* Check for ambiguity with inherited specific targets.  */
10142         for (overridden_tbp = p->overridden; overridden_tbp;
10143              overridden_tbp = overridden_tbp->overridden)
10144           if (overridden_tbp->is_generic)
10145             {
10146               for (g = overridden_tbp->u.generic; g; g = g->next)
10147                 {
10148                   gcc_assert (g->specific);
10149                   if (check_generic_tbp_ambiguity (target, g,
10150                                                    name, p->where) == FAILURE)
10151                     return FAILURE;
10152                 }
10153             }
10154       }
10155
10156   /* If we attempt to "overwrite" a specific binding, this is an error.  */
10157   if (p->overridden && !p->overridden->is_generic)
10158     {
10159       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
10160                  " the same name", name, &p->where);
10161       return FAILURE;
10162     }
10163
10164   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
10165      all must have the same attributes here.  */
10166   first_target = p->u.generic->specific->u.specific;
10167   gcc_assert (first_target);
10168   p->subroutine = first_target->n.sym->attr.subroutine;
10169   p->function = first_target->n.sym->attr.function;
10170
10171   return SUCCESS;
10172 }
10173
10174
10175 /* Resolve a GENERIC procedure binding for a derived type.  */
10176
10177 static gfc_try
10178 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
10179 {
10180   gfc_symbol* super_type;
10181
10182   /* Find the overridden binding if any.  */
10183   st->n.tb->overridden = NULL;
10184   super_type = gfc_get_derived_super_type (derived);
10185   if (super_type)
10186     {
10187       gfc_symtree* overridden;
10188       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
10189                                             true, NULL);
10190
10191       if (overridden && overridden->n.tb)
10192         st->n.tb->overridden = overridden->n.tb;
10193     }
10194
10195   /* Resolve using worker function.  */
10196   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
10197 }
10198
10199
10200 /* Retrieve the target-procedure of an operator binding and do some checks in
10201    common for intrinsic and user-defined type-bound operators.  */
10202
10203 static gfc_symbol*
10204 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
10205 {
10206   gfc_symbol* target_proc;
10207
10208   gcc_assert (target->specific && !target->specific->is_generic);
10209   target_proc = target->specific->u.specific->n.sym;
10210   gcc_assert (target_proc);
10211
10212   /* All operator bindings must have a passed-object dummy argument.  */
10213   if (target->specific->nopass)
10214     {
10215       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
10216       return NULL;
10217     }
10218
10219   return target_proc;
10220 }
10221
10222
10223 /* Resolve a type-bound intrinsic operator.  */
10224
10225 static gfc_try
10226 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
10227                                 gfc_typebound_proc* p)
10228 {
10229   gfc_symbol* super_type;
10230   gfc_tbp_generic* target;
10231   
10232   /* If there's already an error here, do nothing (but don't fail again).  */
10233   if (p->error)
10234     return SUCCESS;
10235
10236   /* Operators should always be GENERIC bindings.  */
10237   gcc_assert (p->is_generic);
10238
10239   /* Look for an overridden binding.  */
10240   super_type = gfc_get_derived_super_type (derived);
10241   if (super_type && super_type->f2k_derived)
10242     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
10243                                                      op, true, NULL);
10244   else
10245     p->overridden = NULL;
10246
10247   /* Resolve general GENERIC properties using worker function.  */
10248   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
10249     goto error;
10250
10251   /* Check the targets to be procedures of correct interface.  */
10252   for (target = p->u.generic; target; target = target->next)
10253     {
10254       gfc_symbol* target_proc;
10255
10256       target_proc = get_checked_tb_operator_target (target, p->where);
10257       if (!target_proc)
10258         goto error;
10259
10260       if (!gfc_check_operator_interface (target_proc, op, p->where))
10261         goto error;
10262     }
10263
10264   return SUCCESS;
10265
10266 error:
10267   p->error = 1;
10268   return FAILURE;
10269 }
10270
10271
10272 /* Resolve a type-bound user operator (tree-walker callback).  */
10273
10274 static gfc_symbol* resolve_bindings_derived;
10275 static gfc_try resolve_bindings_result;
10276
10277 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
10278
10279 static void
10280 resolve_typebound_user_op (gfc_symtree* stree)
10281 {
10282   gfc_symbol* super_type;
10283   gfc_tbp_generic* target;
10284
10285   gcc_assert (stree && stree->n.tb);
10286
10287   if (stree->n.tb->error)
10288     return;
10289
10290   /* Operators should always be GENERIC bindings.  */
10291   gcc_assert (stree->n.tb->is_generic);
10292
10293   /* Find overridden procedure, if any.  */
10294   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10295   if (super_type && super_type->f2k_derived)
10296     {
10297       gfc_symtree* overridden;
10298       overridden = gfc_find_typebound_user_op (super_type, NULL,
10299                                                stree->name, true, NULL);
10300
10301       if (overridden && overridden->n.tb)
10302         stree->n.tb->overridden = overridden->n.tb;
10303     }
10304   else
10305     stree->n.tb->overridden = NULL;
10306
10307   /* Resolve basically using worker function.  */
10308   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
10309         == FAILURE)
10310     goto error;
10311
10312   /* Check the targets to be functions of correct interface.  */
10313   for (target = stree->n.tb->u.generic; target; target = target->next)
10314     {
10315       gfc_symbol* target_proc;
10316
10317       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
10318       if (!target_proc)
10319         goto error;
10320
10321       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
10322         goto error;
10323     }
10324
10325   return;
10326
10327 error:
10328   resolve_bindings_result = FAILURE;
10329   stree->n.tb->error = 1;
10330 }
10331
10332
10333 /* Resolve the type-bound procedures for a derived type.  */
10334
10335 static void
10336 resolve_typebound_procedure (gfc_symtree* stree)
10337 {
10338   gfc_symbol* proc;
10339   locus where;
10340   gfc_symbol* me_arg;
10341   gfc_symbol* super_type;
10342   gfc_component* comp;
10343
10344   gcc_assert (stree);
10345
10346   /* Undefined specific symbol from GENERIC target definition.  */
10347   if (!stree->n.tb)
10348     return;
10349
10350   if (stree->n.tb->error)
10351     return;
10352
10353   /* If this is a GENERIC binding, use that routine.  */
10354   if (stree->n.tb->is_generic)
10355     {
10356       if (resolve_typebound_generic (resolve_bindings_derived, stree)
10357             == FAILURE)
10358         goto error;
10359       return;
10360     }
10361
10362   /* Get the target-procedure to check it.  */
10363   gcc_assert (!stree->n.tb->is_generic);
10364   gcc_assert (stree->n.tb->u.specific);
10365   proc = stree->n.tb->u.specific->n.sym;
10366   where = stree->n.tb->where;
10367
10368   /* Default access should already be resolved from the parser.  */
10369   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
10370
10371   /* It should be a module procedure or an external procedure with explicit
10372      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
10373   if ((!proc->attr.subroutine && !proc->attr.function)
10374       || (proc->attr.proc != PROC_MODULE
10375           && proc->attr.if_source != IFSRC_IFBODY)
10376       || (proc->attr.abstract && !stree->n.tb->deferred))
10377     {
10378       gfc_error ("'%s' must be a module procedure or an external procedure with"
10379                  " an explicit interface at %L", proc->name, &where);
10380       goto error;
10381     }
10382   stree->n.tb->subroutine = proc->attr.subroutine;
10383   stree->n.tb->function = proc->attr.function;
10384
10385   /* Find the super-type of the current derived type.  We could do this once and
10386      store in a global if speed is needed, but as long as not I believe this is
10387      more readable and clearer.  */
10388   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10389
10390   /* If PASS, resolve and check arguments if not already resolved / loaded
10391      from a .mod file.  */
10392   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
10393     {
10394       if (stree->n.tb->pass_arg)
10395         {
10396           gfc_formal_arglist* i;
10397
10398           /* If an explicit passing argument name is given, walk the arg-list
10399              and look for it.  */
10400
10401           me_arg = NULL;
10402           stree->n.tb->pass_arg_num = 1;
10403           for (i = proc->formal; i; i = i->next)
10404             {
10405               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
10406                 {
10407                   me_arg = i->sym;
10408                   break;
10409                 }
10410               ++stree->n.tb->pass_arg_num;
10411             }
10412
10413           if (!me_arg)
10414             {
10415               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
10416                          " argument '%s'",
10417                          proc->name, stree->n.tb->pass_arg, &where,
10418                          stree->n.tb->pass_arg);
10419               goto error;
10420             }
10421         }
10422       else
10423         {
10424           /* Otherwise, take the first one; there should in fact be at least
10425              one.  */
10426           stree->n.tb->pass_arg_num = 1;
10427           if (!proc->formal)
10428             {
10429               gfc_error ("Procedure '%s' with PASS at %L must have at"
10430                          " least one argument", proc->name, &where);
10431               goto error;
10432             }
10433           me_arg = proc->formal->sym;
10434         }
10435
10436       /* Now check that the argument-type matches and the passed-object
10437          dummy argument is generally fine.  */
10438
10439       gcc_assert (me_arg);
10440
10441       if (me_arg->ts.type != BT_CLASS)
10442         {
10443           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10444                      " at %L", proc->name, &where);
10445           goto error;
10446         }
10447
10448       if (CLASS_DATA (me_arg)->ts.u.derived
10449           != resolve_bindings_derived)
10450         {
10451           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10452                      " the derived-type '%s'", me_arg->name, proc->name,
10453                      me_arg->name, &where, resolve_bindings_derived->name);
10454           goto error;
10455         }
10456   
10457       gcc_assert (me_arg->ts.type == BT_CLASS);
10458       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
10459         {
10460           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
10461                      " scalar", proc->name, &where);
10462           goto error;
10463         }
10464       if (CLASS_DATA (me_arg)->attr.allocatable)
10465         {
10466           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10467                      " be ALLOCATABLE", proc->name, &where);
10468           goto error;
10469         }
10470       if (CLASS_DATA (me_arg)->attr.class_pointer)
10471         {
10472           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
10473                      " be POINTER", proc->name, &where);
10474           goto error;
10475         }
10476     }
10477
10478   /* If we are extending some type, check that we don't override a procedure
10479      flagged NON_OVERRIDABLE.  */
10480   stree->n.tb->overridden = NULL;
10481   if (super_type)
10482     {
10483       gfc_symtree* overridden;
10484       overridden = gfc_find_typebound_proc (super_type, NULL,
10485                                             stree->name, true, NULL);
10486
10487       if (overridden && overridden->n.tb)
10488         stree->n.tb->overridden = overridden->n.tb;
10489
10490       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
10491         goto error;
10492     }
10493
10494   /* See if there's a name collision with a component directly in this type.  */
10495   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
10496     if (!strcmp (comp->name, stree->name))
10497       {
10498         gfc_error ("Procedure '%s' at %L has the same name as a component of"
10499                    " '%s'",
10500                    stree->name, &where, resolve_bindings_derived->name);
10501         goto error;
10502       }
10503
10504   /* Try to find a name collision with an inherited component.  */
10505   if (super_type && gfc_find_component (super_type, stree->name, true, true))
10506     {
10507       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
10508                  " component of '%s'",
10509                  stree->name, &where, resolve_bindings_derived->name);
10510       goto error;
10511     }
10512
10513   stree->n.tb->error = 0;
10514   return;
10515
10516 error:
10517   resolve_bindings_result = FAILURE;
10518   stree->n.tb->error = 1;
10519 }
10520
10521 static gfc_try
10522 resolve_typebound_procedures (gfc_symbol* derived)
10523 {
10524   int op;
10525
10526   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
10527     return SUCCESS;
10528
10529   resolve_bindings_derived = derived;
10530   resolve_bindings_result = SUCCESS;
10531
10532   if (derived->f2k_derived->tb_sym_root)
10533     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
10534                           &resolve_typebound_procedure);
10535
10536   if (derived->f2k_derived->tb_uop_root)
10537     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
10538                           &resolve_typebound_user_op);
10539
10540   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
10541     {
10542       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
10543       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
10544                                                p) == FAILURE)
10545         resolve_bindings_result = FAILURE;
10546     }
10547
10548   return resolve_bindings_result;
10549 }
10550
10551
10552 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
10553    to give all identical derived types the same backend_decl.  */
10554 static void
10555 add_dt_to_dt_list (gfc_symbol *derived)
10556 {
10557   gfc_dt_list *dt_list;
10558
10559   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
10560     if (derived == dt_list->derived)
10561       break;
10562
10563   if (dt_list == NULL)
10564     {
10565       dt_list = gfc_get_dt_list ();
10566       dt_list->next = gfc_derived_types;
10567       dt_list->derived = derived;
10568       gfc_derived_types = dt_list;
10569     }
10570 }
10571
10572
10573 /* Ensure that a derived-type is really not abstract, meaning that every
10574    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
10575
10576 static gfc_try
10577 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
10578 {
10579   if (!st)
10580     return SUCCESS;
10581
10582   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
10583     return FAILURE;
10584   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
10585     return FAILURE;
10586
10587   if (st->n.tb && st->n.tb->deferred)
10588     {
10589       gfc_symtree* overriding;
10590       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
10591       if (!overriding)
10592         return FAILURE;
10593       gcc_assert (overriding->n.tb);
10594       if (overriding->n.tb->deferred)
10595         {
10596           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
10597                      " '%s' is DEFERRED and not overridden",
10598                      sub->name, &sub->declared_at, st->name);
10599           return FAILURE;
10600         }
10601     }
10602
10603   return SUCCESS;
10604 }
10605
10606 static gfc_try
10607 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
10608 {
10609   /* The algorithm used here is to recursively travel up the ancestry of sub
10610      and for each ancestor-type, check all bindings.  If any of them is
10611      DEFERRED, look it up starting from sub and see if the found (overriding)
10612      binding is not DEFERRED.
10613      This is not the most efficient way to do this, but it should be ok and is
10614      clearer than something sophisticated.  */
10615
10616   gcc_assert (ancestor && !sub->attr.abstract);
10617   
10618   if (!ancestor->attr.abstract)
10619     return SUCCESS;
10620
10621   /* Walk bindings of this ancestor.  */
10622   if (ancestor->f2k_derived)
10623     {
10624       gfc_try t;
10625       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
10626       if (t == FAILURE)
10627         return FAILURE;
10628     }
10629
10630   /* Find next ancestor type and recurse on it.  */
10631   ancestor = gfc_get_derived_super_type (ancestor);
10632   if (ancestor)
10633     return ensure_not_abstract (sub, ancestor);
10634
10635   return SUCCESS;
10636 }
10637
10638
10639 static void resolve_symbol (gfc_symbol *sym);
10640
10641
10642 /* Resolve the components of a derived type.  */
10643
10644 static gfc_try
10645 resolve_fl_derived (gfc_symbol *sym)
10646 {
10647   gfc_symbol* super_type;
10648   gfc_component *c;
10649   int i;
10650
10651   super_type = gfc_get_derived_super_type (sym);
10652   
10653   if (sym->attr.is_class && sym->ts.u.derived == NULL)
10654     {
10655       /* Fix up incomplete CLASS symbols.  */
10656       gfc_component *data = gfc_find_component (sym, "$data", true, true);
10657       gfc_component *vptr = gfc_find_component (sym, "$vptr", true, true);
10658       if (vptr->ts.u.derived == NULL)
10659         {
10660           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived, false);
10661           gcc_assert (vtab);
10662           vptr->ts.u.derived = vtab->ts.u.derived;
10663         }
10664     }
10665
10666   /* F2008, C432. */
10667   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
10668     {
10669       gfc_error ("As extending type '%s' at %L has a coarray component, "
10670                  "parent type '%s' shall also have one", sym->name,
10671                  &sym->declared_at, super_type->name);
10672       return FAILURE;
10673     }
10674
10675   /* Ensure the extended type gets resolved before we do.  */
10676   if (super_type && resolve_fl_derived (super_type) == FAILURE)
10677     return FAILURE;
10678
10679   /* An ABSTRACT type must be extensible.  */
10680   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
10681     {
10682       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
10683                  sym->name, &sym->declared_at);
10684       return FAILURE;
10685     }
10686
10687   for (c = sym->components; c != NULL; c = c->next)
10688     {
10689       /* F2008, C442.  */
10690       if (c->attr.codimension /* FIXME: c->as check due to PR 43412.  */
10691           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
10692         {
10693           gfc_error ("Coarray component '%s' at %L must be allocatable with "
10694                      "deferred shape", c->name, &c->loc);
10695           return FAILURE;
10696         }
10697
10698       /* F2008, C443.  */
10699       if (c->attr.codimension && c->ts.type == BT_DERIVED
10700           && c->ts.u.derived->ts.is_iso_c)
10701         {
10702           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
10703                      "shall not be a coarray", c->name, &c->loc);
10704           return FAILURE;
10705         }
10706
10707       /* F2008, C444.  */
10708       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
10709           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
10710               || c->attr.allocatable))
10711         {
10712           gfc_error ("Component '%s' at %L with coarray component "
10713                      "shall be a nonpointer, nonallocatable scalar",
10714                      c->name, &c->loc);
10715           return FAILURE;
10716         }
10717
10718       if (c->attr.proc_pointer && c->ts.interface)
10719         {
10720           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
10721             gfc_error ("Interface '%s', used by procedure pointer component "
10722                        "'%s' at %L, is declared in a later PROCEDURE statement",
10723                        c->ts.interface->name, c->name, &c->loc);
10724
10725           /* Get the attributes from the interface (now resolved).  */
10726           if (c->ts.interface->attr.if_source
10727               || c->ts.interface->attr.intrinsic)
10728             {
10729               gfc_symbol *ifc = c->ts.interface;
10730
10731               if (ifc->formal && !ifc->formal_ns)
10732                 resolve_symbol (ifc);
10733
10734               if (ifc->attr.intrinsic)
10735                 resolve_intrinsic (ifc, &ifc->declared_at);
10736
10737               if (ifc->result)
10738                 {
10739                   c->ts = ifc->result->ts;
10740                   c->attr.allocatable = ifc->result->attr.allocatable;
10741                   c->attr.pointer = ifc->result->attr.pointer;
10742                   c->attr.dimension = ifc->result->attr.dimension;
10743                   c->as = gfc_copy_array_spec (ifc->result->as);
10744                 }
10745               else
10746                 {   
10747                   c->ts = ifc->ts;
10748                   c->attr.allocatable = ifc->attr.allocatable;
10749                   c->attr.pointer = ifc->attr.pointer;
10750                   c->attr.dimension = ifc->attr.dimension;
10751                   c->as = gfc_copy_array_spec (ifc->as);
10752                 }
10753               c->ts.interface = ifc;
10754               c->attr.function = ifc->attr.function;
10755               c->attr.subroutine = ifc->attr.subroutine;
10756               gfc_copy_formal_args_ppc (c, ifc);
10757
10758               c->attr.pure = ifc->attr.pure;
10759               c->attr.elemental = ifc->attr.elemental;
10760               c->attr.recursive = ifc->attr.recursive;
10761               c->attr.always_explicit = ifc->attr.always_explicit;
10762               c->attr.ext_attr |= ifc->attr.ext_attr;
10763               /* Replace symbols in array spec.  */
10764               if (c->as)
10765                 {
10766                   int i;
10767                   for (i = 0; i < c->as->rank; i++)
10768                     {
10769                       gfc_expr_replace_comp (c->as->lower[i], c);
10770                       gfc_expr_replace_comp (c->as->upper[i], c);
10771                     }
10772                 }
10773               /* Copy char length.  */
10774               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
10775                 {
10776                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
10777                   gfc_expr_replace_comp (cl->length, c);
10778                   if (cl->length && !cl->resolved
10779                         && gfc_resolve_expr (cl->length) == FAILURE)
10780                     return FAILURE;
10781                   c->ts.u.cl = cl;
10782                 }
10783             }
10784           else if (c->ts.interface->name[0] != '\0' && !sym->attr.vtype)
10785             {
10786               gfc_error ("Interface '%s' of procedure pointer component "
10787                          "'%s' at %L must be explicit", c->ts.interface->name,
10788                          c->name, &c->loc);
10789               return FAILURE;
10790             }
10791         }
10792       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
10793         {
10794           /* Since PPCs are not implicitly typed, a PPC without an explicit
10795              interface must be a subroutine.  */
10796           gfc_add_subroutine (&c->attr, c->name, &c->loc);
10797         }
10798
10799       /* Procedure pointer components: Check PASS arg.  */
10800       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
10801           && !sym->attr.vtype)
10802         {
10803           gfc_symbol* me_arg;
10804
10805           if (c->tb->pass_arg)
10806             {
10807               gfc_formal_arglist* i;
10808
10809               /* If an explicit passing argument name is given, walk the arg-list
10810                 and look for it.  */
10811
10812               me_arg = NULL;
10813               c->tb->pass_arg_num = 1;
10814               for (i = c->formal; i; i = i->next)
10815                 {
10816                   if (!strcmp (i->sym->name, c->tb->pass_arg))
10817                     {
10818                       me_arg = i->sym;
10819                       break;
10820                     }
10821                   c->tb->pass_arg_num++;
10822                 }
10823
10824               if (!me_arg)
10825                 {
10826                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
10827                              "at %L has no argument '%s'", c->name,
10828                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
10829                   c->tb->error = 1;
10830                   return FAILURE;
10831                 }
10832             }
10833           else
10834             {
10835               /* Otherwise, take the first one; there should in fact be at least
10836                 one.  */
10837               c->tb->pass_arg_num = 1;
10838               if (!c->formal)
10839                 {
10840                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
10841                              "must have at least one argument",
10842                              c->name, &c->loc);
10843                   c->tb->error = 1;
10844                   return FAILURE;
10845                 }
10846               me_arg = c->formal->sym;
10847             }
10848
10849           /* Now check that the argument-type matches.  */
10850           gcc_assert (me_arg);
10851           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
10852               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
10853               || (me_arg->ts.type == BT_CLASS
10854                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
10855             {
10856               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
10857                          " the derived type '%s'", me_arg->name, c->name,
10858                          me_arg->name, &c->loc, sym->name);
10859               c->tb->error = 1;
10860               return FAILURE;
10861             }
10862
10863           /* Check for C453.  */
10864           if (me_arg->attr.dimension)
10865             {
10866               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10867                          "must be scalar", me_arg->name, c->name, me_arg->name,
10868                          &c->loc);
10869               c->tb->error = 1;
10870               return FAILURE;
10871             }
10872
10873           if (me_arg->attr.pointer)
10874             {
10875               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10876                          "may not have the POINTER attribute", me_arg->name,
10877                          c->name, me_arg->name, &c->loc);
10878               c->tb->error = 1;
10879               return FAILURE;
10880             }
10881
10882           if (me_arg->attr.allocatable)
10883             {
10884               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
10885                          "may not be ALLOCATABLE", me_arg->name, c->name,
10886                          me_arg->name, &c->loc);
10887               c->tb->error = 1;
10888               return FAILURE;
10889             }
10890
10891           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
10892             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
10893                        " at %L", c->name, &c->loc);
10894
10895         }
10896
10897       /* Check type-spec if this is not the parent-type component.  */
10898       if ((!sym->attr.extension || c != sym->components)
10899           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
10900         return FAILURE;
10901
10902       /* If this type is an extension, set the accessibility of the parent
10903          component.  */
10904       if (super_type && c == sym->components
10905           && strcmp (super_type->name, c->name) == 0)
10906         c->attr.access = super_type->attr.access;
10907       
10908       /* If this type is an extension, see if this component has the same name
10909          as an inherited type-bound procedure.  */
10910       if (super_type && !sym->attr.is_class
10911           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
10912         {
10913           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
10914                      " inherited type-bound procedure",
10915                      c->name, sym->name, &c->loc);
10916           return FAILURE;
10917         }
10918
10919       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer)
10920         {
10921          if (c->ts.u.cl->length == NULL
10922              || (resolve_charlen (c->ts.u.cl) == FAILURE)
10923              || !gfc_is_constant_expr (c->ts.u.cl->length))
10924            {
10925              gfc_error ("Character length of component '%s' needs to "
10926                         "be a constant specification expression at %L",
10927                         c->name,
10928                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
10929              return FAILURE;
10930            }
10931         }
10932
10933       if (c->ts.type == BT_DERIVED
10934           && sym->component_access != ACCESS_PRIVATE
10935           && gfc_check_access (sym->attr.access, sym->ns->default_access)
10936           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
10937           && !c->ts.u.derived->attr.use_assoc
10938           && !gfc_check_access (c->ts.u.derived->attr.access,
10939                                 c->ts.u.derived->ns->default_access)
10940           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
10941                              "is a PRIVATE type and cannot be a component of "
10942                              "'%s', which is PUBLIC at %L", c->name,
10943                              sym->name, &sym->declared_at) == FAILURE)
10944         return FAILURE;
10945
10946       if (sym->attr.sequence)
10947         {
10948           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
10949             {
10950               gfc_error ("Component %s of SEQUENCE type declared at %L does "
10951                          "not have the SEQUENCE attribute",
10952                          c->ts.u.derived->name, &sym->declared_at);
10953               return FAILURE;
10954             }
10955         }
10956
10957       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && c->attr.pointer
10958           && c->ts.u.derived->components == NULL
10959           && !c->ts.u.derived->attr.zero_comp)
10960         {
10961           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
10962                      "that has not been declared", c->name, sym->name,
10963                      &c->loc);
10964           return FAILURE;
10965         }
10966
10967       if (c->ts.type == BT_CLASS && CLASS_DATA (c)->attr.pointer
10968           && CLASS_DATA (c)->ts.u.derived->components == NULL
10969           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
10970         {
10971           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
10972                      "that has not been declared", c->name, sym->name,
10973                      &c->loc);
10974           return FAILURE;
10975         }
10976
10977       /* C437.  */
10978       if (c->ts.type == BT_CLASS
10979           && !(CLASS_DATA (c)->attr.pointer || CLASS_DATA (c)->attr.allocatable))
10980         {
10981           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
10982                      "or pointer", c->name, &c->loc);
10983           return FAILURE;
10984         }
10985
10986       /* Ensure that all the derived type components are put on the
10987          derived type list; even in formal namespaces, where derived type
10988          pointer components might not have been declared.  */
10989       if (c->ts.type == BT_DERIVED
10990             && c->ts.u.derived
10991             && c->ts.u.derived->components
10992             && c->attr.pointer
10993             && sym != c->ts.u.derived)
10994         add_dt_to_dt_list (c->ts.u.derived);
10995
10996       if (c->attr.pointer || c->attr.proc_pointer || c->attr.allocatable
10997           || c->as == NULL)
10998         continue;
10999
11000       for (i = 0; i < c->as->rank; i++)
11001         {
11002           if (c->as->lower[i] == NULL
11003               || (resolve_index_expr (c->as->lower[i]) == FAILURE)
11004               || !gfc_is_constant_expr (c->as->lower[i])
11005               || c->as->upper[i] == NULL
11006               || (resolve_index_expr (c->as->upper[i]) == FAILURE)
11007               || !gfc_is_constant_expr (c->as->upper[i]))
11008             {
11009               gfc_error ("Component '%s' of '%s' at %L must have "
11010                          "constant array bounds",
11011                          c->name, sym->name, &c->loc);
11012               return FAILURE;
11013             }
11014         }
11015     }
11016
11017   /* Resolve the type-bound procedures.  */
11018   if (resolve_typebound_procedures (sym) == FAILURE)
11019     return FAILURE;
11020
11021   /* Resolve the finalizer procedures.  */
11022   if (gfc_resolve_finalizers (sym) == FAILURE)
11023     return FAILURE;
11024
11025   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11026      all DEFERRED bindings are overridden.  */
11027   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11028       && ensure_not_abstract (sym, super_type) == FAILURE)
11029     return FAILURE;
11030
11031   /* Add derived type to the derived type list.  */
11032   add_dt_to_dt_list (sym);
11033
11034   return SUCCESS;
11035 }
11036
11037
11038 static gfc_try
11039 resolve_fl_namelist (gfc_symbol *sym)
11040 {
11041   gfc_namelist *nl;
11042   gfc_symbol *nlsym;
11043
11044   /* Reject PRIVATE objects in a PUBLIC namelist.  */
11045   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
11046     {
11047       for (nl = sym->namelist; nl; nl = nl->next)
11048         {
11049           if (!nl->sym->attr.use_assoc
11050               && !is_sym_host_assoc (nl->sym, sym->ns)
11051               && !gfc_check_access(nl->sym->attr.access,
11052                                 nl->sym->ns->default_access))
11053             {
11054               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
11055                          "cannot be member of PUBLIC namelist '%s' at %L",
11056                          nl->sym->name, sym->name, &sym->declared_at);
11057               return FAILURE;
11058             }
11059
11060           /* Types with private components that came here by USE-association.  */
11061           if (nl->sym->ts.type == BT_DERIVED
11062               && derived_inaccessible (nl->sym->ts.u.derived))
11063             {
11064               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
11065                          "components and cannot be member of namelist '%s' at %L",
11066                          nl->sym->name, sym->name, &sym->declared_at);
11067               return FAILURE;
11068             }
11069
11070           /* Types with private components that are defined in the same module.  */
11071           if (nl->sym->ts.type == BT_DERIVED
11072               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
11073               && !gfc_check_access (nl->sym->ts.u.derived->attr.private_comp
11074                                         ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
11075                                         nl->sym->ns->default_access))
11076             {
11077               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
11078                          "cannot be a member of PUBLIC namelist '%s' at %L",
11079                          nl->sym->name, sym->name, &sym->declared_at);
11080               return FAILURE;
11081             }
11082         }
11083     }
11084
11085   for (nl = sym->namelist; nl; nl = nl->next)
11086     {
11087       /* Reject namelist arrays of assumed shape.  */
11088       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
11089           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
11090                              "must not have assumed shape in namelist "
11091                              "'%s' at %L", nl->sym->name, sym->name,
11092                              &sym->declared_at) == FAILURE)
11093             return FAILURE;
11094
11095       /* Reject namelist arrays that are not constant shape.  */
11096       if (is_non_constant_shape_array (nl->sym))
11097         {
11098           gfc_error ("NAMELIST array object '%s' must have constant "
11099                      "shape in namelist '%s' at %L", nl->sym->name,
11100                      sym->name, &sym->declared_at);
11101           return FAILURE;
11102         }
11103
11104       /* Namelist objects cannot have allocatable or pointer components.  */
11105       if (nl->sym->ts.type != BT_DERIVED)
11106         continue;
11107
11108       if (nl->sym->ts.u.derived->attr.alloc_comp)
11109         {
11110           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11111                      "have ALLOCATABLE components",
11112                      nl->sym->name, sym->name, &sym->declared_at);
11113           return FAILURE;
11114         }
11115
11116       if (nl->sym->ts.u.derived->attr.pointer_comp)
11117         {
11118           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11119                      "have POINTER components", 
11120                      nl->sym->name, sym->name, &sym->declared_at);
11121           return FAILURE;
11122         }
11123     }
11124
11125
11126   /* 14.1.2 A module or internal procedure represent local entities
11127      of the same type as a namelist member and so are not allowed.  */
11128   for (nl = sym->namelist; nl; nl = nl->next)
11129     {
11130       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
11131         continue;
11132
11133       if (nl->sym->attr.function && nl->sym == nl->sym->result)
11134         if ((nl->sym == sym->ns->proc_name)
11135                ||
11136             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
11137           continue;
11138
11139       nlsym = NULL;
11140       if (nl->sym && nl->sym->name)
11141         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
11142       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
11143         {
11144           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
11145                      "attribute in '%s' at %L", nlsym->name,
11146                      &sym->declared_at);
11147           return FAILURE;
11148         }
11149     }
11150
11151   return SUCCESS;
11152 }
11153
11154
11155 static gfc_try
11156 resolve_fl_parameter (gfc_symbol *sym)
11157 {
11158   /* A parameter array's shape needs to be constant.  */
11159   if (sym->as != NULL 
11160       && (sym->as->type == AS_DEFERRED
11161           || is_non_constant_shape_array (sym)))
11162     {
11163       gfc_error ("Parameter array '%s' at %L cannot be automatic "
11164                  "or of deferred shape", sym->name, &sym->declared_at);
11165       return FAILURE;
11166     }
11167
11168   /* Make sure a parameter that has been implicitly typed still
11169      matches the implicit type, since PARAMETER statements can precede
11170      IMPLICIT statements.  */
11171   if (sym->attr.implicit_type
11172       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
11173                                                              sym->ns)))
11174     {
11175       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
11176                  "later IMPLICIT type", sym->name, &sym->declared_at);
11177       return FAILURE;
11178     }
11179
11180   /* Make sure the types of derived parameters are consistent.  This
11181      type checking is deferred until resolution because the type may
11182      refer to a derived type from the host.  */
11183   if (sym->ts.type == BT_DERIVED
11184       && !gfc_compare_types (&sym->ts, &sym->value->ts))
11185     {
11186       gfc_error ("Incompatible derived type in PARAMETER at %L",
11187                  &sym->value->where);
11188       return FAILURE;
11189     }
11190   return SUCCESS;
11191 }
11192
11193
11194 /* Do anything necessary to resolve a symbol.  Right now, we just
11195    assume that an otherwise unknown symbol is a variable.  This sort
11196    of thing commonly happens for symbols in module.  */
11197
11198 static void
11199 resolve_symbol (gfc_symbol *sym)
11200 {
11201   int check_constant, mp_flag;
11202   gfc_symtree *symtree;
11203   gfc_symtree *this_symtree;
11204   gfc_namespace *ns;
11205   gfc_component *c;
11206
11207   /* Avoid double resolution of function result symbols.  */
11208   if ((sym->result || sym->attr.result) && (sym->ns != gfc_current_ns))
11209     return;
11210   
11211   if (sym->attr.flavor == FL_UNKNOWN)
11212     {
11213
11214     /* If we find that a flavorless symbol is an interface in one of the
11215        parent namespaces, find its symtree in this namespace, free the
11216        symbol and set the symtree to point to the interface symbol.  */
11217       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
11218         {
11219           symtree = gfc_find_symtree (ns->sym_root, sym->name);
11220           if (symtree && symtree->n.sym->generic)
11221             {
11222               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
11223                                                sym->name);
11224               sym->refs--;
11225               if (!sym->refs)
11226                 gfc_free_symbol (sym);
11227               symtree->n.sym->refs++;
11228               this_symtree->n.sym = symtree->n.sym;
11229               return;
11230             }
11231         }
11232
11233       /* Otherwise give it a flavor according to such attributes as
11234          it has.  */
11235       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
11236         sym->attr.flavor = FL_VARIABLE;
11237       else
11238         {
11239           sym->attr.flavor = FL_PROCEDURE;
11240           if (sym->attr.dimension)
11241             sym->attr.function = 1;
11242         }
11243     }
11244
11245   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
11246     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
11247
11248   if (sym->attr.procedure && sym->ts.interface
11249       && sym->attr.if_source != IFSRC_DECL)
11250     {
11251       if (sym->ts.interface == sym)
11252         {
11253           gfc_error ("PROCEDURE '%s' at %L may not be used as its own "
11254                      "interface", sym->name, &sym->declared_at);
11255           return;
11256         }
11257       if (sym->ts.interface->attr.procedure)
11258         {
11259           gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared"
11260                      " in a later PROCEDURE statement", sym->ts.interface->name,
11261                      sym->name,&sym->declared_at);
11262           return;
11263         }
11264
11265       /* Get the attributes from the interface (now resolved).  */
11266       if (sym->ts.interface->attr.if_source
11267           || sym->ts.interface->attr.intrinsic)
11268         {
11269           gfc_symbol *ifc = sym->ts.interface;
11270           resolve_symbol (ifc);
11271
11272           if (ifc->attr.intrinsic)
11273             resolve_intrinsic (ifc, &ifc->declared_at);
11274
11275           if (ifc->result)
11276             sym->ts = ifc->result->ts;
11277           else   
11278             sym->ts = ifc->ts;
11279           sym->ts.interface = ifc;
11280           sym->attr.function = ifc->attr.function;
11281           sym->attr.subroutine = ifc->attr.subroutine;
11282           gfc_copy_formal_args (sym, ifc);
11283
11284           sym->attr.allocatable = ifc->attr.allocatable;
11285           sym->attr.pointer = ifc->attr.pointer;
11286           sym->attr.pure = ifc->attr.pure;
11287           sym->attr.elemental = ifc->attr.elemental;
11288           sym->attr.dimension = ifc->attr.dimension;
11289           sym->attr.recursive = ifc->attr.recursive;
11290           sym->attr.always_explicit = ifc->attr.always_explicit;
11291           sym->attr.ext_attr |= ifc->attr.ext_attr;
11292           /* Copy array spec.  */
11293           sym->as = gfc_copy_array_spec (ifc->as);
11294           if (sym->as)
11295             {
11296               int i;
11297               for (i = 0; i < sym->as->rank; i++)
11298                 {
11299                   gfc_expr_replace_symbols (sym->as->lower[i], sym);
11300                   gfc_expr_replace_symbols (sym->as->upper[i], sym);
11301                 }
11302             }
11303           /* Copy char length.  */
11304           if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11305             {
11306               sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11307               gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
11308               if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
11309                     && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
11310                 return;
11311             }
11312         }
11313       else if (sym->ts.interface->name[0] != '\0')
11314         {
11315           gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
11316                     sym->ts.interface->name, sym->name, &sym->declared_at);
11317           return;
11318         }
11319     }
11320
11321   if (sym->attr.is_protected && !sym->attr.proc_pointer
11322       && (sym->attr.procedure || sym->attr.external))
11323     {
11324       if (sym->attr.external)
11325         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
11326                    "at %L", &sym->declared_at);
11327       else
11328         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
11329                    "at %L", &sym->declared_at);
11330
11331       return;
11332     }
11333
11334   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
11335     return;
11336
11337   /* Symbols that are module procedures with results (functions) have
11338      the types and array specification copied for type checking in
11339      procedures that call them, as well as for saving to a module
11340      file.  These symbols can't stand the scrutiny that their results
11341      can.  */
11342   mp_flag = (sym->result != NULL && sym->result != sym);
11343
11344
11345   /* Make sure that the intrinsic is consistent with its internal 
11346      representation. This needs to be done before assigning a default 
11347      type to avoid spurious warnings.  */
11348   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
11349       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
11350     return;
11351
11352   /* Assign default type to symbols that need one and don't have one.  */
11353   if (sym->ts.type == BT_UNKNOWN)
11354     {
11355       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
11356         gfc_set_default_type (sym, 1, NULL);
11357
11358       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
11359           && !sym->attr.function && !sym->attr.subroutine
11360           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
11361         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
11362
11363       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
11364         {
11365           /* The specific case of an external procedure should emit an error
11366              in the case that there is no implicit type.  */
11367           if (!mp_flag)
11368             gfc_set_default_type (sym, sym->attr.external, NULL);
11369           else
11370             {
11371               /* Result may be in another namespace.  */
11372               resolve_symbol (sym->result);
11373
11374               if (!sym->result->attr.proc_pointer)
11375                 {
11376                   sym->ts = sym->result->ts;
11377                   sym->as = gfc_copy_array_spec (sym->result->as);
11378                   sym->attr.dimension = sym->result->attr.dimension;
11379                   sym->attr.pointer = sym->result->attr.pointer;
11380                   sym->attr.allocatable = sym->result->attr.allocatable;
11381                 }
11382             }
11383         }
11384     }
11385
11386   /* Assumed size arrays and assumed shape arrays must be dummy
11387      arguments.  */
11388
11389   if (sym->as != NULL
11390       && ((sym->as->type == AS_ASSUMED_SIZE && !sym->as->cp_was_assumed)
11391           || sym->as->type == AS_ASSUMED_SHAPE)
11392       && sym->attr.dummy == 0)
11393     {
11394       if (sym->as->type == AS_ASSUMED_SIZE)
11395         gfc_error ("Assumed size array at %L must be a dummy argument",
11396                    &sym->declared_at);
11397       else
11398         gfc_error ("Assumed shape array at %L must be a dummy argument",
11399                    &sym->declared_at);
11400       return;
11401     }
11402
11403   /* Make sure symbols with known intent or optional are really dummy
11404      variable.  Because of ENTRY statement, this has to be deferred
11405      until resolution time.  */
11406
11407   if (!sym->attr.dummy
11408       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
11409     {
11410       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
11411       return;
11412     }
11413
11414   if (sym->attr.value && !sym->attr.dummy)
11415     {
11416       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
11417                  "it is not a dummy argument", sym->name, &sym->declared_at);
11418       return;
11419     }
11420
11421   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
11422     {
11423       gfc_charlen *cl = sym->ts.u.cl;
11424       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
11425         {
11426           gfc_error ("Character dummy variable '%s' at %L with VALUE "
11427                      "attribute must have constant length",
11428                      sym->name, &sym->declared_at);
11429           return;
11430         }
11431
11432       if (sym->ts.is_c_interop
11433           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
11434         {
11435           gfc_error ("C interoperable character dummy variable '%s' at %L "
11436                      "with VALUE attribute must have length one",
11437                      sym->name, &sym->declared_at);
11438           return;
11439         }
11440     }
11441
11442   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
11443      do this for something that was implicitly typed because that is handled
11444      in gfc_set_default_type.  Handle dummy arguments and procedure
11445      definitions separately.  Also, anything that is use associated is not
11446      handled here but instead is handled in the module it is declared in.
11447      Finally, derived type definitions are allowed to be BIND(C) since that
11448      only implies that they're interoperable, and they are checked fully for
11449      interoperability when a variable is declared of that type.  */
11450   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
11451       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
11452       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
11453     {
11454       gfc_try t = SUCCESS;
11455       
11456       /* First, make sure the variable is declared at the
11457          module-level scope (J3/04-007, Section 15.3).  */
11458       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
11459           sym->attr.in_common == 0)
11460         {
11461           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
11462                      "is neither a COMMON block nor declared at the "
11463                      "module level scope", sym->name, &(sym->declared_at));
11464           t = FAILURE;
11465         }
11466       else if (sym->common_head != NULL)
11467         {
11468           t = verify_com_block_vars_c_interop (sym->common_head);
11469         }
11470       else
11471         {
11472           /* If type() declaration, we need to verify that the components
11473              of the given type are all C interoperable, etc.  */
11474           if (sym->ts.type == BT_DERIVED &&
11475               sym->ts.u.derived->attr.is_c_interop != 1)
11476             {
11477               /* Make sure the user marked the derived type as BIND(C).  If
11478                  not, call the verify routine.  This could print an error
11479                  for the derived type more than once if multiple variables
11480                  of that type are declared.  */
11481               if (sym->ts.u.derived->attr.is_bind_c != 1)
11482                 verify_bind_c_derived_type (sym->ts.u.derived);
11483               t = FAILURE;
11484             }
11485           
11486           /* Verify the variable itself as C interoperable if it
11487              is BIND(C).  It is not possible for this to succeed if
11488              the verify_bind_c_derived_type failed, so don't have to handle
11489              any error returned by verify_bind_c_derived_type.  */
11490           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
11491                                  sym->common_block);
11492         }
11493
11494       if (t == FAILURE)
11495         {
11496           /* clear the is_bind_c flag to prevent reporting errors more than
11497              once if something failed.  */
11498           sym->attr.is_bind_c = 0;
11499           return;
11500         }
11501     }
11502
11503   /* If a derived type symbol has reached this point, without its
11504      type being declared, we have an error.  Notice that most
11505      conditions that produce undefined derived types have already
11506      been dealt with.  However, the likes of:
11507      implicit type(t) (t) ..... call foo (t) will get us here if
11508      the type is not declared in the scope of the implicit
11509      statement. Change the type to BT_UNKNOWN, both because it is so
11510      and to prevent an ICE.  */
11511   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
11512       && !sym->ts.u.derived->attr.zero_comp)
11513     {
11514       gfc_error ("The derived type '%s' at %L is of type '%s', "
11515                  "which has not been defined", sym->name,
11516                   &sym->declared_at, sym->ts.u.derived->name);
11517       sym->ts.type = BT_UNKNOWN;
11518       return;
11519     }
11520
11521   /* Make sure that the derived type has been resolved and that the
11522      derived type is visible in the symbol's namespace, if it is a
11523      module function and is not PRIVATE.  */
11524   if (sym->ts.type == BT_DERIVED
11525         && sym->ts.u.derived->attr.use_assoc
11526         && sym->ns->proc_name
11527         && sym->ns->proc_name->attr.flavor == FL_MODULE)
11528     {
11529       gfc_symbol *ds;
11530
11531       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
11532         return;
11533
11534       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
11535       if (!ds && sym->attr.function
11536             && gfc_check_access (sym->attr.access, sym->ns->default_access))
11537         {
11538           symtree = gfc_new_symtree (&sym->ns->sym_root,
11539                                      sym->ts.u.derived->name);
11540           symtree->n.sym = sym->ts.u.derived;
11541           sym->ts.u.derived->refs++;
11542         }
11543     }
11544
11545   /* Unless the derived-type declaration is use associated, Fortran 95
11546      does not allow public entries of private derived types.
11547      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
11548      161 in 95-006r3.  */
11549   if (sym->ts.type == BT_DERIVED
11550       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
11551       && !sym->ts.u.derived->attr.use_assoc
11552       && gfc_check_access (sym->attr.access, sym->ns->default_access)
11553       && !gfc_check_access (sym->ts.u.derived->attr.access,
11554                             sym->ts.u.derived->ns->default_access)
11555       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
11556                          "of PRIVATE derived type '%s'",
11557                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
11558                          : "variable", sym->name, &sym->declared_at,
11559                          sym->ts.u.derived->name) == FAILURE)
11560     return;
11561
11562   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
11563      default initialization is defined (5.1.2.4.4).  */
11564   if (sym->ts.type == BT_DERIVED
11565       && sym->attr.dummy
11566       && sym->attr.intent == INTENT_OUT
11567       && sym->as
11568       && sym->as->type == AS_ASSUMED_SIZE)
11569     {
11570       for (c = sym->ts.u.derived->components; c; c = c->next)
11571         {
11572           if (c->initializer)
11573             {
11574               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
11575                          "ASSUMED SIZE and so cannot have a default initializer",
11576                          sym->name, &sym->declared_at);
11577               return;
11578             }
11579         }
11580     }
11581
11582   /* F2008, C526.  */
11583   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11584        || sym->attr.codimension)
11585       && sym->attr.result)
11586     gfc_error ("Function result '%s' at %L shall not be a coarray or have "
11587                "a coarray component", sym->name, &sym->declared_at);
11588
11589   /* F2008, C524.  */
11590   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
11591       && sym->ts.u.derived->ts.is_iso_c)
11592     gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11593                "shall not be a coarray", sym->name, &sym->declared_at);
11594
11595   /* F2008, C525.  */
11596   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp
11597       && (sym->attr.codimension || sym->attr.pointer || sym->attr.dimension
11598           || sym->attr.allocatable))
11599     gfc_error ("Variable '%s' at %L with coarray component "
11600                "shall be a nonpointer, nonallocatable scalar",
11601                sym->name, &sym->declared_at);
11602
11603   /* F2008, C526.  The function-result case was handled above.  */
11604   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11605        || sym->attr.codimension)
11606       && !(sym->attr.allocatable || sym->attr.dummy || sym->attr.save
11607            || sym->ns->proc_name->attr.flavor == FL_MODULE
11608            || sym->ns->proc_name->attr.is_main_program
11609            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
11610     gfc_error ("Variable '%s' at %L is a coarray or has a coarray "
11611                "component and is not ALLOCATABLE, SAVE nor a "
11612                "dummy argument", sym->name, &sym->declared_at);
11613   /* F2008, C528.  */  /* FIXME: sym->as check due to PR 43412.  */
11614   else if (sym->attr.codimension && !sym->attr.allocatable
11615       && sym->as && sym->as->cotype == AS_DEFERRED)
11616     gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
11617                 "deferred shape", sym->name, &sym->declared_at);
11618   else if (sym->attr.codimension && sym->attr.allocatable
11619       && (sym->as->type != AS_DEFERRED || sym->as->cotype != AS_DEFERRED))
11620     gfc_error ("Allocatable coarray variable '%s' at %L must have "
11621                "deferred shape", sym->name, &sym->declared_at);
11622
11623
11624   /* F2008, C541.  */
11625   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
11626        || (sym->attr.codimension && sym->attr.allocatable))
11627       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
11628     gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
11629                "allocatable coarray or have coarray components",
11630                sym->name, &sym->declared_at);
11631
11632   if (sym->attr.codimension && sym->attr.dummy
11633       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
11634     gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
11635                "procedure '%s'", sym->name, &sym->declared_at,
11636                sym->ns->proc_name->name);
11637
11638   switch (sym->attr.flavor)
11639     {
11640     case FL_VARIABLE:
11641       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
11642         return;
11643       break;
11644
11645     case FL_PROCEDURE:
11646       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
11647         return;
11648       break;
11649
11650     case FL_NAMELIST:
11651       if (resolve_fl_namelist (sym) == FAILURE)
11652         return;
11653       break;
11654
11655     case FL_PARAMETER:
11656       if (resolve_fl_parameter (sym) == FAILURE)
11657         return;
11658       break;
11659
11660     default:
11661       break;
11662     }
11663
11664   /* Resolve array specifier. Check as well some constraints
11665      on COMMON blocks.  */
11666
11667   check_constant = sym->attr.in_common && !sym->attr.pointer;
11668
11669   /* Set the formal_arg_flag so that check_conflict will not throw
11670      an error for host associated variables in the specification
11671      expression for an array_valued function.  */
11672   if (sym->attr.function && sym->as)
11673     formal_arg_flag = 1;
11674
11675   gfc_resolve_array_spec (sym->as, check_constant);
11676
11677   formal_arg_flag = 0;
11678
11679   /* Resolve formal namespaces.  */
11680   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
11681       && !sym->attr.contained && !sym->attr.intrinsic)
11682     gfc_resolve (sym->formal_ns);
11683
11684   /* Make sure the formal namespace is present.  */
11685   if (sym->formal && !sym->formal_ns)
11686     {
11687       gfc_formal_arglist *formal = sym->formal;
11688       while (formal && !formal->sym)
11689         formal = formal->next;
11690
11691       if (formal)
11692         {
11693           sym->formal_ns = formal->sym->ns;
11694           sym->formal_ns->refs++;
11695         }
11696     }
11697
11698   /* Check threadprivate restrictions.  */
11699   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
11700       && (!sym->attr.in_common
11701           && sym->module == NULL
11702           && (sym->ns->proc_name == NULL
11703               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
11704     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
11705
11706   /* If we have come this far we can apply default-initializers, as
11707      described in 14.7.5, to those variables that have not already
11708      been assigned one.  */
11709   if (sym->ts.type == BT_DERIVED
11710       && sym->attr.referenced
11711       && sym->ns == gfc_current_ns
11712       && !sym->value
11713       && !sym->attr.allocatable
11714       && !sym->attr.alloc_comp)
11715     {
11716       symbol_attribute *a = &sym->attr;
11717
11718       if ((!a->save && !a->dummy && !a->pointer
11719            && !a->in_common && !a->use_assoc
11720            && !(a->function && sym != sym->result))
11721           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
11722         apply_default_init (sym);
11723     }
11724
11725   /* If this symbol has a type-spec, check it.  */
11726   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
11727       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
11728     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
11729           == FAILURE)
11730       return;
11731 }
11732
11733
11734 /************* Resolve DATA statements *************/
11735
11736 static struct
11737 {
11738   gfc_data_value *vnode;
11739   mpz_t left;
11740 }
11741 values;
11742
11743
11744 /* Advance the values structure to point to the next value in the data list.  */
11745
11746 static gfc_try
11747 next_data_value (void)
11748 {
11749   while (mpz_cmp_ui (values.left, 0) == 0)
11750     {
11751
11752       if (values.vnode->next == NULL)
11753         return FAILURE;
11754
11755       values.vnode = values.vnode->next;
11756       mpz_set (values.left, values.vnode->repeat);
11757     }
11758
11759   return SUCCESS;
11760 }
11761
11762
11763 static gfc_try
11764 check_data_variable (gfc_data_variable *var, locus *where)
11765 {
11766   gfc_expr *e;
11767   mpz_t size;
11768   mpz_t offset;
11769   gfc_try t;
11770   ar_type mark = AR_UNKNOWN;
11771   int i;
11772   mpz_t section_index[GFC_MAX_DIMENSIONS];
11773   gfc_ref *ref;
11774   gfc_array_ref *ar;
11775   gfc_symbol *sym;
11776   int has_pointer;
11777
11778   if (gfc_resolve_expr (var->expr) == FAILURE)
11779     return FAILURE;
11780
11781   ar = NULL;
11782   mpz_init_set_si (offset, 0);
11783   e = var->expr;
11784
11785   if (e->expr_type != EXPR_VARIABLE)
11786     gfc_internal_error ("check_data_variable(): Bad expression");
11787
11788   sym = e->symtree->n.sym;
11789
11790   if (sym->ns->is_block_data && !sym->attr.in_common)
11791     {
11792       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
11793                  sym->name, &sym->declared_at);
11794     }
11795
11796   if (e->ref == NULL && sym->as)
11797     {
11798       gfc_error ("DATA array '%s' at %L must be specified in a previous"
11799                  " declaration", sym->name, where);
11800       return FAILURE;
11801     }
11802
11803   has_pointer = sym->attr.pointer;
11804
11805   for (ref = e->ref; ref; ref = ref->next)
11806     {
11807       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
11808         has_pointer = 1;
11809
11810       if (ref->type == REF_ARRAY && ref->u.ar.codimen)
11811         {
11812           gfc_error ("DATA element '%s' at %L cannot have a coindex",
11813                      sym->name, where);
11814           return FAILURE;
11815         }
11816
11817       if (has_pointer
11818             && ref->type == REF_ARRAY
11819             && ref->u.ar.type != AR_FULL)
11820           {
11821             gfc_error ("DATA element '%s' at %L is a pointer and so must "
11822                         "be a full array", sym->name, where);
11823             return FAILURE;
11824           }
11825     }
11826
11827   if (e->rank == 0 || has_pointer)
11828     {
11829       mpz_init_set_ui (size, 1);
11830       ref = NULL;
11831     }
11832   else
11833     {
11834       ref = e->ref;
11835
11836       /* Find the array section reference.  */
11837       for (ref = e->ref; ref; ref = ref->next)
11838         {
11839           if (ref->type != REF_ARRAY)
11840             continue;
11841           if (ref->u.ar.type == AR_ELEMENT)
11842             continue;
11843           break;
11844         }
11845       gcc_assert (ref);
11846
11847       /* Set marks according to the reference pattern.  */
11848       switch (ref->u.ar.type)
11849         {
11850         case AR_FULL:
11851           mark = AR_FULL;
11852           break;
11853
11854         case AR_SECTION:
11855           ar = &ref->u.ar;
11856           /* Get the start position of array section.  */
11857           gfc_get_section_index (ar, section_index, &offset);
11858           mark = AR_SECTION;
11859           break;
11860
11861         default:
11862           gcc_unreachable ();
11863         }
11864
11865       if (gfc_array_size (e, &size) == FAILURE)
11866         {
11867           gfc_error ("Nonconstant array section at %L in DATA statement",
11868                      &e->where);
11869           mpz_clear (offset);
11870           return FAILURE;
11871         }
11872     }
11873
11874   t = SUCCESS;
11875
11876   while (mpz_cmp_ui (size, 0) > 0)
11877     {
11878       if (next_data_value () == FAILURE)
11879         {
11880           gfc_error ("DATA statement at %L has more variables than values",
11881                      where);
11882           t = FAILURE;
11883           break;
11884         }
11885
11886       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
11887       if (t == FAILURE)
11888         break;
11889
11890       /* If we have more than one element left in the repeat count,
11891          and we have more than one element left in the target variable,
11892          then create a range assignment.  */
11893       /* FIXME: Only done for full arrays for now, since array sections
11894          seem tricky.  */
11895       if (mark == AR_FULL && ref && ref->next == NULL
11896           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
11897         {
11898           mpz_t range;
11899
11900           if (mpz_cmp (size, values.left) >= 0)
11901             {
11902               mpz_init_set (range, values.left);
11903               mpz_sub (size, size, values.left);
11904               mpz_set_ui (values.left, 0);
11905             }
11906           else
11907             {
11908               mpz_init_set (range, size);
11909               mpz_sub (values.left, values.left, size);
11910               mpz_set_ui (size, 0);
11911             }
11912
11913           t = gfc_assign_data_value_range (var->expr, values.vnode->expr,
11914                                            offset, range);
11915
11916           mpz_add (offset, offset, range);
11917           mpz_clear (range);
11918
11919           if (t == FAILURE)
11920             break;
11921         }
11922
11923       /* Assign initial value to symbol.  */
11924       else
11925         {
11926           mpz_sub_ui (values.left, values.left, 1);
11927           mpz_sub_ui (size, size, 1);
11928
11929           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
11930           if (t == FAILURE)
11931             break;
11932
11933           if (mark == AR_FULL)
11934             mpz_add_ui (offset, offset, 1);
11935
11936           /* Modify the array section indexes and recalculate the offset
11937              for next element.  */
11938           else if (mark == AR_SECTION)
11939             gfc_advance_section (section_index, ar, &offset);
11940         }
11941     }
11942
11943   if (mark == AR_SECTION)
11944     {
11945       for (i = 0; i < ar->dimen; i++)
11946         mpz_clear (section_index[i]);
11947     }
11948
11949   mpz_clear (size);
11950   mpz_clear (offset);
11951
11952   return t;
11953 }
11954
11955
11956 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
11957
11958 /* Iterate over a list of elements in a DATA statement.  */
11959
11960 static gfc_try
11961 traverse_data_list (gfc_data_variable *var, locus *where)
11962 {
11963   mpz_t trip;
11964   iterator_stack frame;
11965   gfc_expr *e, *start, *end, *step;
11966   gfc_try retval = SUCCESS;
11967
11968   mpz_init (frame.value);
11969   mpz_init (trip);
11970
11971   start = gfc_copy_expr (var->iter.start);
11972   end = gfc_copy_expr (var->iter.end);
11973   step = gfc_copy_expr (var->iter.step);
11974
11975   if (gfc_simplify_expr (start, 1) == FAILURE
11976       || start->expr_type != EXPR_CONSTANT)
11977     {
11978       gfc_error ("start of implied-do loop at %L could not be "
11979                  "simplified to a constant value", &start->where);
11980       retval = FAILURE;
11981       goto cleanup;
11982     }
11983   if (gfc_simplify_expr (end, 1) == FAILURE
11984       || end->expr_type != EXPR_CONSTANT)
11985     {
11986       gfc_error ("end of implied-do loop at %L could not be "
11987                  "simplified to a constant value", &start->where);
11988       retval = FAILURE;
11989       goto cleanup;
11990     }
11991   if (gfc_simplify_expr (step, 1) == FAILURE
11992       || step->expr_type != EXPR_CONSTANT)
11993     {
11994       gfc_error ("step of implied-do loop at %L could not be "
11995                  "simplified to a constant value", &start->where);
11996       retval = FAILURE;
11997       goto cleanup;
11998     }
11999
12000   mpz_set (trip, end->value.integer);
12001   mpz_sub (trip, trip, start->value.integer);
12002   mpz_add (trip, trip, step->value.integer);
12003
12004   mpz_div (trip, trip, step->value.integer);
12005
12006   mpz_set (frame.value, start->value.integer);
12007
12008   frame.prev = iter_stack;
12009   frame.variable = var->iter.var->symtree;
12010   iter_stack = &frame;
12011
12012   while (mpz_cmp_ui (trip, 0) > 0)
12013     {
12014       if (traverse_data_var (var->list, where) == FAILURE)
12015         {
12016           retval = FAILURE;
12017           goto cleanup;
12018         }
12019
12020       e = gfc_copy_expr (var->expr);
12021       if (gfc_simplify_expr (e, 1) == FAILURE)
12022         {
12023           gfc_free_expr (e);
12024           retval = FAILURE;
12025           goto cleanup;
12026         }
12027
12028       mpz_add (frame.value, frame.value, step->value.integer);
12029
12030       mpz_sub_ui (trip, trip, 1);
12031     }
12032
12033 cleanup:
12034   mpz_clear (frame.value);
12035   mpz_clear (trip);
12036
12037   gfc_free_expr (start);
12038   gfc_free_expr (end);
12039   gfc_free_expr (step);
12040
12041   iter_stack = frame.prev;
12042   return retval;
12043 }
12044
12045
12046 /* Type resolve variables in the variable list of a DATA statement.  */
12047
12048 static gfc_try
12049 traverse_data_var (gfc_data_variable *var, locus *where)
12050 {
12051   gfc_try t;
12052
12053   for (; var; var = var->next)
12054     {
12055       if (var->expr == NULL)
12056         t = traverse_data_list (var, where);
12057       else
12058         t = check_data_variable (var, where);
12059
12060       if (t == FAILURE)
12061         return FAILURE;
12062     }
12063
12064   return SUCCESS;
12065 }
12066
12067
12068 /* Resolve the expressions and iterators associated with a data statement.
12069    This is separate from the assignment checking because data lists should
12070    only be resolved once.  */
12071
12072 static gfc_try
12073 resolve_data_variables (gfc_data_variable *d)
12074 {
12075   for (; d; d = d->next)
12076     {
12077       if (d->list == NULL)
12078         {
12079           if (gfc_resolve_expr (d->expr) == FAILURE)
12080             return FAILURE;
12081         }
12082       else
12083         {
12084           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
12085             return FAILURE;
12086
12087           if (resolve_data_variables (d->list) == FAILURE)
12088             return FAILURE;
12089         }
12090     }
12091
12092   return SUCCESS;
12093 }
12094
12095
12096 /* Resolve a single DATA statement.  We implement this by storing a pointer to
12097    the value list into static variables, and then recursively traversing the
12098    variables list, expanding iterators and such.  */
12099
12100 static void
12101 resolve_data (gfc_data *d)
12102 {
12103
12104   if (resolve_data_variables (d->var) == FAILURE)
12105     return;
12106
12107   values.vnode = d->value;
12108   if (d->value == NULL)
12109     mpz_set_ui (values.left, 0);
12110   else
12111     mpz_set (values.left, d->value->repeat);
12112
12113   if (traverse_data_var (d->var, &d->where) == FAILURE)
12114     return;
12115
12116   /* At this point, we better not have any values left.  */
12117
12118   if (next_data_value () == SUCCESS)
12119     gfc_error ("DATA statement at %L has more values than variables",
12120                &d->where);
12121 }
12122
12123
12124 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
12125    accessed by host or use association, is a dummy argument to a pure function,
12126    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
12127    is storage associated with any such variable, shall not be used in the
12128    following contexts: (clients of this function).  */
12129
12130 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
12131    procedure.  Returns zero if assignment is OK, nonzero if there is a
12132    problem.  */
12133 int
12134 gfc_impure_variable (gfc_symbol *sym)
12135 {
12136   gfc_symbol *proc;
12137   gfc_namespace *ns;
12138
12139   if (sym->attr.use_assoc || sym->attr.in_common)
12140     return 1;
12141
12142   /* Check if the symbol's ns is inside the pure procedure.  */
12143   for (ns = gfc_current_ns; ns; ns = ns->parent)
12144     {
12145       if (ns == sym->ns)
12146         break;
12147       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
12148         return 1;
12149     }
12150
12151   proc = sym->ns->proc_name;
12152   if (sym->attr.dummy && gfc_pure (proc)
12153         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
12154                 ||
12155              proc->attr.function))
12156     return 1;
12157
12158   /* TODO: Sort out what can be storage associated, if anything, and include
12159      it here.  In principle equivalences should be scanned but it does not
12160      seem to be possible to storage associate an impure variable this way.  */
12161   return 0;
12162 }
12163
12164
12165 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
12166    current namespace is inside a pure procedure.  */
12167
12168 int
12169 gfc_pure (gfc_symbol *sym)
12170 {
12171   symbol_attribute attr;
12172   gfc_namespace *ns;
12173
12174   if (sym == NULL)
12175     {
12176       /* Check if the current namespace or one of its parents
12177         belongs to a pure procedure.  */
12178       for (ns = gfc_current_ns; ns; ns = ns->parent)
12179         {
12180           sym = ns->proc_name;
12181           if (sym == NULL)
12182             return 0;
12183           attr = sym->attr;
12184           if (attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental))
12185             return 1;
12186         }
12187       return 0;
12188     }
12189
12190   attr = sym->attr;
12191
12192   return attr.flavor == FL_PROCEDURE && (attr.pure || attr.elemental);
12193 }
12194
12195
12196 /* Test whether the current procedure is elemental or not.  */
12197
12198 int
12199 gfc_elemental (gfc_symbol *sym)
12200 {
12201   symbol_attribute attr;
12202
12203   if (sym == NULL)
12204     sym = gfc_current_ns->proc_name;
12205   if (sym == NULL)
12206     return 0;
12207   attr = sym->attr;
12208
12209   return attr.flavor == FL_PROCEDURE && attr.elemental;
12210 }
12211
12212
12213 /* Warn about unused labels.  */
12214
12215 static void
12216 warn_unused_fortran_label (gfc_st_label *label)
12217 {
12218   if (label == NULL)
12219     return;
12220
12221   warn_unused_fortran_label (label->left);
12222
12223   if (label->defined == ST_LABEL_UNKNOWN)
12224     return;
12225
12226   switch (label->referenced)
12227     {
12228     case ST_LABEL_UNKNOWN:
12229       gfc_warning ("Label %d at %L defined but not used", label->value,
12230                    &label->where);
12231       break;
12232
12233     case ST_LABEL_BAD_TARGET:
12234       gfc_warning ("Label %d at %L defined but cannot be used",
12235                    label->value, &label->where);
12236       break;
12237
12238     default:
12239       break;
12240     }
12241
12242   warn_unused_fortran_label (label->right);
12243 }
12244
12245
12246 /* Returns the sequence type of a symbol or sequence.  */
12247
12248 static seq_type
12249 sequence_type (gfc_typespec ts)
12250 {
12251   seq_type result;
12252   gfc_component *c;
12253
12254   switch (ts.type)
12255   {
12256     case BT_DERIVED:
12257
12258       if (ts.u.derived->components == NULL)
12259         return SEQ_NONDEFAULT;
12260
12261       result = sequence_type (ts.u.derived->components->ts);
12262       for (c = ts.u.derived->components->next; c; c = c->next)
12263         if (sequence_type (c->ts) != result)
12264           return SEQ_MIXED;
12265
12266       return result;
12267
12268     case BT_CHARACTER:
12269       if (ts.kind != gfc_default_character_kind)
12270           return SEQ_NONDEFAULT;
12271
12272       return SEQ_CHARACTER;
12273
12274     case BT_INTEGER:
12275       if (ts.kind != gfc_default_integer_kind)
12276           return SEQ_NONDEFAULT;
12277
12278       return SEQ_NUMERIC;
12279
12280     case BT_REAL:
12281       if (!(ts.kind == gfc_default_real_kind
12282             || ts.kind == gfc_default_double_kind))
12283           return SEQ_NONDEFAULT;
12284
12285       return SEQ_NUMERIC;
12286
12287     case BT_COMPLEX:
12288       if (ts.kind != gfc_default_complex_kind)
12289           return SEQ_NONDEFAULT;
12290
12291       return SEQ_NUMERIC;
12292
12293     case BT_LOGICAL:
12294       if (ts.kind != gfc_default_logical_kind)
12295           return SEQ_NONDEFAULT;
12296
12297       return SEQ_NUMERIC;
12298
12299     default:
12300       return SEQ_NONDEFAULT;
12301   }
12302 }
12303
12304
12305 /* Resolve derived type EQUIVALENCE object.  */
12306
12307 static gfc_try
12308 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
12309 {
12310   gfc_component *c = derived->components;
12311
12312   if (!derived)
12313     return SUCCESS;
12314
12315   /* Shall not be an object of nonsequence derived type.  */
12316   if (!derived->attr.sequence)
12317     {
12318       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
12319                  "attribute to be an EQUIVALENCE object", sym->name,
12320                  &e->where);
12321       return FAILURE;
12322     }
12323
12324   /* Shall not have allocatable components.  */
12325   if (derived->attr.alloc_comp)
12326     {
12327       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
12328                  "components to be an EQUIVALENCE object",sym->name,
12329                  &e->where);
12330       return FAILURE;
12331     }
12332
12333   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
12334     {
12335       gfc_error ("Derived type variable '%s' at %L with default "
12336                  "initialization cannot be in EQUIVALENCE with a variable "
12337                  "in COMMON", sym->name, &e->where);
12338       return FAILURE;
12339     }
12340
12341   for (; c ; c = c->next)
12342     {
12343       if (c->ts.type == BT_DERIVED
12344           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
12345         return FAILURE;
12346
12347       /* Shall not be an object of sequence derived type containing a pointer
12348          in the structure.  */
12349       if (c->attr.pointer)
12350         {
12351           gfc_error ("Derived type variable '%s' at %L with pointer "
12352                      "component(s) cannot be an EQUIVALENCE object",
12353                      sym->name, &e->where);
12354           return FAILURE;
12355         }
12356     }
12357   return SUCCESS;
12358 }
12359
12360
12361 /* Resolve equivalence object. 
12362    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
12363    an allocatable array, an object of nonsequence derived type, an object of
12364    sequence derived type containing a pointer at any level of component
12365    selection, an automatic object, a function name, an entry name, a result
12366    name, a named constant, a structure component, or a subobject of any of
12367    the preceding objects.  A substring shall not have length zero.  A
12368    derived type shall not have components with default initialization nor
12369    shall two objects of an equivalence group be initialized.
12370    Either all or none of the objects shall have an protected attribute.
12371    The simple constraints are done in symbol.c(check_conflict) and the rest
12372    are implemented here.  */
12373
12374 static void
12375 resolve_equivalence (gfc_equiv *eq)
12376 {
12377   gfc_symbol *sym;
12378   gfc_symbol *first_sym;
12379   gfc_expr *e;
12380   gfc_ref *r;
12381   locus *last_where = NULL;
12382   seq_type eq_type, last_eq_type;
12383   gfc_typespec *last_ts;
12384   int object, cnt_protected;
12385   const char *msg;
12386
12387   last_ts = &eq->expr->symtree->n.sym->ts;
12388
12389   first_sym = eq->expr->symtree->n.sym;
12390
12391   cnt_protected = 0;
12392
12393   for (object = 1; eq; eq = eq->eq, object++)
12394     {
12395       e = eq->expr;
12396
12397       e->ts = e->symtree->n.sym->ts;
12398       /* match_varspec might not know yet if it is seeing
12399          array reference or substring reference, as it doesn't
12400          know the types.  */
12401       if (e->ref && e->ref->type == REF_ARRAY)
12402         {
12403           gfc_ref *ref = e->ref;
12404           sym = e->symtree->n.sym;
12405
12406           if (sym->attr.dimension)
12407             {
12408               ref->u.ar.as = sym->as;
12409               ref = ref->next;
12410             }
12411
12412           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
12413           if (e->ts.type == BT_CHARACTER
12414               && ref
12415               && ref->type == REF_ARRAY
12416               && ref->u.ar.dimen == 1
12417               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
12418               && ref->u.ar.stride[0] == NULL)
12419             {
12420               gfc_expr *start = ref->u.ar.start[0];
12421               gfc_expr *end = ref->u.ar.end[0];
12422               void *mem = NULL;
12423
12424               /* Optimize away the (:) reference.  */
12425               if (start == NULL && end == NULL)
12426                 {
12427                   if (e->ref == ref)
12428                     e->ref = ref->next;
12429                   else
12430                     e->ref->next = ref->next;
12431                   mem = ref;
12432                 }
12433               else
12434                 {
12435                   ref->type = REF_SUBSTRING;
12436                   if (start == NULL)
12437                     start = gfc_get_int_expr (gfc_default_integer_kind,
12438                                               NULL, 1);
12439                   ref->u.ss.start = start;
12440                   if (end == NULL && e->ts.u.cl)
12441                     end = gfc_copy_expr (e->ts.u.cl->length);
12442                   ref->u.ss.end = end;
12443                   ref->u.ss.length = e->ts.u.cl;
12444                   e->ts.u.cl = NULL;
12445                 }
12446               ref = ref->next;
12447               gfc_free (mem);
12448             }
12449
12450           /* Any further ref is an error.  */
12451           if (ref)
12452             {
12453               gcc_assert (ref->type == REF_ARRAY);
12454               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
12455                          &ref->u.ar.where);
12456               continue;
12457             }
12458         }
12459
12460       if (gfc_resolve_expr (e) == FAILURE)
12461         continue;
12462
12463       sym = e->symtree->n.sym;
12464
12465       if (sym->attr.is_protected)
12466         cnt_protected++;
12467       if (cnt_protected > 0 && cnt_protected != object)
12468         {
12469               gfc_error ("Either all or none of the objects in the "
12470                          "EQUIVALENCE set at %L shall have the "
12471                          "PROTECTED attribute",
12472                          &e->where);
12473               break;
12474         }
12475
12476       /* Shall not equivalence common block variables in a PURE procedure.  */
12477       if (sym->ns->proc_name
12478           && sym->ns->proc_name->attr.pure
12479           && sym->attr.in_common)
12480         {
12481           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
12482                      "object in the pure procedure '%s'",
12483                      sym->name, &e->where, sym->ns->proc_name->name);
12484           break;
12485         }
12486
12487       /* Shall not be a named constant.  */
12488       if (e->expr_type == EXPR_CONSTANT)
12489         {
12490           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
12491                      "object", sym->name, &e->where);
12492           continue;
12493         }
12494
12495       if (e->ts.type == BT_DERIVED
12496           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
12497         continue;
12498
12499       /* Check that the types correspond correctly:
12500          Note 5.28:
12501          A numeric sequence structure may be equivalenced to another sequence
12502          structure, an object of default integer type, default real type, double
12503          precision real type, default logical type such that components of the
12504          structure ultimately only become associated to objects of the same
12505          kind. A character sequence structure may be equivalenced to an object
12506          of default character kind or another character sequence structure.
12507          Other objects may be equivalenced only to objects of the same type and
12508          kind parameters.  */
12509
12510       /* Identical types are unconditionally OK.  */
12511       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
12512         goto identical_types;
12513
12514       last_eq_type = sequence_type (*last_ts);
12515       eq_type = sequence_type (sym->ts);
12516
12517       /* Since the pair of objects is not of the same type, mixed or
12518          non-default sequences can be rejected.  */
12519
12520       msg = "Sequence %s with mixed components in EQUIVALENCE "
12521             "statement at %L with different type objects";
12522       if ((object ==2
12523            && last_eq_type == SEQ_MIXED
12524            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
12525               == FAILURE)
12526           || (eq_type == SEQ_MIXED
12527               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12528                                  &e->where) == FAILURE))
12529         continue;
12530
12531       msg = "Non-default type object or sequence %s in EQUIVALENCE "
12532             "statement at %L with objects of different type";
12533       if ((object ==2
12534            && last_eq_type == SEQ_NONDEFAULT
12535            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
12536                               last_where) == FAILURE)
12537           || (eq_type == SEQ_NONDEFAULT
12538               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12539                                  &e->where) == FAILURE))
12540         continue;
12541
12542       msg ="Non-CHARACTER object '%s' in default CHARACTER "
12543            "EQUIVALENCE statement at %L";
12544       if (last_eq_type == SEQ_CHARACTER
12545           && eq_type != SEQ_CHARACTER
12546           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12547                              &e->where) == FAILURE)
12548                 continue;
12549
12550       msg ="Non-NUMERIC object '%s' in default NUMERIC "
12551            "EQUIVALENCE statement at %L";
12552       if (last_eq_type == SEQ_NUMERIC
12553           && eq_type != SEQ_NUMERIC
12554           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
12555                              &e->where) == FAILURE)
12556                 continue;
12557
12558   identical_types:
12559       last_ts =&sym->ts;
12560       last_where = &e->where;
12561
12562       if (!e->ref)
12563         continue;
12564
12565       /* Shall not be an automatic array.  */
12566       if (e->ref->type == REF_ARRAY
12567           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
12568         {
12569           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
12570                      "an EQUIVALENCE object", sym->name, &e->where);
12571           continue;
12572         }
12573
12574       r = e->ref;
12575       while (r)
12576         {
12577           /* Shall not be a structure component.  */
12578           if (r->type == REF_COMPONENT)
12579             {
12580               gfc_error ("Structure component '%s' at %L cannot be an "
12581                          "EQUIVALENCE object",
12582                          r->u.c.component->name, &e->where);
12583               break;
12584             }
12585
12586           /* A substring shall not have length zero.  */
12587           if (r->type == REF_SUBSTRING)
12588             {
12589               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
12590                 {
12591                   gfc_error ("Substring at %L has length zero",
12592                              &r->u.ss.start->where);
12593                   break;
12594                 }
12595             }
12596           r = r->next;
12597         }
12598     }
12599 }
12600
12601
12602 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
12603
12604 static void
12605 resolve_fntype (gfc_namespace *ns)
12606 {
12607   gfc_entry_list *el;
12608   gfc_symbol *sym;
12609
12610   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
12611     return;
12612
12613   /* If there are any entries, ns->proc_name is the entry master
12614      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
12615   if (ns->entries)
12616     sym = ns->entries->sym;
12617   else
12618     sym = ns->proc_name;
12619   if (sym->result == sym
12620       && sym->ts.type == BT_UNKNOWN
12621       && gfc_set_default_type (sym, 0, NULL) == FAILURE
12622       && !sym->attr.untyped)
12623     {
12624       gfc_error ("Function '%s' at %L has no IMPLICIT type",
12625                  sym->name, &sym->declared_at);
12626       sym->attr.untyped = 1;
12627     }
12628
12629   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
12630       && !sym->attr.contained
12631       && !gfc_check_access (sym->ts.u.derived->attr.access,
12632                             sym->ts.u.derived->ns->default_access)
12633       && gfc_check_access (sym->attr.access, sym->ns->default_access))
12634     {
12635       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
12636                       "%L of PRIVATE type '%s'", sym->name,
12637                       &sym->declared_at, sym->ts.u.derived->name);
12638     }
12639
12640     if (ns->entries)
12641     for (el = ns->entries->next; el; el = el->next)
12642       {
12643         if (el->sym->result == el->sym
12644             && el->sym->ts.type == BT_UNKNOWN
12645             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
12646             && !el->sym->attr.untyped)
12647           {
12648             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
12649                        el->sym->name, &el->sym->declared_at);
12650             el->sym->attr.untyped = 1;
12651           }
12652       }
12653 }
12654
12655
12656 /* 12.3.2.1.1 Defined operators.  */
12657
12658 static gfc_try
12659 check_uop_procedure (gfc_symbol *sym, locus where)
12660 {
12661   gfc_formal_arglist *formal;
12662
12663   if (!sym->attr.function)
12664     {
12665       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
12666                  sym->name, &where);
12667       return FAILURE;
12668     }
12669
12670   if (sym->ts.type == BT_CHARACTER
12671       && !(sym->ts.u.cl && sym->ts.u.cl->length)
12672       && !(sym->result && sym->result->ts.u.cl
12673            && sym->result->ts.u.cl->length))
12674     {
12675       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
12676                  "character length", sym->name, &where);
12677       return FAILURE;
12678     }
12679
12680   formal = sym->formal;
12681   if (!formal || !formal->sym)
12682     {
12683       gfc_error ("User operator procedure '%s' at %L must have at least "
12684                  "one argument", sym->name, &where);
12685       return FAILURE;
12686     }
12687
12688   if (formal->sym->attr.intent != INTENT_IN)
12689     {
12690       gfc_error ("First argument of operator interface at %L must be "
12691                  "INTENT(IN)", &where);
12692       return FAILURE;
12693     }
12694
12695   if (formal->sym->attr.optional)
12696     {
12697       gfc_error ("First argument of operator interface at %L cannot be "
12698                  "optional", &where);
12699       return FAILURE;
12700     }
12701
12702   formal = formal->next;
12703   if (!formal || !formal->sym)
12704     return SUCCESS;
12705
12706   if (formal->sym->attr.intent != INTENT_IN)
12707     {
12708       gfc_error ("Second argument of operator interface at %L must be "
12709                  "INTENT(IN)", &where);
12710       return FAILURE;
12711     }
12712
12713   if (formal->sym->attr.optional)
12714     {
12715       gfc_error ("Second argument of operator interface at %L cannot be "
12716                  "optional", &where);
12717       return FAILURE;
12718     }
12719
12720   if (formal->next)
12721     {
12722       gfc_error ("Operator interface at %L must have, at most, two "
12723                  "arguments", &where);
12724       return FAILURE;
12725     }
12726
12727   return SUCCESS;
12728 }
12729
12730 static void
12731 gfc_resolve_uops (gfc_symtree *symtree)
12732 {
12733   gfc_interface *itr;
12734
12735   if (symtree == NULL)
12736     return;
12737
12738   gfc_resolve_uops (symtree->left);
12739   gfc_resolve_uops (symtree->right);
12740
12741   for (itr = symtree->n.uop->op; itr; itr = itr->next)
12742     check_uop_procedure (itr->sym, itr->sym->declared_at);
12743 }
12744
12745
12746 /* Examine all of the expressions associated with a program unit,
12747    assign types to all intermediate expressions, make sure that all
12748    assignments are to compatible types and figure out which names
12749    refer to which functions or subroutines.  It doesn't check code
12750    block, which is handled by resolve_code.  */
12751
12752 static void
12753 resolve_types (gfc_namespace *ns)
12754 {
12755   gfc_namespace *n;
12756   gfc_charlen *cl;
12757   gfc_data *d;
12758   gfc_equiv *eq;
12759   gfc_namespace* old_ns = gfc_current_ns;
12760
12761   /* Check that all IMPLICIT types are ok.  */
12762   if (!ns->seen_implicit_none)
12763     {
12764       unsigned letter;
12765       for (letter = 0; letter != GFC_LETTERS; ++letter)
12766         if (ns->set_flag[letter]
12767             && resolve_typespec_used (&ns->default_type[letter],
12768                                       &ns->implicit_loc[letter],
12769                                       NULL) == FAILURE)
12770           return;
12771     }
12772
12773   gfc_current_ns = ns;
12774
12775   resolve_entries (ns);
12776
12777   resolve_common_vars (ns->blank_common.head, false);
12778   resolve_common_blocks (ns->common_root);
12779
12780   resolve_contained_functions (ns);
12781
12782   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
12783
12784   for (cl = ns->cl_list; cl; cl = cl->next)
12785     resolve_charlen (cl);
12786
12787   gfc_traverse_ns (ns, resolve_symbol);
12788
12789   resolve_fntype (ns);
12790
12791   for (n = ns->contained; n; n = n->sibling)
12792     {
12793       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
12794         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
12795                    "also be PURE", n->proc_name->name,
12796                    &n->proc_name->declared_at);
12797
12798       resolve_types (n);
12799     }
12800
12801   forall_flag = 0;
12802   gfc_check_interfaces (ns);
12803
12804   gfc_traverse_ns (ns, resolve_values);
12805
12806   if (ns->save_all)
12807     gfc_save_all (ns);
12808
12809   iter_stack = NULL;
12810   for (d = ns->data; d; d = d->next)
12811     resolve_data (d);
12812
12813   iter_stack = NULL;
12814   gfc_traverse_ns (ns, gfc_formalize_init_value);
12815
12816   gfc_traverse_ns (ns, gfc_verify_binding_labels);
12817
12818   if (ns->common_root != NULL)
12819     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
12820
12821   for (eq = ns->equiv; eq; eq = eq->next)
12822     resolve_equivalence (eq);
12823
12824   /* Warn about unused labels.  */
12825   if (warn_unused_label)
12826     warn_unused_fortran_label (ns->st_labels);
12827
12828   gfc_resolve_uops (ns->uop_root);
12829
12830   gfc_current_ns = old_ns;
12831 }
12832
12833
12834 /* Call resolve_code recursively.  */
12835
12836 static void
12837 resolve_codes (gfc_namespace *ns)
12838 {
12839   gfc_namespace *n;
12840   bitmap_obstack old_obstack;
12841
12842   for (n = ns->contained; n; n = n->sibling)
12843     resolve_codes (n);
12844
12845   gfc_current_ns = ns;
12846
12847   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
12848   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
12849     cs_base = NULL;
12850
12851   /* Set to an out of range value.  */
12852   current_entry_id = -1;
12853
12854   old_obstack = labels_obstack;
12855   bitmap_obstack_initialize (&labels_obstack);
12856
12857   resolve_code (ns->code, ns);
12858
12859   bitmap_obstack_release (&labels_obstack);
12860   labels_obstack = old_obstack;
12861 }
12862
12863
12864 /* This function is called after a complete program unit has been compiled.
12865    Its purpose is to examine all of the expressions associated with a program
12866    unit, assign types to all intermediate expressions, make sure that all
12867    assignments are to compatible types and figure out which names refer to
12868    which functions or subroutines.  */
12869
12870 void
12871 gfc_resolve (gfc_namespace *ns)
12872 {
12873   gfc_namespace *old_ns;
12874   code_stack *old_cs_base;
12875
12876   if (ns->resolved)
12877     return;
12878
12879   ns->resolved = -1;
12880   old_ns = gfc_current_ns;
12881   old_cs_base = cs_base;
12882
12883   resolve_types (ns);
12884   resolve_codes (ns);
12885
12886   gfc_current_ns = old_ns;
12887   cs_base = old_cs_base;
12888   ns->resolved = 1;
12889 }