OSDN Git Service

2012-01-10 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009,
3    2010, 2011, 2012
4    Free Software Foundation, Inc.
5    Contributed by Andy Vaught
6
7 This file is part of GCC.
8
9 GCC is free software; you can redistribute it and/or modify it under
10 the terms of the GNU General Public License as published by the Free
11 Software Foundation; either version 3, or (at your option) any later
12 version.
13
14 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15 WARRANTY; without even the implied warranty of MERCHANTABILITY or
16 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
17 for more details.
18
19 You should have received a copy of the GNU General Public License
20 along with GCC; see the file COPYING3.  If not see
21 <http://www.gnu.org/licenses/>.  */
22
23 #include "config.h"
24 #include "system.h"
25 #include "flags.h"
26 #include "gfortran.h"
27 #include "obstack.h"
28 #include "bitmap.h"
29 #include "arith.h"  /* For gfc_compare_expr().  */
30 #include "dependency.h"
31 #include "data.h"
32 #include "target-memory.h" /* for gfc_simplify_transfer */
33 #include "constructor.h"
34
35 /* Types used in equivalence statements.  */
36
37 typedef enum seq_type
38 {
39   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
40 }
41 seq_type;
42
43 /* Stack to keep track of the nesting of blocks as we move through the
44    code.  See resolve_branch() and resolve_code().  */
45
46 typedef struct code_stack
47 {
48   struct gfc_code *head, *current;
49   struct code_stack *prev;
50
51   /* This bitmap keeps track of the targets valid for a branch from
52      inside this block except for END {IF|SELECT}s of enclosing
53      blocks.  */
54   bitmap reachable_labels;
55 }
56 code_stack;
57
58 static code_stack *cs_base = NULL;
59
60
61 /* Nonzero if we're inside a FORALL or DO CONCURRENT block.  */
62
63 static int forall_flag;
64 static int do_concurrent_flag;
65
66 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
67
68 static int omp_workshare_flag;
69
70 /* Nonzero if we are processing a formal arglist. The corresponding function
71    resets the flag each time that it is read.  */
72 static int formal_arg_flag = 0;
73
74 /* True if we are resolving a specification expression.  */
75 static int specification_expr = 0;
76
77 /* The id of the last entry seen.  */
78 static int current_entry_id;
79
80 /* We use bitmaps to determine if a branch target is valid.  */
81 static bitmap_obstack labels_obstack;
82
83 /* True when simplifying a EXPR_VARIABLE argument to an inquiry function.  */
84 static bool inquiry_argument = false;
85
86 int
87 gfc_is_formal_arg (void)
88 {
89   return formal_arg_flag;
90 }
91
92 /* Is the symbol host associated?  */
93 static bool
94 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
95 {
96   for (ns = ns->parent; ns; ns = ns->parent)
97     {      
98       if (sym->ns == ns)
99         return true;
100     }
101
102   return false;
103 }
104
105 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
106    an ABSTRACT derived-type.  If where is not NULL, an error message with that
107    locus is printed, optionally using name.  */
108
109 static gfc_try
110 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
111 {
112   if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
113     {
114       if (where)
115         {
116           if (name)
117             gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
118                        name, where, ts->u.derived->name);
119           else
120             gfc_error ("ABSTRACT type '%s' used at %L",
121                        ts->u.derived->name, where);
122         }
123
124       return FAILURE;
125     }
126
127   return SUCCESS;
128 }
129
130
131 static void resolve_symbol (gfc_symbol *sym);
132 static gfc_try resolve_intrinsic (gfc_symbol *sym, locus *loc);
133
134
135 /* Resolve the interface for a PROCEDURE declaration or procedure pointer.  */
136
137 static gfc_try
138 resolve_procedure_interface (gfc_symbol *sym)
139 {
140   if (sym->ts.interface == sym)
141     {
142       gfc_error ("PROCEDURE '%s' at %L may not be used as its own interface",
143                  sym->name, &sym->declared_at);
144       return FAILURE;
145     }
146   if (sym->ts.interface->attr.procedure)
147     {
148       gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared "
149                  "in a later PROCEDURE statement", sym->ts.interface->name,
150                  sym->name, &sym->declared_at);
151       return FAILURE;
152     }
153
154   /* Get the attributes from the interface (now resolved).  */
155   if (sym->ts.interface->attr.if_source || sym->ts.interface->attr.intrinsic)
156     {
157       gfc_symbol *ifc = sym->ts.interface;
158       resolve_symbol (ifc);
159
160       if (ifc->attr.intrinsic)
161         resolve_intrinsic (ifc, &ifc->declared_at);
162
163       if (ifc->result)
164         {
165           sym->ts = ifc->result->ts;
166           sym->result = sym;
167         }
168       else   
169         sym->ts = ifc->ts;
170       sym->ts.interface = ifc;
171       sym->attr.function = ifc->attr.function;
172       sym->attr.subroutine = ifc->attr.subroutine;
173       gfc_copy_formal_args (sym, ifc);
174
175       sym->attr.allocatable = ifc->attr.allocatable;
176       sym->attr.pointer = ifc->attr.pointer;
177       sym->attr.pure = ifc->attr.pure;
178       sym->attr.elemental = ifc->attr.elemental;
179       sym->attr.dimension = ifc->attr.dimension;
180       sym->attr.contiguous = ifc->attr.contiguous;
181       sym->attr.recursive = ifc->attr.recursive;
182       sym->attr.always_explicit = ifc->attr.always_explicit;
183       sym->attr.ext_attr |= ifc->attr.ext_attr;
184       sym->attr.is_bind_c = ifc->attr.is_bind_c;
185       /* Copy array spec.  */
186       sym->as = gfc_copy_array_spec (ifc->as);
187       if (sym->as)
188         {
189           int i;
190           for (i = 0; i < sym->as->rank; i++)
191             {
192               gfc_expr_replace_symbols (sym->as->lower[i], sym);
193               gfc_expr_replace_symbols (sym->as->upper[i], sym);
194             }
195         }
196       /* Copy char length.  */
197       if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
198         {
199           sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
200           gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
201           if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
202               && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
203             return FAILURE;
204         }
205     }
206   else if (sym->ts.interface->name[0] != '\0')
207     {
208       gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
209                  sym->ts.interface->name, sym->name, &sym->declared_at);
210       return FAILURE;
211     }
212
213   return SUCCESS;
214 }
215
216
217 /* Resolve types of formal argument lists.  These have to be done early so that
218    the formal argument lists of module procedures can be copied to the
219    containing module before the individual procedures are resolved
220    individually.  We also resolve argument lists of procedures in interface
221    blocks because they are self-contained scoping units.
222
223    Since a dummy argument cannot be a non-dummy procedure, the only
224    resort left for untyped names are the IMPLICIT types.  */
225
226 static void
227 resolve_formal_arglist (gfc_symbol *proc)
228 {
229   gfc_formal_arglist *f;
230   gfc_symbol *sym;
231   int i;
232
233   if (proc->result != NULL)
234     sym = proc->result;
235   else
236     sym = proc;
237
238   if (gfc_elemental (proc)
239       || sym->attr.pointer || sym->attr.allocatable
240       || (sym->as && sym->as->rank > 0))
241     {
242       proc->attr.always_explicit = 1;
243       sym->attr.always_explicit = 1;
244     }
245
246   formal_arg_flag = 1;
247
248   for (f = proc->formal; f; f = f->next)
249     {
250       sym = f->sym;
251
252       if (sym == NULL)
253         {
254           /* Alternate return placeholder.  */
255           if (gfc_elemental (proc))
256             gfc_error ("Alternate return specifier in elemental subroutine "
257                        "'%s' at %L is not allowed", proc->name,
258                        &proc->declared_at);
259           if (proc->attr.function)
260             gfc_error ("Alternate return specifier in function "
261                        "'%s' at %L is not allowed", proc->name,
262                        &proc->declared_at);
263           continue;
264         }
265       else if (sym->attr.procedure && sym->ts.interface
266                && sym->attr.if_source != IFSRC_DECL)
267         resolve_procedure_interface (sym);
268
269       if (sym->attr.if_source != IFSRC_UNKNOWN)
270         resolve_formal_arglist (sym);
271
272       if (sym->attr.subroutine || sym->attr.external)
273         {
274           if (sym->attr.flavor == FL_UNKNOWN)
275             gfc_add_flavor (&sym->attr, FL_PROCEDURE, sym->name, &sym->declared_at);
276         }
277       else
278         {
279           if (sym->ts.type == BT_UNKNOWN && !proc->attr.intrinsic
280               && (!sym->attr.function || sym->result == sym))
281             gfc_set_default_type (sym, 1, sym->ns);
282         }
283
284       gfc_resolve_array_spec (sym->as, 0);
285
286       /* We can't tell if an array with dimension (:) is assumed or deferred
287          shape until we know if it has the pointer or allocatable attributes.
288       */
289       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
290           && !(sym->attr.pointer || sym->attr.allocatable)
291           && sym->attr.flavor != FL_PROCEDURE)
292         {
293           sym->as->type = AS_ASSUMED_SHAPE;
294           for (i = 0; i < sym->as->rank; i++)
295             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
296                                                   NULL, 1);
297         }
298
299       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
300           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
301           || sym->attr.optional)
302         {
303           proc->attr.always_explicit = 1;
304           if (proc->result)
305             proc->result->attr.always_explicit = 1;
306         }
307
308       /* If the flavor is unknown at this point, it has to be a variable.
309          A procedure specification would have already set the type.  */
310
311       if (sym->attr.flavor == FL_UNKNOWN)
312         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
313
314       if (gfc_pure (proc))
315         {
316           if (sym->attr.flavor == FL_PROCEDURE)
317             {
318               /* F08:C1279.  */
319               if (!gfc_pure (sym))
320                 {
321                   gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
322                             "also be PURE", sym->name, &sym->declared_at);
323                   continue;
324                 }
325             }
326           else if (!sym->attr.pointer)
327             {
328               if (proc->attr.function && sym->attr.intent != INTENT_IN)
329                 {
330                   if (sym->attr.value)
331                     gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s'"
332                                     " of pure function '%s' at %L with VALUE "
333                                     "attribute but without INTENT(IN)",
334                                     sym->name, proc->name, &sym->declared_at);
335                   else
336                     gfc_error ("Argument '%s' of pure function '%s' at %L must "
337                                "be INTENT(IN) or VALUE", sym->name, proc->name,
338                                &sym->declared_at);
339                 }
340
341               if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
342                 {
343                   if (sym->attr.value)
344                     gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s'"
345                                     " of pure subroutine '%s' at %L with VALUE "
346                                     "attribute but without INTENT", sym->name,
347                                     proc->name, &sym->declared_at);
348                   else
349                     gfc_error ("Argument '%s' of pure subroutine '%s' at %L "
350                                "must have its INTENT specified or have the "
351                                "VALUE attribute", sym->name, proc->name,
352                                &sym->declared_at);
353                 }
354             }
355         }
356
357       if (proc->attr.implicit_pure)
358         {
359           if (sym->attr.flavor == FL_PROCEDURE)
360             {
361               if (!gfc_pure(sym))
362                 proc->attr.implicit_pure = 0;
363             }
364           else if (!sym->attr.pointer)
365             {
366               if (proc->attr.function && sym->attr.intent != INTENT_IN)
367                 proc->attr.implicit_pure = 0;
368
369               if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
370                 proc->attr.implicit_pure = 0;
371             }
372         }
373
374       if (gfc_elemental (proc))
375         {
376           /* F08:C1289.  */
377           if (sym->attr.codimension)
378             {
379               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
380                          "procedure", sym->name, &sym->declared_at);
381               continue;
382             }
383
384           if (sym->as != NULL)
385             {
386               gfc_error ("Argument '%s' of elemental procedure at %L must "
387                          "be scalar", sym->name, &sym->declared_at);
388               continue;
389             }
390
391           if (sym->attr.allocatable)
392             {
393               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
394                          "have the ALLOCATABLE attribute", sym->name,
395                          &sym->declared_at);
396               continue;
397             }
398
399           if (sym->attr.pointer)
400             {
401               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
402                          "have the POINTER attribute", sym->name,
403                          &sym->declared_at);
404               continue;
405             }
406
407           if (sym->attr.flavor == FL_PROCEDURE)
408             {
409               gfc_error ("Dummy procedure '%s' not allowed in elemental "
410                          "procedure '%s' at %L", sym->name, proc->name,
411                          &sym->declared_at);
412               continue;
413             }
414
415           if (sym->attr.intent == INTENT_UNKNOWN)
416             {
417               gfc_error ("Argument '%s' of elemental procedure '%s' at %L must "
418                          "have its INTENT specified", sym->name, proc->name,
419                          &sym->declared_at);
420               continue;
421             }
422         }
423
424       /* Each dummy shall be specified to be scalar.  */
425       if (proc->attr.proc == PROC_ST_FUNCTION)
426         {
427           if (sym->as != NULL)
428             {
429               gfc_error ("Argument '%s' of statement function at %L must "
430                          "be scalar", sym->name, &sym->declared_at);
431               continue;
432             }
433
434           if (sym->ts.type == BT_CHARACTER)
435             {
436               gfc_charlen *cl = sym->ts.u.cl;
437               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
438                 {
439                   gfc_error ("Character-valued argument '%s' of statement "
440                              "function at %L must have constant length",
441                              sym->name, &sym->declared_at);
442                   continue;
443                 }
444             }
445         }
446     }
447   formal_arg_flag = 0;
448 }
449
450
451 /* Work function called when searching for symbols that have argument lists
452    associated with them.  */
453
454 static void
455 find_arglists (gfc_symbol *sym)
456 {
457   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns
458       || sym->attr.flavor == FL_DERIVED)
459     return;
460
461   resolve_formal_arglist (sym);
462 }
463
464
465 /* Given a namespace, resolve all formal argument lists within the namespace.
466  */
467
468 static void
469 resolve_formal_arglists (gfc_namespace *ns)
470 {
471   if (ns == NULL)
472     return;
473
474   gfc_traverse_ns (ns, find_arglists);
475 }
476
477
478 static void
479 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
480 {
481   gfc_try t;
482
483   /* If this namespace is not a function or an entry master function,
484      ignore it.  */
485   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
486       || sym->attr.entry_master)
487     return;
488
489   /* Try to find out of what the return type is.  */
490   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
491     {
492       t = gfc_set_default_type (sym->result, 0, ns);
493
494       if (t == FAILURE && !sym->result->attr.untyped)
495         {
496           if (sym->result == sym)
497             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
498                        sym->name, &sym->declared_at);
499           else if (!sym->result->attr.proc_pointer)
500             gfc_error ("Result '%s' of contained function '%s' at %L has "
501                        "no IMPLICIT type", sym->result->name, sym->name,
502                        &sym->result->declared_at);
503           sym->result->attr.untyped = 1;
504         }
505     }
506
507   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
508      type, lists the only ways a character length value of * can be used:
509      dummy arguments of procedures, named constants, and function results
510      in external functions.  Internal function results and results of module
511      procedures are not on this list, ergo, not permitted.  */
512
513   if (sym->result->ts.type == BT_CHARACTER)
514     {
515       gfc_charlen *cl = sym->result->ts.u.cl;
516       if ((!cl || !cl->length) && !sym->result->ts.deferred)
517         {
518           /* See if this is a module-procedure and adapt error message
519              accordingly.  */
520           bool module_proc;
521           gcc_assert (ns->parent && ns->parent->proc_name);
522           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
523
524           gfc_error ("Character-valued %s '%s' at %L must not be"
525                      " assumed length",
526                      module_proc ? _("module procedure")
527                                  : _("internal function"),
528                      sym->name, &sym->declared_at);
529         }
530     }
531 }
532
533
534 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
535    introduce duplicates.  */
536
537 static void
538 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
539 {
540   gfc_formal_arglist *f, *new_arglist;
541   gfc_symbol *new_sym;
542
543   for (; new_args != NULL; new_args = new_args->next)
544     {
545       new_sym = new_args->sym;
546       /* See if this arg is already in the formal argument list.  */
547       for (f = proc->formal; f; f = f->next)
548         {
549           if (new_sym == f->sym)
550             break;
551         }
552
553       if (f)
554         continue;
555
556       /* Add a new argument.  Argument order is not important.  */
557       new_arglist = gfc_get_formal_arglist ();
558       new_arglist->sym = new_sym;
559       new_arglist->next = proc->formal;
560       proc->formal  = new_arglist;
561     }
562 }
563
564
565 /* Flag the arguments that are not present in all entries.  */
566
567 static void
568 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
569 {
570   gfc_formal_arglist *f, *head;
571   head = new_args;
572
573   for (f = proc->formal; f; f = f->next)
574     {
575       if (f->sym == NULL)
576         continue;
577
578       for (new_args = head; new_args; new_args = new_args->next)
579         {
580           if (new_args->sym == f->sym)
581             break;
582         }
583
584       if (new_args)
585         continue;
586
587       f->sym->attr.not_always_present = 1;
588     }
589 }
590
591
592 /* Resolve alternate entry points.  If a symbol has multiple entry points we
593    create a new master symbol for the main routine, and turn the existing
594    symbol into an entry point.  */
595
596 static void
597 resolve_entries (gfc_namespace *ns)
598 {
599   gfc_namespace *old_ns;
600   gfc_code *c;
601   gfc_symbol *proc;
602   gfc_entry_list *el;
603   char name[GFC_MAX_SYMBOL_LEN + 1];
604   static int master_count = 0;
605
606   if (ns->proc_name == NULL)
607     return;
608
609   /* No need to do anything if this procedure doesn't have alternate entry
610      points.  */
611   if (!ns->entries)
612     return;
613
614   /* We may already have resolved alternate entry points.  */
615   if (ns->proc_name->attr.entry_master)
616     return;
617
618   /* If this isn't a procedure something has gone horribly wrong.  */
619   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
620
621   /* Remember the current namespace.  */
622   old_ns = gfc_current_ns;
623
624   gfc_current_ns = ns;
625
626   /* Add the main entry point to the list of entry points.  */
627   el = gfc_get_entry_list ();
628   el->sym = ns->proc_name;
629   el->id = 0;
630   el->next = ns->entries;
631   ns->entries = el;
632   ns->proc_name->attr.entry = 1;
633
634   /* If it is a module function, it needs to be in the right namespace
635      so that gfc_get_fake_result_decl can gather up the results. The
636      need for this arose in get_proc_name, where these beasts were
637      left in their own namespace, to keep prior references linked to
638      the entry declaration.*/
639   if (ns->proc_name->attr.function
640       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
641     el->sym->ns = ns;
642
643   /* Do the same for entries where the master is not a module
644      procedure.  These are retained in the module namespace because
645      of the module procedure declaration.  */
646   for (el = el->next; el; el = el->next)
647     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
648           && el->sym->attr.mod_proc)
649       el->sym->ns = ns;
650   el = ns->entries;
651
652   /* Add an entry statement for it.  */
653   c = gfc_get_code ();
654   c->op = EXEC_ENTRY;
655   c->ext.entry = el;
656   c->next = ns->code;
657   ns->code = c;
658
659   /* Create a new symbol for the master function.  */
660   /* Give the internal function a unique name (within this file).
661      Also include the function name so the user has some hope of figuring
662      out what is going on.  */
663   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
664             master_count++, ns->proc_name->name);
665   gfc_get_ha_symbol (name, &proc);
666   gcc_assert (proc != NULL);
667
668   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
669   if (ns->proc_name->attr.subroutine)
670     gfc_add_subroutine (&proc->attr, proc->name, NULL);
671   else
672     {
673       gfc_symbol *sym;
674       gfc_typespec *ts, *fts;
675       gfc_array_spec *as, *fas;
676       gfc_add_function (&proc->attr, proc->name, NULL);
677       proc->result = proc;
678       fas = ns->entries->sym->as;
679       fas = fas ? fas : ns->entries->sym->result->as;
680       fts = &ns->entries->sym->result->ts;
681       if (fts->type == BT_UNKNOWN)
682         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
683       for (el = ns->entries->next; el; el = el->next)
684         {
685           ts = &el->sym->result->ts;
686           as = el->sym->as;
687           as = as ? as : el->sym->result->as;
688           if (ts->type == BT_UNKNOWN)
689             ts = gfc_get_default_type (el->sym->result->name, NULL);
690
691           if (! gfc_compare_types (ts, fts)
692               || (el->sym->result->attr.dimension
693                   != ns->entries->sym->result->attr.dimension)
694               || (el->sym->result->attr.pointer
695                   != ns->entries->sym->result->attr.pointer))
696             break;
697           else if (as && fas && ns->entries->sym->result != el->sym->result
698                       && gfc_compare_array_spec (as, fas) == 0)
699             gfc_error ("Function %s at %L has entries with mismatched "
700                        "array specifications", ns->entries->sym->name,
701                        &ns->entries->sym->declared_at);
702           /* The characteristics need to match and thus both need to have
703              the same string length, i.e. both len=*, or both len=4.
704              Having both len=<variable> is also possible, but difficult to
705              check at compile time.  */
706           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
707                    && (((ts->u.cl->length && !fts->u.cl->length)
708                         ||(!ts->u.cl->length && fts->u.cl->length))
709                        || (ts->u.cl->length
710                            && ts->u.cl->length->expr_type
711                               != fts->u.cl->length->expr_type)
712                        || (ts->u.cl->length
713                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
714                            && mpz_cmp (ts->u.cl->length->value.integer,
715                                        fts->u.cl->length->value.integer) != 0)))
716             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
717                             "entries returning variables of different "
718                             "string lengths", ns->entries->sym->name,
719                             &ns->entries->sym->declared_at);
720         }
721
722       if (el == NULL)
723         {
724           sym = ns->entries->sym->result;
725           /* All result types the same.  */
726           proc->ts = *fts;
727           if (sym->attr.dimension)
728             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
729           if (sym->attr.pointer)
730             gfc_add_pointer (&proc->attr, NULL);
731         }
732       else
733         {
734           /* Otherwise the result will be passed through a union by
735              reference.  */
736           proc->attr.mixed_entry_master = 1;
737           for (el = ns->entries; el; el = el->next)
738             {
739               sym = el->sym->result;
740               if (sym->attr.dimension)
741                 {
742                   if (el == ns->entries)
743                     gfc_error ("FUNCTION result %s can't be an array in "
744                                "FUNCTION %s at %L", sym->name,
745                                ns->entries->sym->name, &sym->declared_at);
746                   else
747                     gfc_error ("ENTRY result %s can't be an array in "
748                                "FUNCTION %s at %L", sym->name,
749                                ns->entries->sym->name, &sym->declared_at);
750                 }
751               else if (sym->attr.pointer)
752                 {
753                   if (el == ns->entries)
754                     gfc_error ("FUNCTION result %s can't be a POINTER in "
755                                "FUNCTION %s at %L", sym->name,
756                                ns->entries->sym->name, &sym->declared_at);
757                   else
758                     gfc_error ("ENTRY result %s can't be a POINTER in "
759                                "FUNCTION %s at %L", sym->name,
760                                ns->entries->sym->name, &sym->declared_at);
761                 }
762               else
763                 {
764                   ts = &sym->ts;
765                   if (ts->type == BT_UNKNOWN)
766                     ts = gfc_get_default_type (sym->name, NULL);
767                   switch (ts->type)
768                     {
769                     case BT_INTEGER:
770                       if (ts->kind == gfc_default_integer_kind)
771                         sym = NULL;
772                       break;
773                     case BT_REAL:
774                       if (ts->kind == gfc_default_real_kind
775                           || ts->kind == gfc_default_double_kind)
776                         sym = NULL;
777                       break;
778                     case BT_COMPLEX:
779                       if (ts->kind == gfc_default_complex_kind)
780                         sym = NULL;
781                       break;
782                     case BT_LOGICAL:
783                       if (ts->kind == gfc_default_logical_kind)
784                         sym = NULL;
785                       break;
786                     case BT_UNKNOWN:
787                       /* We will issue error elsewhere.  */
788                       sym = NULL;
789                       break;
790                     default:
791                       break;
792                     }
793                   if (sym)
794                     {
795                       if (el == ns->entries)
796                         gfc_error ("FUNCTION result %s can't be of type %s "
797                                    "in FUNCTION %s at %L", sym->name,
798                                    gfc_typename (ts), ns->entries->sym->name,
799                                    &sym->declared_at);
800                       else
801                         gfc_error ("ENTRY result %s can't be of type %s "
802                                    "in FUNCTION %s at %L", sym->name,
803                                    gfc_typename (ts), ns->entries->sym->name,
804                                    &sym->declared_at);
805                     }
806                 }
807             }
808         }
809     }
810   proc->attr.access = ACCESS_PRIVATE;
811   proc->attr.entry_master = 1;
812
813   /* Merge all the entry point arguments.  */
814   for (el = ns->entries; el; el = el->next)
815     merge_argument_lists (proc, el->sym->formal);
816
817   /* Check the master formal arguments for any that are not
818      present in all entry points.  */
819   for (el = ns->entries; el; el = el->next)
820     check_argument_lists (proc, el->sym->formal);
821
822   /* Use the master function for the function body.  */
823   ns->proc_name = proc;
824
825   /* Finalize the new symbols.  */
826   gfc_commit_symbols ();
827
828   /* Restore the original namespace.  */
829   gfc_current_ns = old_ns;
830 }
831
832
833 /* Resolve common variables.  */
834 static void
835 resolve_common_vars (gfc_symbol *sym, bool named_common)
836 {
837   gfc_symbol *csym = sym;
838
839   for (; csym; csym = csym->common_next)
840     {
841       if (csym->value || csym->attr.data)
842         {
843           if (!csym->ns->is_block_data)
844             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
845                             "but only in BLOCK DATA initialization is "
846                             "allowed", csym->name, &csym->declared_at);
847           else if (!named_common)
848             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
849                             "in a blank COMMON but initialization is only "
850                             "allowed in named common blocks", csym->name,
851                             &csym->declared_at);
852         }
853
854       if (csym->ts.type != BT_DERIVED)
855         continue;
856
857       if (!(csym->ts.u.derived->attr.sequence
858             || csym->ts.u.derived->attr.is_bind_c))
859         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
860                        "has neither the SEQUENCE nor the BIND(C) "
861                        "attribute", csym->name, &csym->declared_at);
862       if (csym->ts.u.derived->attr.alloc_comp)
863         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
864                        "has an ultimate component that is "
865                        "allocatable", csym->name, &csym->declared_at);
866       if (gfc_has_default_initializer (csym->ts.u.derived))
867         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
868                        "may not have default initializer", csym->name,
869                        &csym->declared_at);
870
871       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
872         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
873     }
874 }
875
876 /* Resolve common blocks.  */
877 static void
878 resolve_common_blocks (gfc_symtree *common_root)
879 {
880   gfc_symbol *sym;
881
882   if (common_root == NULL)
883     return;
884
885   if (common_root->left)
886     resolve_common_blocks (common_root->left);
887   if (common_root->right)
888     resolve_common_blocks (common_root->right);
889
890   resolve_common_vars (common_root->n.common->head, true);
891
892   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
893   if (sym == NULL)
894     return;
895
896   if (sym->attr.flavor == FL_PARAMETER)
897     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
898                sym->name, &common_root->n.common->where, &sym->declared_at);
899
900   if (sym->attr.external)
901     gfc_error ("COMMON block '%s' at %L can not have the EXTERNAL attribute",
902                sym->name, &common_root->n.common->where);
903
904   if (sym->attr.intrinsic)
905     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
906                sym->name, &common_root->n.common->where);
907   else if (sym->attr.result
908            || gfc_is_function_return_value (sym, gfc_current_ns))
909     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
910                     "that is also a function result", sym->name,
911                     &common_root->n.common->where);
912   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
913            && sym->attr.proc != PROC_ST_FUNCTION)
914     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
915                     "that is also a global procedure", sym->name,
916                     &common_root->n.common->where);
917 }
918
919
920 /* Resolve contained function types.  Because contained functions can call one
921    another, they have to be worked out before any of the contained procedures
922    can be resolved.
923
924    The good news is that if a function doesn't already have a type, the only
925    way it can get one is through an IMPLICIT type or a RESULT variable, because
926    by definition contained functions are contained namespace they're contained
927    in, not in a sibling or parent namespace.  */
928
929 static void
930 resolve_contained_functions (gfc_namespace *ns)
931 {
932   gfc_namespace *child;
933   gfc_entry_list *el;
934
935   resolve_formal_arglists (ns);
936
937   for (child = ns->contained; child; child = child->sibling)
938     {
939       /* Resolve alternate entry points first.  */
940       resolve_entries (child);
941
942       /* Then check function return types.  */
943       resolve_contained_fntype (child->proc_name, child);
944       for (el = child->entries; el; el = el->next)
945         resolve_contained_fntype (el->sym, child);
946     }
947 }
948
949
950 static gfc_try resolve_fl_derived0 (gfc_symbol *sym);
951
952
953 /* Resolve all of the elements of a structure constructor and make sure that
954    the types are correct. The 'init' flag indicates that the given
955    constructor is an initializer.  */
956
957 static gfc_try
958 resolve_structure_cons (gfc_expr *expr, int init)
959 {
960   gfc_constructor *cons;
961   gfc_component *comp;
962   gfc_try t;
963   symbol_attribute a;
964
965   t = SUCCESS;
966
967   if (expr->ts.type == BT_DERIVED)
968     resolve_fl_derived0 (expr->ts.u.derived);
969
970   cons = gfc_constructor_first (expr->value.constructor);
971
972   /* See if the user is trying to invoke a structure constructor for one of
973      the iso_c_binding derived types.  */
974   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
975       && expr->ts.u.derived->ts.is_iso_c && cons
976       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
977     {
978       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
979                  expr->ts.u.derived->name, &(expr->where));
980       return FAILURE;
981     }
982
983   /* Return if structure constructor is c_null_(fun)prt.  */
984   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
985       && expr->ts.u.derived->ts.is_iso_c && cons
986       && cons->expr && cons->expr->expr_type == EXPR_NULL)
987     return SUCCESS;
988
989   /* A constructor may have references if it is the result of substituting a
990      parameter variable.  In this case we just pull out the component we
991      want.  */
992   if (expr->ref)
993     comp = expr->ref->u.c.sym->components;
994   else
995     comp = expr->ts.u.derived->components;
996
997   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
998     {
999       int rank;
1000
1001       if (!cons->expr)
1002         continue;
1003
1004       if (gfc_resolve_expr (cons->expr) == FAILURE)
1005         {
1006           t = FAILURE;
1007           continue;
1008         }
1009
1010       rank = comp->as ? comp->as->rank : 0;
1011       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
1012           && (comp->attr.allocatable || cons->expr->rank))
1013         {
1014           gfc_error ("The rank of the element in the structure "
1015                      "constructor at %L does not match that of the "
1016                      "component (%d/%d)", &cons->expr->where,
1017                      cons->expr->rank, rank);
1018           t = FAILURE;
1019         }
1020
1021       /* If we don't have the right type, try to convert it.  */
1022
1023       if (!comp->attr.proc_pointer &&
1024           !gfc_compare_types (&cons->expr->ts, &comp->ts))
1025         {
1026           t = FAILURE;
1027           if (strcmp (comp->name, "_extends") == 0)
1028             {
1029               /* Can afford to be brutal with the _extends initializer.
1030                  The derived type can get lost because it is PRIVATE
1031                  but it is not usage constrained by the standard.  */
1032               cons->expr->ts = comp->ts;
1033               t = SUCCESS;
1034             }
1035           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
1036             gfc_error ("The element in the structure constructor at %L, "
1037                        "for pointer component '%s', is %s but should be %s",
1038                        &cons->expr->where, comp->name,
1039                        gfc_basic_typename (cons->expr->ts.type),
1040                        gfc_basic_typename (comp->ts.type));
1041           else
1042             t = gfc_convert_type (cons->expr, &comp->ts, 1);
1043         }
1044
1045       /* For strings, the length of the constructor should be the same as
1046          the one of the structure, ensure this if the lengths are known at
1047          compile time and when we are dealing with PARAMETER or structure
1048          constructors.  */
1049       if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1050           && comp->ts.u.cl->length
1051           && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1052           && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1053           && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1054           && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1055                       comp->ts.u.cl->length->value.integer) != 0)
1056         {
1057           if (cons->expr->expr_type == EXPR_VARIABLE
1058               && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1059             {
1060               /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1061                  to make use of the gfc_resolve_character_array_constructor
1062                  machinery.  The expression is later simplified away to
1063                  an array of string literals.  */
1064               gfc_expr *para = cons->expr;
1065               cons->expr = gfc_get_expr ();
1066               cons->expr->ts = para->ts;
1067               cons->expr->where = para->where;
1068               cons->expr->expr_type = EXPR_ARRAY;
1069               cons->expr->rank = para->rank;
1070               cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1071               gfc_constructor_append_expr (&cons->expr->value.constructor,
1072                                            para, &cons->expr->where);
1073             }
1074           if (cons->expr->expr_type == EXPR_ARRAY)
1075             {
1076               gfc_constructor *p;
1077               p = gfc_constructor_first (cons->expr->value.constructor);
1078               if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1079                 {
1080                   gfc_charlen *cl, *cl2;
1081
1082                   cl2 = NULL;
1083                   for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1084                     {
1085                       if (cl == cons->expr->ts.u.cl)
1086                         break;
1087                       cl2 = cl;
1088                     }
1089
1090                   gcc_assert (cl);
1091
1092                   if (cl2)
1093                     cl2->next = cl->next;
1094
1095                   gfc_free_expr (cl->length);
1096                   free (cl);
1097                 }
1098
1099               cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1100               cons->expr->ts.u.cl->length_from_typespec = true;
1101               cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1102               gfc_resolve_character_array_constructor (cons->expr);
1103             }
1104         }
1105
1106       if (cons->expr->expr_type == EXPR_NULL
1107           && !(comp->attr.pointer || comp->attr.allocatable
1108                || comp->attr.proc_pointer
1109                || (comp->ts.type == BT_CLASS
1110                    && (CLASS_DATA (comp)->attr.class_pointer
1111                        || CLASS_DATA (comp)->attr.allocatable))))
1112         {
1113           t = FAILURE;
1114           gfc_error ("The NULL in the structure constructor at %L is "
1115                      "being applied to component '%s', which is neither "
1116                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
1117                      comp->name);
1118         }
1119
1120       if (comp->attr.proc_pointer && comp->ts.interface)
1121         {
1122           /* Check procedure pointer interface.  */
1123           gfc_symbol *s2 = NULL;
1124           gfc_component *c2;
1125           const char *name;
1126           char err[200];
1127
1128           if (gfc_is_proc_ptr_comp (cons->expr, &c2))
1129             {
1130               s2 = c2->ts.interface;
1131               name = c2->name;
1132             }
1133           else if (cons->expr->expr_type == EXPR_FUNCTION)
1134             {
1135               s2 = cons->expr->symtree->n.sym->result;
1136               name = cons->expr->symtree->n.sym->result->name;
1137             }
1138           else if (cons->expr->expr_type != EXPR_NULL)
1139             {
1140               s2 = cons->expr->symtree->n.sym;
1141               name = cons->expr->symtree->n.sym->name;
1142             }
1143
1144           if (s2 && !gfc_compare_interfaces (comp->ts.interface, s2, name, 0, 1,
1145                                              err, sizeof (err)))
1146             {
1147               gfc_error ("Interface mismatch for procedure-pointer component "
1148                          "'%s' in structure constructor at %L: %s",
1149                          comp->name, &cons->expr->where, err);
1150               return FAILURE;
1151             }
1152         }
1153
1154       if (!comp->attr.pointer || comp->attr.proc_pointer
1155           || cons->expr->expr_type == EXPR_NULL)
1156         continue;
1157
1158       a = gfc_expr_attr (cons->expr);
1159
1160       if (!a.pointer && !a.target)
1161         {
1162           t = FAILURE;
1163           gfc_error ("The element in the structure constructor at %L, "
1164                      "for pointer component '%s' should be a POINTER or "
1165                      "a TARGET", &cons->expr->where, comp->name);
1166         }
1167
1168       if (init)
1169         {
1170           /* F08:C461. Additional checks for pointer initialization.  */
1171           if (a.allocatable)
1172             {
1173               t = FAILURE;
1174               gfc_error ("Pointer initialization target at %L "
1175                          "must not be ALLOCATABLE ", &cons->expr->where);
1176             }
1177           if (!a.save)
1178             {
1179               t = FAILURE;
1180               gfc_error ("Pointer initialization target at %L "
1181                          "must have the SAVE attribute", &cons->expr->where);
1182             }
1183         }
1184
1185       /* F2003, C1272 (3).  */
1186       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
1187           && (gfc_impure_variable (cons->expr->symtree->n.sym)
1188               || gfc_is_coindexed (cons->expr)))
1189         {
1190           t = FAILURE;
1191           gfc_error ("Invalid expression in the structure constructor for "
1192                      "pointer component '%s' at %L in PURE procedure",
1193                      comp->name, &cons->expr->where);
1194         }
1195
1196       if (gfc_implicit_pure (NULL)
1197             && cons->expr->expr_type == EXPR_VARIABLE
1198             && (gfc_impure_variable (cons->expr->symtree->n.sym)
1199                 || gfc_is_coindexed (cons->expr)))
1200         gfc_current_ns->proc_name->attr.implicit_pure = 0;
1201
1202     }
1203
1204   return t;
1205 }
1206
1207
1208 /****************** Expression name resolution ******************/
1209
1210 /* Returns 0 if a symbol was not declared with a type or
1211    attribute declaration statement, nonzero otherwise.  */
1212
1213 static int
1214 was_declared (gfc_symbol *sym)
1215 {
1216   symbol_attribute a;
1217
1218   a = sym->attr;
1219
1220   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1221     return 1;
1222
1223   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1224       || a.optional || a.pointer || a.save || a.target || a.volatile_
1225       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1226       || a.asynchronous || a.codimension)
1227     return 1;
1228
1229   return 0;
1230 }
1231
1232
1233 /* Determine if a symbol is generic or not.  */
1234
1235 static int
1236 generic_sym (gfc_symbol *sym)
1237 {
1238   gfc_symbol *s;
1239
1240   if (sym->attr.generic ||
1241       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1242     return 1;
1243
1244   if (was_declared (sym) || sym->ns->parent == NULL)
1245     return 0;
1246
1247   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1248   
1249   if (s != NULL)
1250     {
1251       if (s == sym)
1252         return 0;
1253       else
1254         return generic_sym (s);
1255     }
1256
1257   return 0;
1258 }
1259
1260
1261 /* Determine if a symbol is specific or not.  */
1262
1263 static int
1264 specific_sym (gfc_symbol *sym)
1265 {
1266   gfc_symbol *s;
1267
1268   if (sym->attr.if_source == IFSRC_IFBODY
1269       || sym->attr.proc == PROC_MODULE
1270       || sym->attr.proc == PROC_INTERNAL
1271       || sym->attr.proc == PROC_ST_FUNCTION
1272       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1273       || sym->attr.external)
1274     return 1;
1275
1276   if (was_declared (sym) || sym->ns->parent == NULL)
1277     return 0;
1278
1279   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1280
1281   return (s == NULL) ? 0 : specific_sym (s);
1282 }
1283
1284
1285 /* Figure out if the procedure is specific, generic or unknown.  */
1286
1287 typedef enum
1288 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1289 proc_type;
1290
1291 static proc_type
1292 procedure_kind (gfc_symbol *sym)
1293 {
1294   if (generic_sym (sym))
1295     return PTYPE_GENERIC;
1296
1297   if (specific_sym (sym))
1298     return PTYPE_SPECIFIC;
1299
1300   return PTYPE_UNKNOWN;
1301 }
1302
1303 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1304    is nonzero when matching actual arguments.  */
1305
1306 static int need_full_assumed_size = 0;
1307
1308 static bool
1309 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1310 {
1311   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1312       return false;
1313
1314   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1315      What should it be?  */
1316   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1317           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1318                && (e->ref->u.ar.type == AR_FULL))
1319     {
1320       gfc_error ("The upper bound in the last dimension must "
1321                  "appear in the reference to the assumed size "
1322                  "array '%s' at %L", sym->name, &e->where);
1323       return true;
1324     }
1325   return false;
1326 }
1327
1328
1329 /* Look for bad assumed size array references in argument expressions
1330   of elemental and array valued intrinsic procedures.  Since this is
1331   called from procedure resolution functions, it only recurses at
1332   operators.  */
1333
1334 static bool
1335 resolve_assumed_size_actual (gfc_expr *e)
1336 {
1337   if (e == NULL)
1338    return false;
1339
1340   switch (e->expr_type)
1341     {
1342     case EXPR_VARIABLE:
1343       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1344         return true;
1345       break;
1346
1347     case EXPR_OP:
1348       if (resolve_assumed_size_actual (e->value.op.op1)
1349           || resolve_assumed_size_actual (e->value.op.op2))
1350         return true;
1351       break;
1352
1353     default:
1354       break;
1355     }
1356   return false;
1357 }
1358
1359
1360 /* Check a generic procedure, passed as an actual argument, to see if
1361    there is a matching specific name.  If none, it is an error, and if
1362    more than one, the reference is ambiguous.  */
1363 static int
1364 count_specific_procs (gfc_expr *e)
1365 {
1366   int n;
1367   gfc_interface *p;
1368   gfc_symbol *sym;
1369         
1370   n = 0;
1371   sym = e->symtree->n.sym;
1372
1373   for (p = sym->generic; p; p = p->next)
1374     if (strcmp (sym->name, p->sym->name) == 0)
1375       {
1376         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1377                                        sym->name);
1378         n++;
1379       }
1380
1381   if (n > 1)
1382     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1383                &e->where);
1384
1385   if (n == 0)
1386     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1387                "argument at %L", sym->name, &e->where);
1388
1389   return n;
1390 }
1391
1392
1393 /* See if a call to sym could possibly be a not allowed RECURSION because of
1394    a missing RECURIVE declaration.  This means that either sym is the current
1395    context itself, or sym is the parent of a contained procedure calling its
1396    non-RECURSIVE containing procedure.
1397    This also works if sym is an ENTRY.  */
1398
1399 static bool
1400 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1401 {
1402   gfc_symbol* proc_sym;
1403   gfc_symbol* context_proc;
1404   gfc_namespace* real_context;
1405
1406   if (sym->attr.flavor == FL_PROGRAM
1407       || sym->attr.flavor == FL_DERIVED)
1408     return false;
1409
1410   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1411
1412   /* If we've got an ENTRY, find real procedure.  */
1413   if (sym->attr.entry && sym->ns->entries)
1414     proc_sym = sym->ns->entries->sym;
1415   else
1416     proc_sym = sym;
1417
1418   /* If sym is RECURSIVE, all is well of course.  */
1419   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1420     return false;
1421
1422   /* Find the context procedure's "real" symbol if it has entries.
1423      We look for a procedure symbol, so recurse on the parents if we don't
1424      find one (like in case of a BLOCK construct).  */
1425   for (real_context = context; ; real_context = real_context->parent)
1426     {
1427       /* We should find something, eventually!  */
1428       gcc_assert (real_context);
1429
1430       context_proc = (real_context->entries ? real_context->entries->sym
1431                                             : real_context->proc_name);
1432
1433       /* In some special cases, there may not be a proc_name, like for this
1434          invalid code:
1435          real(bad_kind()) function foo () ...
1436          when checking the call to bad_kind ().
1437          In these cases, we simply return here and assume that the
1438          call is ok.  */
1439       if (!context_proc)
1440         return false;
1441
1442       if (context_proc->attr.flavor != FL_LABEL)
1443         break;
1444     }
1445
1446   /* A call from sym's body to itself is recursion, of course.  */
1447   if (context_proc == proc_sym)
1448     return true;
1449
1450   /* The same is true if context is a contained procedure and sym the
1451      containing one.  */
1452   if (context_proc->attr.contained)
1453     {
1454       gfc_symbol* parent_proc;
1455
1456       gcc_assert (context->parent);
1457       parent_proc = (context->parent->entries ? context->parent->entries->sym
1458                                               : context->parent->proc_name);
1459
1460       if (parent_proc == proc_sym)
1461         return true;
1462     }
1463
1464   return false;
1465 }
1466
1467
1468 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1469    its typespec and formal argument list.  */
1470
1471 static gfc_try
1472 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1473 {
1474   gfc_intrinsic_sym* isym = NULL;
1475   const char* symstd;
1476
1477   if (sym->formal)
1478     return SUCCESS;
1479
1480   /* Already resolved.  */
1481   if (sym->from_intmod && sym->ts.type != BT_UNKNOWN)
1482     return SUCCESS;
1483
1484   /* We already know this one is an intrinsic, so we don't call
1485      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1486      gfc_find_subroutine directly to check whether it is a function or
1487      subroutine.  */
1488
1489   if (sym->intmod_sym_id)
1490     isym = gfc_intrinsic_function_by_id ((gfc_isym_id) sym->intmod_sym_id);
1491   else
1492     isym = gfc_find_function (sym->name);
1493
1494   if (isym)
1495     {
1496       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1497           && !sym->attr.implicit_type)
1498         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1499                       " ignored", sym->name, &sym->declared_at);
1500
1501       if (!sym->attr.function &&
1502           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1503         return FAILURE;
1504
1505       sym->ts = isym->ts;
1506     }
1507   else if ((isym = gfc_find_subroutine (sym->name)))
1508     {
1509       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1510         {
1511           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1512                       " specifier", sym->name, &sym->declared_at);
1513           return FAILURE;
1514         }
1515
1516       if (!sym->attr.subroutine &&
1517           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1518         return FAILURE;
1519     }
1520   else
1521     {
1522       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1523                  &sym->declared_at);
1524       return FAILURE;
1525     }
1526
1527   gfc_copy_formal_args_intr (sym, isym);
1528
1529   /* Check it is actually available in the standard settings.  */
1530   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1531       == FAILURE)
1532     {
1533       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1534                  " available in the current standard settings but %s.  Use"
1535                  " an appropriate -std=* option or enable -fall-intrinsics"
1536                  " in order to use it.",
1537                  sym->name, &sym->declared_at, symstd);
1538       return FAILURE;
1539     }
1540
1541   return SUCCESS;
1542 }
1543
1544
1545 /* Resolve a procedure expression, like passing it to a called procedure or as
1546    RHS for a procedure pointer assignment.  */
1547
1548 static gfc_try
1549 resolve_procedure_expression (gfc_expr* expr)
1550 {
1551   gfc_symbol* sym;
1552
1553   if (expr->expr_type != EXPR_VARIABLE)
1554     return SUCCESS;
1555   gcc_assert (expr->symtree);
1556
1557   sym = expr->symtree->n.sym;
1558
1559   if (sym->attr.intrinsic)
1560     resolve_intrinsic (sym, &expr->where);
1561
1562   if (sym->attr.flavor != FL_PROCEDURE
1563       || (sym->attr.function && sym->result == sym))
1564     return SUCCESS;
1565
1566   /* A non-RECURSIVE procedure that is used as procedure expression within its
1567      own body is in danger of being called recursively.  */
1568   if (is_illegal_recursion (sym, gfc_current_ns))
1569     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1570                  " itself recursively.  Declare it RECURSIVE or use"
1571                  " -frecursive", sym->name, &expr->where);
1572   
1573   return SUCCESS;
1574 }
1575
1576
1577 /* Resolve an actual argument list.  Most of the time, this is just
1578    resolving the expressions in the list.
1579    The exception is that we sometimes have to decide whether arguments
1580    that look like procedure arguments are really simple variable
1581    references.  */
1582
1583 static gfc_try
1584 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1585                         bool no_formal_args)
1586 {
1587   gfc_symbol *sym;
1588   gfc_symtree *parent_st;
1589   gfc_expr *e;
1590   int save_need_full_assumed_size;
1591
1592   for (; arg; arg = arg->next)
1593     {
1594       e = arg->expr;
1595       if (e == NULL)
1596         {
1597           /* Check the label is a valid branching target.  */
1598           if (arg->label)
1599             {
1600               if (arg->label->defined == ST_LABEL_UNKNOWN)
1601                 {
1602                   gfc_error ("Label %d referenced at %L is never defined",
1603                              arg->label->value, &arg->label->where);
1604                   return FAILURE;
1605                 }
1606             }
1607           continue;
1608         }
1609
1610       if (e->expr_type == EXPR_VARIABLE
1611             && e->symtree->n.sym->attr.generic
1612             && no_formal_args
1613             && count_specific_procs (e) != 1)
1614         return FAILURE;
1615
1616       if (e->ts.type != BT_PROCEDURE)
1617         {
1618           save_need_full_assumed_size = need_full_assumed_size;
1619           if (e->expr_type != EXPR_VARIABLE)
1620             need_full_assumed_size = 0;
1621           if (gfc_resolve_expr (e) != SUCCESS)
1622             return FAILURE;
1623           need_full_assumed_size = save_need_full_assumed_size;
1624           goto argument_list;
1625         }
1626
1627       /* See if the expression node should really be a variable reference.  */
1628
1629       sym = e->symtree->n.sym;
1630
1631       if (sym->attr.flavor == FL_PROCEDURE
1632           || sym->attr.intrinsic
1633           || sym->attr.external)
1634         {
1635           int actual_ok;
1636
1637           /* If a procedure is not already determined to be something else
1638              check if it is intrinsic.  */
1639           if (!sym->attr.intrinsic
1640               && !(sym->attr.external || sym->attr.use_assoc
1641                    || sym->attr.if_source == IFSRC_IFBODY)
1642               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1643             sym->attr.intrinsic = 1;
1644
1645           if (sym->attr.proc == PROC_ST_FUNCTION)
1646             {
1647               gfc_error ("Statement function '%s' at %L is not allowed as an "
1648                          "actual argument", sym->name, &e->where);
1649             }
1650
1651           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1652                                                sym->attr.subroutine);
1653           if (sym->attr.intrinsic && actual_ok == 0)
1654             {
1655               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1656                          "actual argument", sym->name, &e->where);
1657             }
1658
1659           if (sym->attr.contained && !sym->attr.use_assoc
1660               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1661             {
1662               if (gfc_notify_std (GFC_STD_F2008,
1663                                   "Fortran 2008: Internal procedure '%s' is"
1664                                   " used as actual argument at %L",
1665                                   sym->name, &e->where) == FAILURE)
1666                 return FAILURE;
1667             }
1668
1669           if (sym->attr.elemental && !sym->attr.intrinsic)
1670             {
1671               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1672                          "allowed as an actual argument at %L", sym->name,
1673                          &e->where);
1674             }
1675
1676           /* Check if a generic interface has a specific procedure
1677             with the same name before emitting an error.  */
1678           if (sym->attr.generic && count_specific_procs (e) != 1)
1679             return FAILURE;
1680           
1681           /* Just in case a specific was found for the expression.  */
1682           sym = e->symtree->n.sym;
1683
1684           /* If the symbol is the function that names the current (or
1685              parent) scope, then we really have a variable reference.  */
1686
1687           if (gfc_is_function_return_value (sym, sym->ns))
1688             goto got_variable;
1689
1690           /* If all else fails, see if we have a specific intrinsic.  */
1691           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1692             {
1693               gfc_intrinsic_sym *isym;
1694
1695               isym = gfc_find_function (sym->name);
1696               if (isym == NULL || !isym->specific)
1697                 {
1698                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1699                              "for the reference '%s' at %L", sym->name,
1700                              &e->where);
1701                   return FAILURE;
1702                 }
1703               sym->ts = isym->ts;
1704               sym->attr.intrinsic = 1;
1705               sym->attr.function = 1;
1706             }
1707
1708           if (gfc_resolve_expr (e) == FAILURE)
1709             return FAILURE;
1710           goto argument_list;
1711         }
1712
1713       /* See if the name is a module procedure in a parent unit.  */
1714
1715       if (was_declared (sym) || sym->ns->parent == NULL)
1716         goto got_variable;
1717
1718       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1719         {
1720           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1721           return FAILURE;
1722         }
1723
1724       if (parent_st == NULL)
1725         goto got_variable;
1726
1727       sym = parent_st->n.sym;
1728       e->symtree = parent_st;           /* Point to the right thing.  */
1729
1730       if (sym->attr.flavor == FL_PROCEDURE
1731           || sym->attr.intrinsic
1732           || sym->attr.external)
1733         {
1734           if (gfc_resolve_expr (e) == FAILURE)
1735             return FAILURE;
1736           goto argument_list;
1737         }
1738
1739     got_variable:
1740       e->expr_type = EXPR_VARIABLE;
1741       e->ts = sym->ts;
1742       if (sym->as != NULL)
1743         {
1744           e->rank = sym->as->rank;
1745           e->ref = gfc_get_ref ();
1746           e->ref->type = REF_ARRAY;
1747           e->ref->u.ar.type = AR_FULL;
1748           e->ref->u.ar.as = sym->as;
1749         }
1750
1751       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1752          primary.c (match_actual_arg). If above code determines that it
1753          is a  variable instead, it needs to be resolved as it was not
1754          done at the beginning of this function.  */
1755       save_need_full_assumed_size = need_full_assumed_size;
1756       if (e->expr_type != EXPR_VARIABLE)
1757         need_full_assumed_size = 0;
1758       if (gfc_resolve_expr (e) != SUCCESS)
1759         return FAILURE;
1760       need_full_assumed_size = save_need_full_assumed_size;
1761
1762     argument_list:
1763       /* Check argument list functions %VAL, %LOC and %REF.  There is
1764          nothing to do for %REF.  */
1765       if (arg->name && arg->name[0] == '%')
1766         {
1767           if (strncmp ("%VAL", arg->name, 4) == 0)
1768             {
1769               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1770                 {
1771                   gfc_error ("By-value argument at %L is not of numeric "
1772                              "type", &e->where);
1773                   return FAILURE;
1774                 }
1775
1776               if (e->rank)
1777                 {
1778                   gfc_error ("By-value argument at %L cannot be an array or "
1779                              "an array section", &e->where);
1780                 return FAILURE;
1781                 }
1782
1783               /* Intrinsics are still PROC_UNKNOWN here.  However,
1784                  since same file external procedures are not resolvable
1785                  in gfortran, it is a good deal easier to leave them to
1786                  intrinsic.c.  */
1787               if (ptype != PROC_UNKNOWN
1788                   && ptype != PROC_DUMMY
1789                   && ptype != PROC_EXTERNAL
1790                   && ptype != PROC_MODULE)
1791                 {
1792                   gfc_error ("By-value argument at %L is not allowed "
1793                              "in this context", &e->where);
1794                   return FAILURE;
1795                 }
1796             }
1797
1798           /* Statement functions have already been excluded above.  */
1799           else if (strncmp ("%LOC", arg->name, 4) == 0
1800                    && e->ts.type == BT_PROCEDURE)
1801             {
1802               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1803                 {
1804                   gfc_error ("Passing internal procedure at %L by location "
1805                              "not allowed", &e->where);
1806                   return FAILURE;
1807                 }
1808             }
1809         }
1810
1811       /* Fortran 2008, C1237.  */
1812       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1813           && gfc_has_ultimate_pointer (e))
1814         {
1815           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1816                      "component", &e->where);
1817           return FAILURE;
1818         }
1819     }
1820
1821   return SUCCESS;
1822 }
1823
1824
1825 /* Do the checks of the actual argument list that are specific to elemental
1826    procedures.  If called with c == NULL, we have a function, otherwise if
1827    expr == NULL, we have a subroutine.  */
1828
1829 static gfc_try
1830 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1831 {
1832   gfc_actual_arglist *arg0;
1833   gfc_actual_arglist *arg;
1834   gfc_symbol *esym = NULL;
1835   gfc_intrinsic_sym *isym = NULL;
1836   gfc_expr *e = NULL;
1837   gfc_intrinsic_arg *iformal = NULL;
1838   gfc_formal_arglist *eformal = NULL;
1839   bool formal_optional = false;
1840   bool set_by_optional = false;
1841   int i;
1842   int rank = 0;
1843
1844   /* Is this an elemental procedure?  */
1845   if (expr && expr->value.function.actual != NULL)
1846     {
1847       if (expr->value.function.esym != NULL
1848           && expr->value.function.esym->attr.elemental)
1849         {
1850           arg0 = expr->value.function.actual;
1851           esym = expr->value.function.esym;
1852         }
1853       else if (expr->value.function.isym != NULL
1854                && expr->value.function.isym->elemental)
1855         {
1856           arg0 = expr->value.function.actual;
1857           isym = expr->value.function.isym;
1858         }
1859       else
1860         return SUCCESS;
1861     }
1862   else if (c && c->ext.actual != NULL)
1863     {
1864       arg0 = c->ext.actual;
1865       
1866       if (c->resolved_sym)
1867         esym = c->resolved_sym;
1868       else
1869         esym = c->symtree->n.sym;
1870       gcc_assert (esym);
1871
1872       if (!esym->attr.elemental)
1873         return SUCCESS;
1874     }
1875   else
1876     return SUCCESS;
1877
1878   /* The rank of an elemental is the rank of its array argument(s).  */
1879   for (arg = arg0; arg; arg = arg->next)
1880     {
1881       if (arg->expr != NULL && arg->expr->rank > 0)
1882         {
1883           rank = arg->expr->rank;
1884           if (arg->expr->expr_type == EXPR_VARIABLE
1885               && arg->expr->symtree->n.sym->attr.optional)
1886             set_by_optional = true;
1887
1888           /* Function specific; set the result rank and shape.  */
1889           if (expr)
1890             {
1891               expr->rank = rank;
1892               if (!expr->shape && arg->expr->shape)
1893                 {
1894                   expr->shape = gfc_get_shape (rank);
1895                   for (i = 0; i < rank; i++)
1896                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1897                 }
1898             }
1899           break;
1900         }
1901     }
1902
1903   /* If it is an array, it shall not be supplied as an actual argument
1904      to an elemental procedure unless an array of the same rank is supplied
1905      as an actual argument corresponding to a nonoptional dummy argument of
1906      that elemental procedure(12.4.1.5).  */
1907   formal_optional = false;
1908   if (isym)
1909     iformal = isym->formal;
1910   else
1911     eformal = esym->formal;
1912
1913   for (arg = arg0; arg; arg = arg->next)
1914     {
1915       if (eformal)
1916         {
1917           if (eformal->sym && eformal->sym->attr.optional)
1918             formal_optional = true;
1919           eformal = eformal->next;
1920         }
1921       else if (isym && iformal)
1922         {
1923           if (iformal->optional)
1924             formal_optional = true;
1925           iformal = iformal->next;
1926         }
1927       else if (isym)
1928         formal_optional = true;
1929
1930       if (pedantic && arg->expr != NULL
1931           && arg->expr->expr_type == EXPR_VARIABLE
1932           && arg->expr->symtree->n.sym->attr.optional
1933           && formal_optional
1934           && arg->expr->rank
1935           && (set_by_optional || arg->expr->rank != rank)
1936           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1937         {
1938           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1939                        "MISSING, it cannot be the actual argument of an "
1940                        "ELEMENTAL procedure unless there is a non-optional "
1941                        "argument with the same rank (12.4.1.5)",
1942                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1943           return FAILURE;
1944         }
1945     }
1946
1947   for (arg = arg0; arg; arg = arg->next)
1948     {
1949       if (arg->expr == NULL || arg->expr->rank == 0)
1950         continue;
1951
1952       /* Being elemental, the last upper bound of an assumed size array
1953          argument must be present.  */
1954       if (resolve_assumed_size_actual (arg->expr))
1955         return FAILURE;
1956
1957       /* Elemental procedure's array actual arguments must conform.  */
1958       if (e != NULL)
1959         {
1960           if (gfc_check_conformance (arg->expr, e,
1961                                      "elemental procedure") == FAILURE)
1962             return FAILURE;
1963         }
1964       else
1965         e = arg->expr;
1966     }
1967
1968   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1969      is an array, the intent inout/out variable needs to be also an array.  */
1970   if (rank > 0 && esym && expr == NULL)
1971     for (eformal = esym->formal, arg = arg0; arg && eformal;
1972          arg = arg->next, eformal = eformal->next)
1973       if ((eformal->sym->attr.intent == INTENT_OUT
1974            || eformal->sym->attr.intent == INTENT_INOUT)
1975           && arg->expr && arg->expr->rank == 0)
1976         {
1977           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1978                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1979                      "actual argument is an array", &arg->expr->where,
1980                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1981                      : "INOUT", eformal->sym->name, esym->name);
1982           return FAILURE;
1983         }
1984   return SUCCESS;
1985 }
1986
1987
1988 /* This function does the checking of references to global procedures
1989    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1990    77 and 95 standards.  It checks for a gsymbol for the name, making
1991    one if it does not already exist.  If it already exists, then the
1992    reference being resolved must correspond to the type of gsymbol.
1993    Otherwise, the new symbol is equipped with the attributes of the
1994    reference.  The corresponding code that is called in creating
1995    global entities is parse.c.
1996
1997    In addition, for all but -std=legacy, the gsymbols are used to
1998    check the interfaces of external procedures from the same file.
1999    The namespace of the gsymbol is resolved and then, once this is
2000    done the interface is checked.  */
2001
2002
2003 static bool
2004 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
2005 {
2006   if (!gsym_ns->proc_name->attr.recursive)
2007     return true;
2008
2009   if (sym->ns == gsym_ns)
2010     return false;
2011
2012   if (sym->ns->parent && sym->ns->parent == gsym_ns)
2013     return false;
2014
2015   return true;
2016 }
2017
2018 static bool
2019 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
2020 {
2021   if (gsym_ns->entries)
2022     {
2023       gfc_entry_list *entry = gsym_ns->entries;
2024
2025       for (; entry; entry = entry->next)
2026         {
2027           if (strcmp (sym->name, entry->sym->name) == 0)
2028             {
2029               if (strcmp (gsym_ns->proc_name->name,
2030                           sym->ns->proc_name->name) == 0)
2031                 return false;
2032
2033               if (sym->ns->parent
2034                   && strcmp (gsym_ns->proc_name->name,
2035                              sym->ns->parent->proc_name->name) == 0)
2036                 return false;
2037             }
2038         }
2039     }
2040   return true;
2041 }
2042
2043 static void
2044 resolve_global_procedure (gfc_symbol *sym, locus *where,
2045                           gfc_actual_arglist **actual, int sub)
2046 {
2047   gfc_gsymbol * gsym;
2048   gfc_namespace *ns;
2049   enum gfc_symbol_type type;
2050
2051   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
2052
2053   gsym = gfc_get_gsymbol (sym->name);
2054
2055   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
2056     gfc_global_used (gsym, where);
2057
2058   if (gfc_option.flag_whole_file
2059         && (sym->attr.if_source == IFSRC_UNKNOWN
2060             || sym->attr.if_source == IFSRC_IFBODY)
2061         && gsym->type != GSYM_UNKNOWN
2062         && gsym->ns
2063         && gsym->ns->resolved != -1
2064         && gsym->ns->proc_name
2065         && not_in_recursive (sym, gsym->ns)
2066         && not_entry_self_reference (sym, gsym->ns))
2067     {
2068       gfc_symbol *def_sym;
2069
2070       /* Resolve the gsymbol namespace if needed.  */
2071       if (!gsym->ns->resolved)
2072         {
2073           gfc_dt_list *old_dt_list;
2074           struct gfc_omp_saved_state old_omp_state;
2075
2076           /* Stash away derived types so that the backend_decls do not
2077              get mixed up.  */
2078           old_dt_list = gfc_derived_types;
2079           gfc_derived_types = NULL;
2080           /* And stash away openmp state.  */
2081           gfc_omp_save_and_clear_state (&old_omp_state);
2082
2083           gfc_resolve (gsym->ns);
2084
2085           /* Store the new derived types with the global namespace.  */
2086           if (gfc_derived_types)
2087             gsym->ns->derived_types = gfc_derived_types;
2088
2089           /* Restore the derived types of this namespace.  */
2090           gfc_derived_types = old_dt_list;
2091           /* And openmp state.  */
2092           gfc_omp_restore_state (&old_omp_state);
2093         }
2094
2095       /* Make sure that translation for the gsymbol occurs before
2096          the procedure currently being resolved.  */
2097       ns = gfc_global_ns_list;
2098       for (; ns && ns != gsym->ns; ns = ns->sibling)
2099         {
2100           if (ns->sibling == gsym->ns)
2101             {
2102               ns->sibling = gsym->ns->sibling;
2103               gsym->ns->sibling = gfc_global_ns_list;
2104               gfc_global_ns_list = gsym->ns;
2105               break;
2106             }
2107         }
2108
2109       def_sym = gsym->ns->proc_name;
2110       if (def_sym->attr.entry_master)
2111         {
2112           gfc_entry_list *entry;
2113           for (entry = gsym->ns->entries; entry; entry = entry->next)
2114             if (strcmp (entry->sym->name, sym->name) == 0)
2115               {
2116                 def_sym = entry->sym;
2117                 break;
2118               }
2119         }
2120
2121       /* Differences in constant character lengths.  */
2122       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
2123         {
2124           long int l1 = 0, l2 = 0;
2125           gfc_charlen *cl1 = sym->ts.u.cl;
2126           gfc_charlen *cl2 = def_sym->ts.u.cl;
2127
2128           if (cl1 != NULL
2129               && cl1->length != NULL
2130               && cl1->length->expr_type == EXPR_CONSTANT)
2131             l1 = mpz_get_si (cl1->length->value.integer);
2132
2133           if (cl2 != NULL
2134               && cl2->length != NULL
2135               && cl2->length->expr_type == EXPR_CONSTANT)
2136             l2 = mpz_get_si (cl2->length->value.integer);
2137
2138           if (l1 && l2 && l1 != l2)
2139             gfc_error ("Character length mismatch in return type of "
2140                        "function '%s' at %L (%ld/%ld)", sym->name,
2141                        &sym->declared_at, l1, l2);
2142         }
2143
2144      /* Type mismatch of function return type and expected type.  */
2145      if (sym->attr.function
2146          && !gfc_compare_types (&sym->ts, &def_sym->ts))
2147         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
2148                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2149                    gfc_typename (&def_sym->ts));
2150
2151       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
2152         {
2153           gfc_formal_arglist *arg = def_sym->formal;
2154           for ( ; arg; arg = arg->next)
2155             if (!arg->sym)
2156               continue;
2157             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
2158             else if (arg->sym->attr.allocatable
2159                      || arg->sym->attr.asynchronous
2160                      || arg->sym->attr.optional
2161                      || arg->sym->attr.pointer
2162                      || arg->sym->attr.target
2163                      || arg->sym->attr.value
2164                      || arg->sym->attr.volatile_)
2165               {
2166                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
2167                            "has an attribute that requires an explicit "
2168                            "interface for this procedure", arg->sym->name,
2169                            sym->name, &sym->declared_at);
2170                 break;
2171               }
2172             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
2173             else if (arg->sym && arg->sym->as
2174                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
2175               {
2176                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
2177                            "argument '%s' must have an explicit interface",
2178                            sym->name, &sym->declared_at, arg->sym->name);
2179                 break;
2180               }
2181             /* F2008, 12.4.2.2 (2c)  */
2182             else if (arg->sym->attr.codimension)
2183               {
2184                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
2185                            "'%s' must have an explicit interface",
2186                            sym->name, &sym->declared_at, arg->sym->name);
2187                 break;
2188               }
2189             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
2190             else if (false) /* TODO: is a parametrized derived type  */
2191               {
2192                 gfc_error ("Procedure '%s' at %L with parametrized derived "
2193                            "type argument '%s' must have an explicit "
2194                            "interface", sym->name, &sym->declared_at,
2195                            arg->sym->name);
2196                 break;
2197               }
2198             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
2199             else if (arg->sym->ts.type == BT_CLASS)
2200               {
2201                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
2202                            "argument '%s' must have an explicit interface",
2203                            sym->name, &sym->declared_at, arg->sym->name);
2204                 break;
2205               }
2206         }
2207
2208       if (def_sym->attr.function)
2209         {
2210           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
2211           if (def_sym->as && def_sym->as->rank
2212               && (!sym->as || sym->as->rank != def_sym->as->rank))
2213             gfc_error ("The reference to function '%s' at %L either needs an "
2214                        "explicit INTERFACE or the rank is incorrect", sym->name,
2215                        where);
2216
2217           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
2218           if ((def_sym->result->attr.pointer
2219                || def_sym->result->attr.allocatable)
2220                && (sym->attr.if_source != IFSRC_IFBODY
2221                    || def_sym->result->attr.pointer
2222                         != sym->result->attr.pointer
2223                    || def_sym->result->attr.allocatable
2224                         != sym->result->attr.allocatable))
2225             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
2226                        "result must have an explicit interface", sym->name,
2227                        where);
2228
2229           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
2230           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
2231               && def_sym->ts.type == BT_CHARACTER && def_sym->ts.u.cl->length != NULL)
2232             {
2233               gfc_charlen *cl = sym->ts.u.cl;
2234
2235               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
2236                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
2237                 {
2238                   gfc_error ("Nonconstant character-length function '%s' at %L "
2239                              "must have an explicit interface", sym->name,
2240                              &sym->declared_at);
2241                 }
2242             }
2243         }
2244
2245       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2246       if (def_sym->attr.elemental && !sym->attr.elemental)
2247         {
2248           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2249                      "interface", sym->name, &sym->declared_at);
2250         }
2251
2252       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2253       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2254         {
2255           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2256                      "an explicit interface", sym->name, &sym->declared_at);
2257         }
2258
2259       if (gfc_option.flag_whole_file == 1
2260           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2261               && !(gfc_option.warn_std & GFC_STD_GNU)))
2262         gfc_errors_to_warnings (1);
2263
2264       if (sym->attr.if_source != IFSRC_IFBODY)  
2265         gfc_procedure_use (def_sym, actual, where);
2266
2267       gfc_errors_to_warnings (0);
2268     }
2269
2270   if (gsym->type == GSYM_UNKNOWN)
2271     {
2272       gsym->type = type;
2273       gsym->where = *where;
2274     }
2275
2276   gsym->used = 1;
2277 }
2278
2279
2280 /************* Function resolution *************/
2281
2282 /* Resolve a function call known to be generic.
2283    Section 14.1.2.4.1.  */
2284
2285 static match
2286 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2287 {
2288   gfc_symbol *s;
2289
2290   if (sym->attr.generic)
2291     {
2292       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2293       if (s != NULL)
2294         {
2295           expr->value.function.name = s->name;
2296           expr->value.function.esym = s;
2297
2298           if (s->ts.type != BT_UNKNOWN)
2299             expr->ts = s->ts;
2300           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2301             expr->ts = s->result->ts;
2302
2303           if (s->as != NULL)
2304             expr->rank = s->as->rank;
2305           else if (s->result != NULL && s->result->as != NULL)
2306             expr->rank = s->result->as->rank;
2307
2308           gfc_set_sym_referenced (expr->value.function.esym);
2309
2310           return MATCH_YES;
2311         }
2312
2313       /* TODO: Need to search for elemental references in generic
2314          interface.  */
2315     }
2316
2317   if (sym->attr.intrinsic)
2318     return gfc_intrinsic_func_interface (expr, 0);
2319
2320   return MATCH_NO;
2321 }
2322
2323
2324 static gfc_try
2325 resolve_generic_f (gfc_expr *expr)
2326 {
2327   gfc_symbol *sym;
2328   match m;
2329   gfc_interface *intr = NULL;
2330
2331   sym = expr->symtree->n.sym;
2332
2333   for (;;)
2334     {
2335       m = resolve_generic_f0 (expr, sym);
2336       if (m == MATCH_YES)
2337         return SUCCESS;
2338       else if (m == MATCH_ERROR)
2339         return FAILURE;
2340
2341 generic:
2342       if (!intr)
2343         for (intr = sym->generic; intr; intr = intr->next)
2344           if (intr->sym->attr.flavor == FL_DERIVED)
2345             break;
2346
2347       if (sym->ns->parent == NULL)
2348         break;
2349       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2350
2351       if (sym == NULL)
2352         break;
2353       if (!generic_sym (sym))
2354         goto generic;
2355     }
2356
2357   /* Last ditch attempt.  See if the reference is to an intrinsic
2358      that possesses a matching interface.  14.1.2.4  */
2359   if (sym  && !intr && !gfc_is_intrinsic (sym, 0, expr->where))
2360     {
2361       gfc_error ("There is no specific function for the generic '%s' "
2362                  "at %L", expr->symtree->n.sym->name, &expr->where);
2363       return FAILURE;
2364     }
2365
2366   if (intr)
2367     {
2368       if (gfc_convert_to_structure_constructor (expr, intr->sym, NULL, NULL,
2369                                                 false) != SUCCESS)
2370         return FAILURE;
2371       return resolve_structure_cons (expr, 0);
2372     }
2373
2374   m = gfc_intrinsic_func_interface (expr, 0);
2375   if (m == MATCH_YES)
2376     return SUCCESS;
2377
2378   if (m == MATCH_NO)
2379     gfc_error ("Generic function '%s' at %L is not consistent with a "
2380                "specific intrinsic interface", expr->symtree->n.sym->name,
2381                &expr->where);
2382
2383   return FAILURE;
2384 }
2385
2386
2387 /* Resolve a function call known to be specific.  */
2388
2389 static match
2390 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2391 {
2392   match m;
2393
2394   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2395     {
2396       if (sym->attr.dummy)
2397         {
2398           sym->attr.proc = PROC_DUMMY;
2399           goto found;
2400         }
2401
2402       sym->attr.proc = PROC_EXTERNAL;
2403       goto found;
2404     }
2405
2406   if (sym->attr.proc == PROC_MODULE
2407       || sym->attr.proc == PROC_ST_FUNCTION
2408       || sym->attr.proc == PROC_INTERNAL)
2409     goto found;
2410
2411   if (sym->attr.intrinsic)
2412     {
2413       m = gfc_intrinsic_func_interface (expr, 1);
2414       if (m == MATCH_YES)
2415         return MATCH_YES;
2416       if (m == MATCH_NO)
2417         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2418                    "with an intrinsic", sym->name, &expr->where);
2419
2420       return MATCH_ERROR;
2421     }
2422
2423   return MATCH_NO;
2424
2425 found:
2426   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2427
2428   if (sym->result)
2429     expr->ts = sym->result->ts;
2430   else
2431     expr->ts = sym->ts;
2432   expr->value.function.name = sym->name;
2433   expr->value.function.esym = sym;
2434   if (sym->as != NULL)
2435     expr->rank = sym->as->rank;
2436
2437   return MATCH_YES;
2438 }
2439
2440
2441 static gfc_try
2442 resolve_specific_f (gfc_expr *expr)
2443 {
2444   gfc_symbol *sym;
2445   match m;
2446
2447   sym = expr->symtree->n.sym;
2448
2449   for (;;)
2450     {
2451       m = resolve_specific_f0 (sym, expr);
2452       if (m == MATCH_YES)
2453         return SUCCESS;
2454       if (m == MATCH_ERROR)
2455         return FAILURE;
2456
2457       if (sym->ns->parent == NULL)
2458         break;
2459
2460       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2461
2462       if (sym == NULL)
2463         break;
2464     }
2465
2466   gfc_error ("Unable to resolve the specific function '%s' at %L",
2467              expr->symtree->n.sym->name, &expr->where);
2468
2469   return SUCCESS;
2470 }
2471
2472
2473 /* Resolve a procedure call not known to be generic nor specific.  */
2474
2475 static gfc_try
2476 resolve_unknown_f (gfc_expr *expr)
2477 {
2478   gfc_symbol *sym;
2479   gfc_typespec *ts;
2480
2481   sym = expr->symtree->n.sym;
2482
2483   if (sym->attr.dummy)
2484     {
2485       sym->attr.proc = PROC_DUMMY;
2486       expr->value.function.name = sym->name;
2487       goto set_type;
2488     }
2489
2490   /* See if we have an intrinsic function reference.  */
2491
2492   if (gfc_is_intrinsic (sym, 0, expr->where))
2493     {
2494       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2495         return SUCCESS;
2496       return FAILURE;
2497     }
2498
2499   /* The reference is to an external name.  */
2500
2501   sym->attr.proc = PROC_EXTERNAL;
2502   expr->value.function.name = sym->name;
2503   expr->value.function.esym = expr->symtree->n.sym;
2504
2505   if (sym->as != NULL)
2506     expr->rank = sym->as->rank;
2507
2508   /* Type of the expression is either the type of the symbol or the
2509      default type of the symbol.  */
2510
2511 set_type:
2512   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2513
2514   if (sym->ts.type != BT_UNKNOWN)
2515     expr->ts = sym->ts;
2516   else
2517     {
2518       ts = gfc_get_default_type (sym->name, sym->ns);
2519
2520       if (ts->type == BT_UNKNOWN)
2521         {
2522           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2523                      sym->name, &expr->where);
2524           return FAILURE;
2525         }
2526       else
2527         expr->ts = *ts;
2528     }
2529
2530   return SUCCESS;
2531 }
2532
2533
2534 /* Return true, if the symbol is an external procedure.  */
2535 static bool
2536 is_external_proc (gfc_symbol *sym)
2537 {
2538   if (!sym->attr.dummy && !sym->attr.contained
2539         && !(sym->attr.intrinsic
2540               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2541         && sym->attr.proc != PROC_ST_FUNCTION
2542         && !sym->attr.proc_pointer
2543         && !sym->attr.use_assoc
2544         && sym->name)
2545     return true;
2546
2547   return false;
2548 }
2549
2550
2551 /* Figure out if a function reference is pure or not.  Also set the name
2552    of the function for a potential error message.  Return nonzero if the
2553    function is PURE, zero if not.  */
2554 static int
2555 pure_stmt_function (gfc_expr *, gfc_symbol *);
2556
2557 static int
2558 pure_function (gfc_expr *e, const char **name)
2559 {
2560   int pure;
2561
2562   *name = NULL;
2563
2564   if (e->symtree != NULL
2565         && e->symtree->n.sym != NULL
2566         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2567     return pure_stmt_function (e, e->symtree->n.sym);
2568
2569   if (e->value.function.esym)
2570     {
2571       pure = gfc_pure (e->value.function.esym);
2572       *name = e->value.function.esym->name;
2573     }
2574   else if (e->value.function.isym)
2575     {
2576       pure = e->value.function.isym->pure
2577              || e->value.function.isym->elemental;
2578       *name = e->value.function.isym->name;
2579     }
2580   else
2581     {
2582       /* Implicit functions are not pure.  */
2583       pure = 0;
2584       *name = e->value.function.name;
2585     }
2586
2587   return pure;
2588 }
2589
2590
2591 static bool
2592 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2593                  int *f ATTRIBUTE_UNUSED)
2594 {
2595   const char *name;
2596
2597   /* Don't bother recursing into other statement functions
2598      since they will be checked individually for purity.  */
2599   if (e->expr_type != EXPR_FUNCTION
2600         || !e->symtree
2601         || e->symtree->n.sym == sym
2602         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2603     return false;
2604
2605   return pure_function (e, &name) ? false : true;
2606 }
2607
2608
2609 static int
2610 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2611 {
2612   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2613 }
2614
2615
2616 static gfc_try
2617 is_scalar_expr_ptr (gfc_expr *expr)
2618 {
2619   gfc_try retval = SUCCESS;
2620   gfc_ref *ref;
2621   int start;
2622   int end;
2623
2624   /* See if we have a gfc_ref, which means we have a substring, array
2625      reference, or a component.  */
2626   if (expr->ref != NULL)
2627     {
2628       ref = expr->ref;
2629       while (ref->next != NULL)
2630         ref = ref->next;
2631
2632       switch (ref->type)
2633         {
2634         case REF_SUBSTRING:
2635           if (ref->u.ss.start == NULL || ref->u.ss.end == NULL
2636               || gfc_dep_compare_expr (ref->u.ss.start, ref->u.ss.end) != 0)
2637             retval = FAILURE;
2638           break;
2639
2640         case REF_ARRAY:
2641           if (ref->u.ar.type == AR_ELEMENT)
2642             retval = SUCCESS;
2643           else if (ref->u.ar.type == AR_FULL)
2644             {
2645               /* The user can give a full array if the array is of size 1.  */
2646               if (ref->u.ar.as != NULL
2647                   && ref->u.ar.as->rank == 1
2648                   && ref->u.ar.as->type == AS_EXPLICIT
2649                   && ref->u.ar.as->lower[0] != NULL
2650                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2651                   && ref->u.ar.as->upper[0] != NULL
2652                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2653                 {
2654                   /* If we have a character string, we need to check if
2655                      its length is one.  */
2656                   if (expr->ts.type == BT_CHARACTER)
2657                     {
2658                       if (expr->ts.u.cl == NULL
2659                           || expr->ts.u.cl->length == NULL
2660                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2661                           != 0)
2662                         retval = FAILURE;
2663                     }
2664                   else
2665                     {
2666                       /* We have constant lower and upper bounds.  If the
2667                          difference between is 1, it can be considered a
2668                          scalar.  
2669                          FIXME: Use gfc_dep_compare_expr instead.  */
2670                       start = (int) mpz_get_si
2671                                 (ref->u.ar.as->lower[0]->value.integer);
2672                       end = (int) mpz_get_si
2673                                 (ref->u.ar.as->upper[0]->value.integer);
2674                       if (end - start + 1 != 1)
2675                         retval = FAILURE;
2676                    }
2677                 }
2678               else
2679                 retval = FAILURE;
2680             }
2681           else
2682             retval = FAILURE;
2683           break;
2684         default:
2685           retval = SUCCESS;
2686           break;
2687         }
2688     }
2689   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2690     {
2691       /* Character string.  Make sure it's of length 1.  */
2692       if (expr->ts.u.cl == NULL
2693           || expr->ts.u.cl->length == NULL
2694           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2695         retval = FAILURE;
2696     }
2697   else if (expr->rank != 0)
2698     retval = FAILURE;
2699
2700   return retval;
2701 }
2702
2703
2704 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2705    and, in the case of c_associated, set the binding label based on
2706    the arguments.  */
2707
2708 static gfc_try
2709 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2710                           gfc_symbol **new_sym)
2711 {
2712   char name[GFC_MAX_SYMBOL_LEN + 1];
2713   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2714   int optional_arg = 0;
2715   gfc_try retval = SUCCESS;
2716   gfc_symbol *args_sym;
2717   gfc_typespec *arg_ts;
2718   symbol_attribute arg_attr;
2719
2720   if (args->expr->expr_type == EXPR_CONSTANT
2721       || args->expr->expr_type == EXPR_OP
2722       || args->expr->expr_type == EXPR_NULL)
2723     {
2724       gfc_error ("Argument to '%s' at %L is not a variable",
2725                  sym->name, &(args->expr->where));
2726       return FAILURE;
2727     }
2728
2729   args_sym = args->expr->symtree->n.sym;
2730
2731   /* The typespec for the actual arg should be that stored in the expr
2732      and not necessarily that of the expr symbol (args_sym), because
2733      the actual expression could be a part-ref of the expr symbol.  */
2734   arg_ts = &(args->expr->ts);
2735   arg_attr = gfc_expr_attr (args->expr);
2736     
2737   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2738     {
2739       /* If the user gave two args then they are providing something for
2740          the optional arg (the second cptr).  Therefore, set the name and
2741          binding label to the c_associated for two cptrs.  Otherwise,
2742          set c_associated to expect one cptr.  */
2743       if (args->next)
2744         {
2745           /* two args.  */
2746           sprintf (name, "%s_2", sym->name);
2747           sprintf (binding_label, "%s_2", sym->binding_label);
2748           optional_arg = 1;
2749         }
2750       else
2751         {
2752           /* one arg.  */
2753           sprintf (name, "%s_1", sym->name);
2754           sprintf (binding_label, "%s_1", sym->binding_label);
2755           optional_arg = 0;
2756         }
2757
2758       /* Get a new symbol for the version of c_associated that
2759          will get called.  */
2760       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2761     }
2762   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2763            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2764     {
2765       sprintf (name, "%s", sym->name);
2766       sprintf (binding_label, "%s", sym->binding_label);
2767
2768       /* Error check the call.  */
2769       if (args->next != NULL)
2770         {
2771           gfc_error_now ("More actual than formal arguments in '%s' "
2772                          "call at %L", name, &(args->expr->where));
2773           retval = FAILURE;
2774         }
2775       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2776         {
2777           gfc_ref *ref;
2778           bool seen_section;
2779
2780           /* Make sure we have either the target or pointer attribute.  */
2781           if (!arg_attr.target && !arg_attr.pointer)
2782             {
2783               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2784                              "a TARGET or an associated pointer",
2785                              args_sym->name,
2786                              sym->name, &(args->expr->where));
2787               retval = FAILURE;
2788             }
2789
2790           if (gfc_is_coindexed (args->expr))
2791             {
2792               gfc_error_now ("Coindexed argument not permitted"
2793                              " in '%s' call at %L", name,
2794                              &(args->expr->where));
2795               retval = FAILURE;
2796             }
2797
2798           /* Follow references to make sure there are no array
2799              sections.  */
2800           seen_section = false;
2801
2802           for (ref=args->expr->ref; ref; ref = ref->next)
2803             {
2804               if (ref->type == REF_ARRAY)
2805                 {
2806                   if (ref->u.ar.type == AR_SECTION)
2807                     seen_section = true;
2808
2809                   if (ref->u.ar.type != AR_ELEMENT)
2810                     {
2811                       gfc_ref *r;
2812                       for (r = ref->next; r; r=r->next)
2813                         if (r->type == REF_COMPONENT)
2814                           {
2815                             gfc_error_now ("Array section not permitted"
2816                                            " in '%s' call at %L", name,
2817                                            &(args->expr->where));
2818                             retval = FAILURE;
2819                             break;
2820                           }
2821                     }
2822                 }
2823             }
2824
2825           if (seen_section && retval == SUCCESS)
2826             gfc_warning ("Array section in '%s' call at %L", name,
2827                          &(args->expr->where));
2828                          
2829           /* See if we have interoperable type and type param.  */
2830           if (gfc_verify_c_interop (arg_ts) == SUCCESS
2831               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2832             {
2833               if (args_sym->attr.target == 1)
2834                 {
2835                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2836                      has the target attribute and is interoperable.  */
2837                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2838                      allocatable variable that has the TARGET attribute and
2839                      is not an array of zero size.  */
2840                   if (args_sym->attr.allocatable == 1)
2841                     {
2842                       if (args_sym->attr.dimension != 0 
2843                           && (args_sym->as && args_sym->as->rank == 0))
2844                         {
2845                           gfc_error_now ("Allocatable variable '%s' used as a "
2846                                          "parameter to '%s' at %L must not be "
2847                                          "an array of zero size",
2848                                          args_sym->name, sym->name,
2849                                          &(args->expr->where));
2850                           retval = FAILURE;
2851                         }
2852                     }
2853                   else
2854                     {
2855                       /* A non-allocatable target variable with C
2856                          interoperable type and type parameters must be
2857                          interoperable.  */
2858                       if (args_sym && args_sym->attr.dimension)
2859                         {
2860                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2861                             {
2862                               gfc_error ("Assumed-shape array '%s' at %L "
2863                                          "cannot be an argument to the "
2864                                          "procedure '%s' because "
2865                                          "it is not C interoperable",
2866                                          args_sym->name,
2867                                          &(args->expr->where), sym->name);
2868                               retval = FAILURE;
2869                             }
2870                           else if (args_sym->as->type == AS_DEFERRED)
2871                             {
2872                               gfc_error ("Deferred-shape array '%s' at %L "
2873                                          "cannot be an argument to the "
2874                                          "procedure '%s' because "
2875                                          "it is not C interoperable",
2876                                          args_sym->name,
2877                                          &(args->expr->where), sym->name);
2878                               retval = FAILURE;
2879                             }
2880                         }
2881                               
2882                       /* Make sure it's not a character string.  Arrays of
2883                          any type should be ok if the variable is of a C
2884                          interoperable type.  */
2885                       if (arg_ts->type == BT_CHARACTER)
2886                         if (arg_ts->u.cl != NULL
2887                             && (arg_ts->u.cl->length == NULL
2888                                 || arg_ts->u.cl->length->expr_type
2889                                    != EXPR_CONSTANT
2890                                 || mpz_cmp_si
2891                                     (arg_ts->u.cl->length->value.integer, 1)
2892                                    != 0)
2893                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2894                           {
2895                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2896                                            "at %L must have a length of 1",
2897                                            args_sym->name, sym->name,
2898                                            &(args->expr->where));
2899                             retval = FAILURE;
2900                           }
2901                     }
2902                 }
2903               else if (arg_attr.pointer
2904                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2905                 {
2906                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2907                      scalar pointer.  */
2908                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2909                                  "associated scalar POINTER", args_sym->name,
2910                                  sym->name, &(args->expr->where));
2911                   retval = FAILURE;
2912                 }
2913             }
2914           else
2915             {
2916               /* The parameter is not required to be C interoperable.  If it
2917                  is not C interoperable, it must be a nonpolymorphic scalar
2918                  with no length type parameters.  It still must have either
2919                  the pointer or target attribute, and it can be
2920                  allocatable (but must be allocated when c_loc is called).  */
2921               if (args->expr->rank != 0 
2922                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2923                 {
2924                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2925                                  "scalar", args_sym->name, sym->name,
2926                                  &(args->expr->where));
2927                   retval = FAILURE;
2928                 }
2929               else if (arg_ts->type == BT_CHARACTER 
2930                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2931                 {
2932                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2933                                  "%L must have a length of 1",
2934                                  args_sym->name, sym->name,
2935                                  &(args->expr->where));
2936                   retval = FAILURE;
2937                 }
2938               else if (arg_ts->type == BT_CLASS)
2939                 {
2940                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
2941                                  "polymorphic", args_sym->name, sym->name,
2942                                  &(args->expr->where));
2943                   retval = FAILURE;
2944                 }
2945             }
2946         }
2947       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2948         {
2949           if (args_sym->attr.flavor != FL_PROCEDURE)
2950             {
2951               /* TODO: Update this error message to allow for procedure
2952                  pointers once they are implemented.  */
2953               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2954                              "procedure",
2955                              args_sym->name, sym->name,
2956                              &(args->expr->where));
2957               retval = FAILURE;
2958             }
2959           else if (args_sym->attr.is_bind_c != 1)
2960             {
2961               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2962                              "BIND(C)",
2963                              args_sym->name, sym->name,
2964                              &(args->expr->where));
2965               retval = FAILURE;
2966             }
2967         }
2968       
2969       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2970       *new_sym = sym;
2971     }
2972   else
2973     {
2974       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2975                           "iso_c_binding function: '%s'!\n", sym->name);
2976     }
2977
2978   return retval;
2979 }
2980
2981
2982 /* Resolve a function call, which means resolving the arguments, then figuring
2983    out which entity the name refers to.  */
2984
2985 static gfc_try
2986 resolve_function (gfc_expr *expr)
2987 {
2988   gfc_actual_arglist *arg;
2989   gfc_symbol *sym;
2990   const char *name;
2991   gfc_try t;
2992   int temp;
2993   procedure_type p = PROC_INTRINSIC;
2994   bool no_formal_args;
2995
2996   sym = NULL;
2997   if (expr->symtree)
2998     sym = expr->symtree->n.sym;
2999
3000   /* If this is a procedure pointer component, it has already been resolved.  */
3001   if (gfc_is_proc_ptr_comp (expr, NULL))
3002     return SUCCESS;
3003   
3004   if (sym && sym->attr.intrinsic
3005       && resolve_intrinsic (sym, &expr->where) == FAILURE)
3006     return FAILURE;
3007
3008   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
3009     {
3010       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
3011       return FAILURE;
3012     }
3013
3014   /* If this ia a deferred TBP with an abstract interface (which may
3015      of course be referenced), expr->value.function.esym will be set.  */
3016   if (sym && sym->attr.abstract && !expr->value.function.esym)
3017     {
3018       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3019                  sym->name, &expr->where);
3020       return FAILURE;
3021     }
3022
3023   /* Switch off assumed size checking and do this again for certain kinds
3024      of procedure, once the procedure itself is resolved.  */
3025   need_full_assumed_size++;
3026
3027   if (expr->symtree && expr->symtree->n.sym)
3028     p = expr->symtree->n.sym->attr.proc;
3029
3030   if (expr->value.function.isym && expr->value.function.isym->inquiry)
3031     inquiry_argument = true;
3032   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
3033
3034   if (resolve_actual_arglist (expr->value.function.actual,
3035                               p, no_formal_args) == FAILURE)
3036     {
3037       inquiry_argument = false;
3038       return FAILURE;
3039     }
3040
3041   inquiry_argument = false;
3042  
3043   /* Need to setup the call to the correct c_associated, depending on
3044      the number of cptrs to user gives to compare.  */
3045   if (sym && sym->attr.is_iso_c == 1)
3046     {
3047       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
3048           == FAILURE)
3049         return FAILURE;
3050       
3051       /* Get the symtree for the new symbol (resolved func).
3052          the old one will be freed later, when it's no longer used.  */
3053       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
3054     }
3055   
3056   /* Resume assumed_size checking.  */
3057   need_full_assumed_size--;
3058
3059   /* If the procedure is external, check for usage.  */
3060   if (sym && is_external_proc (sym))
3061     resolve_global_procedure (sym, &expr->where,
3062                               &expr->value.function.actual, 0);
3063
3064   if (sym && sym->ts.type == BT_CHARACTER
3065       && sym->ts.u.cl
3066       && sym->ts.u.cl->length == NULL
3067       && !sym->attr.dummy
3068       && !sym->ts.deferred
3069       && expr->value.function.esym == NULL
3070       && !sym->attr.contained)
3071     {
3072       /* Internal procedures are taken care of in resolve_contained_fntype.  */
3073       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
3074                  "be used at %L since it is not a dummy argument",
3075                  sym->name, &expr->where);
3076       return FAILURE;
3077     }
3078
3079   /* See if function is already resolved.  */
3080
3081   if (expr->value.function.name != NULL)
3082     {
3083       if (expr->ts.type == BT_UNKNOWN)
3084         expr->ts = sym->ts;
3085       t = SUCCESS;
3086     }
3087   else
3088     {
3089       /* Apply the rules of section 14.1.2.  */
3090
3091       switch (procedure_kind (sym))
3092         {
3093         case PTYPE_GENERIC:
3094           t = resolve_generic_f (expr);
3095           break;
3096
3097         case PTYPE_SPECIFIC:
3098           t = resolve_specific_f (expr);
3099           break;
3100
3101         case PTYPE_UNKNOWN:
3102           t = resolve_unknown_f (expr);
3103           break;
3104
3105         default:
3106           gfc_internal_error ("resolve_function(): bad function type");
3107         }
3108     }
3109
3110   /* If the expression is still a function (it might have simplified),
3111      then we check to see if we are calling an elemental function.  */
3112
3113   if (expr->expr_type != EXPR_FUNCTION)
3114     return t;
3115
3116   temp = need_full_assumed_size;
3117   need_full_assumed_size = 0;
3118
3119   if (resolve_elemental_actual (expr, NULL) == FAILURE)
3120     return FAILURE;
3121
3122   if (omp_workshare_flag
3123       && expr->value.function.esym
3124       && ! gfc_elemental (expr->value.function.esym))
3125     {
3126       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
3127                  "in WORKSHARE construct", expr->value.function.esym->name,
3128                  &expr->where);
3129       t = FAILURE;
3130     }
3131
3132 #define GENERIC_ID expr->value.function.isym->id
3133   else if (expr->value.function.actual != NULL
3134            && expr->value.function.isym != NULL
3135            && GENERIC_ID != GFC_ISYM_LBOUND
3136            && GENERIC_ID != GFC_ISYM_LEN
3137            && GENERIC_ID != GFC_ISYM_LOC
3138            && GENERIC_ID != GFC_ISYM_PRESENT)
3139     {
3140       /* Array intrinsics must also have the last upper bound of an
3141          assumed size array argument.  UBOUND and SIZE have to be
3142          excluded from the check if the second argument is anything
3143          than a constant.  */
3144
3145       for (arg = expr->value.function.actual; arg; arg = arg->next)
3146         {
3147           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3148               && arg->next != NULL && arg->next->expr)
3149             {
3150               if (arg->next->expr->expr_type != EXPR_CONSTANT)
3151                 break;
3152
3153               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
3154                 break;
3155
3156               if ((int)mpz_get_si (arg->next->expr->value.integer)
3157                         < arg->expr->rank)
3158                 break;
3159             }
3160
3161           if (arg->expr != NULL
3162               && arg->expr->rank > 0
3163               && resolve_assumed_size_actual (arg->expr))
3164             return FAILURE;
3165         }
3166     }
3167 #undef GENERIC_ID
3168
3169   need_full_assumed_size = temp;
3170   name = NULL;
3171
3172   if (!pure_function (expr, &name) && name)
3173     {
3174       if (forall_flag)
3175         {
3176           gfc_error ("Reference to non-PURE function '%s' at %L inside a "
3177                      "FORALL %s", name, &expr->where,
3178                      forall_flag == 2 ? "mask" : "block");
3179           t = FAILURE;
3180         }
3181       else if (do_concurrent_flag)
3182         {
3183           gfc_error ("Reference to non-PURE function '%s' at %L inside a "
3184                      "DO CONCURRENT %s", name, &expr->where,
3185                      do_concurrent_flag == 2 ? "mask" : "block");
3186           t = FAILURE;
3187         }
3188       else if (gfc_pure (NULL))
3189         {
3190           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
3191                      "procedure within a PURE procedure", name, &expr->where);
3192           t = FAILURE;
3193         }
3194
3195       if (gfc_implicit_pure (NULL))
3196         gfc_current_ns->proc_name->attr.implicit_pure = 0;
3197     }
3198
3199   /* Functions without the RECURSIVE attribution are not allowed to
3200    * call themselves.  */
3201   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3202     {
3203       gfc_symbol *esym;
3204       esym = expr->value.function.esym;
3205
3206       if (is_illegal_recursion (esym, gfc_current_ns))
3207       {
3208         if (esym->attr.entry && esym->ns->entries)
3209           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3210                      " function '%s' is not RECURSIVE",
3211                      esym->name, &expr->where, esym->ns->entries->sym->name);
3212         else
3213           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
3214                      " is not RECURSIVE", esym->name, &expr->where);
3215
3216         t = FAILURE;
3217       }
3218     }
3219
3220   /* Character lengths of use associated functions may contains references to
3221      symbols not referenced from the current program unit otherwise.  Make sure
3222      those symbols are marked as referenced.  */
3223
3224   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3225       && expr->value.function.esym->attr.use_assoc)
3226     {
3227       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3228     }
3229
3230   /* Make sure that the expression has a typespec that works.  */
3231   if (expr->ts.type == BT_UNKNOWN)
3232     {
3233       if (expr->symtree->n.sym->result
3234             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3235             && !expr->symtree->n.sym->result->attr.proc_pointer)
3236         expr->ts = expr->symtree->n.sym->result->ts;
3237     }
3238
3239   return t;
3240 }
3241
3242
3243 /************* Subroutine resolution *************/
3244
3245 static void
3246 pure_subroutine (gfc_code *c, gfc_symbol *sym)
3247 {
3248   if (gfc_pure (sym))
3249     return;
3250
3251   if (forall_flag)
3252     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
3253                sym->name, &c->loc);
3254   else if (do_concurrent_flag)
3255     gfc_error ("Subroutine call to '%s' in DO CONCURRENT block at %L is not "
3256                "PURE", sym->name, &c->loc);
3257   else if (gfc_pure (NULL))
3258     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
3259                &c->loc);
3260
3261   if (gfc_implicit_pure (NULL))
3262     gfc_current_ns->proc_name->attr.implicit_pure = 0;
3263 }
3264
3265
3266 static match
3267 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3268 {
3269   gfc_symbol *s;
3270
3271   if (sym->attr.generic)
3272     {
3273       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3274       if (s != NULL)
3275         {
3276           c->resolved_sym = s;
3277           pure_subroutine (c, s);
3278           return MATCH_YES;
3279         }
3280
3281       /* TODO: Need to search for elemental references in generic interface.  */
3282     }
3283
3284   if (sym->attr.intrinsic)
3285     return gfc_intrinsic_sub_interface (c, 0);
3286
3287   return MATCH_NO;
3288 }
3289
3290
3291 static gfc_try
3292 resolve_generic_s (gfc_code *c)
3293 {
3294   gfc_symbol *sym;
3295   match m;
3296
3297   sym = c->symtree->n.sym;
3298
3299   for (;;)
3300     {
3301       m = resolve_generic_s0 (c, sym);
3302       if (m == MATCH_YES)
3303         return SUCCESS;
3304       else if (m == MATCH_ERROR)
3305         return FAILURE;
3306
3307 generic:
3308       if (sym->ns->parent == NULL)
3309         break;
3310       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3311
3312       if (sym == NULL)
3313         break;
3314       if (!generic_sym (sym))
3315         goto generic;
3316     }
3317
3318   /* Last ditch attempt.  See if the reference is to an intrinsic
3319      that possesses a matching interface.  14.1.2.4  */
3320   sym = c->symtree->n.sym;
3321
3322   if (!gfc_is_intrinsic (sym, 1, c->loc))
3323     {
3324       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3325                  sym->name, &c->loc);
3326       return FAILURE;
3327     }
3328
3329   m = gfc_intrinsic_sub_interface (c, 0);
3330   if (m == MATCH_YES)
3331     return SUCCESS;
3332   if (m == MATCH_NO)
3333     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3334                "intrinsic subroutine interface", sym->name, &c->loc);
3335
3336   return FAILURE;
3337 }
3338
3339
3340 /* Set the name and binding label of the subroutine symbol in the call
3341    expression represented by 'c' to include the type and kind of the
3342    second parameter.  This function is for resolving the appropriate
3343    version of c_f_pointer() and c_f_procpointer().  For example, a
3344    call to c_f_pointer() for a default integer pointer could have a
3345    name of c_f_pointer_i4.  If no second arg exists, which is an error
3346    for these two functions, it defaults to the generic symbol's name
3347    and binding label.  */
3348
3349 static void
3350 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3351                     char *name, char *binding_label)
3352 {
3353   gfc_expr *arg = NULL;
3354   char type;
3355   int kind;
3356
3357   /* The second arg of c_f_pointer and c_f_procpointer determines
3358      the type and kind for the procedure name.  */
3359   arg = c->ext.actual->next->expr;
3360
3361   if (arg != NULL)
3362     {
3363       /* Set up the name to have the given symbol's name,
3364          plus the type and kind.  */
3365       /* a derived type is marked with the type letter 'u' */
3366       if (arg->ts.type == BT_DERIVED)
3367         {
3368           type = 'd';
3369           kind = 0; /* set the kind as 0 for now */
3370         }
3371       else
3372         {
3373           type = gfc_type_letter (arg->ts.type);
3374           kind = arg->ts.kind;
3375         }
3376
3377       if (arg->ts.type == BT_CHARACTER)
3378         /* Kind info for character strings not needed.  */
3379         kind = 0;
3380
3381       sprintf (name, "%s_%c%d", sym->name, type, kind);
3382       /* Set up the binding label as the given symbol's label plus
3383          the type and kind.  */
3384       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
3385     }
3386   else
3387     {
3388       /* If the second arg is missing, set the name and label as
3389          was, cause it should at least be found, and the missing
3390          arg error will be caught by compare_parameters().  */
3391       sprintf (name, "%s", sym->name);
3392       sprintf (binding_label, "%s", sym->binding_label);
3393     }
3394    
3395   return;
3396 }
3397
3398
3399 /* Resolve a generic version of the iso_c_binding procedure given
3400    (sym) to the specific one based on the type and kind of the
3401    argument(s).  Currently, this function resolves c_f_pointer() and
3402    c_f_procpointer based on the type and kind of the second argument
3403    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3404    Upon successfully exiting, c->resolved_sym will hold the resolved
3405    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3406    otherwise.  */
3407
3408 match
3409 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3410 {
3411   gfc_symbol *new_sym;
3412   /* this is fine, since we know the names won't use the max */
3413   char name[GFC_MAX_SYMBOL_LEN + 1];
3414   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3415   /* default to success; will override if find error */
3416   match m = MATCH_YES;
3417
3418   /* Make sure the actual arguments are in the necessary order (based on the 
3419      formal args) before resolving.  */
3420   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3421
3422   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3423       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3424     {
3425       set_name_and_label (c, sym, name, binding_label);
3426       
3427       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3428         {
3429           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3430             {
3431               /* Make sure we got a third arg if the second arg has non-zero
3432                  rank.  We must also check that the type and rank are
3433                  correct since we short-circuit this check in
3434                  gfc_procedure_use() (called above to sort actual args).  */
3435               if (c->ext.actual->next->expr->rank != 0)
3436                 {
3437                   if(c->ext.actual->next->next == NULL 
3438                      || c->ext.actual->next->next->expr == NULL)
3439                     {
3440                       m = MATCH_ERROR;
3441                       gfc_error ("Missing SHAPE parameter for call to %s "
3442                                  "at %L", sym->name, &(c->loc));
3443                     }
3444                   else if (c->ext.actual->next->next->expr->ts.type
3445                            != BT_INTEGER
3446                            || c->ext.actual->next->next->expr->rank != 1)
3447                     {
3448                       m = MATCH_ERROR;
3449                       gfc_error ("SHAPE parameter for call to %s at %L must "
3450                                  "be a rank 1 INTEGER array", sym->name,
3451                                  &(c->loc));
3452                     }
3453                 }
3454             }
3455         }
3456       
3457       if (m != MATCH_ERROR)
3458         {
3459           /* the 1 means to add the optional arg to formal list */
3460           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3461          
3462           /* for error reporting, say it's declared where the original was */
3463           new_sym->declared_at = sym->declared_at;
3464         }
3465     }
3466   else
3467     {
3468       /* no differences for c_loc or c_funloc */
3469       new_sym = sym;
3470     }
3471
3472   /* set the resolved symbol */
3473   if (m != MATCH_ERROR)
3474     c->resolved_sym = new_sym;
3475   else
3476     c->resolved_sym = sym;
3477   
3478   return m;
3479 }
3480
3481
3482 /* Resolve a subroutine call known to be specific.  */
3483
3484 static match
3485 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3486 {
3487   match m;
3488
3489   if(sym->attr.is_iso_c)
3490     {
3491       m = gfc_iso_c_sub_interface (c,sym);
3492       return m;
3493     }
3494   
3495   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3496     {
3497       if (sym->attr.dummy)
3498         {
3499           sym->attr.proc = PROC_DUMMY;
3500           goto found;
3501         }
3502
3503       sym->attr.proc = PROC_EXTERNAL;
3504       goto found;
3505     }
3506
3507   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3508     goto found;
3509
3510   if (sym->attr.intrinsic)
3511     {
3512       m = gfc_intrinsic_sub_interface (c, 1);
3513       if (m == MATCH_YES)
3514         return MATCH_YES;
3515       if (m == MATCH_NO)
3516         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3517                    "with an intrinsic", sym->name, &c->loc);
3518
3519       return MATCH_ERROR;
3520     }
3521
3522   return MATCH_NO;
3523
3524 found:
3525   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3526
3527   c->resolved_sym = sym;
3528   pure_subroutine (c, sym);
3529
3530   return MATCH_YES;
3531 }
3532
3533
3534 static gfc_try
3535 resolve_specific_s (gfc_code *c)
3536 {
3537   gfc_symbol *sym;
3538   match m;
3539
3540   sym = c->symtree->n.sym;
3541
3542   for (;;)
3543     {
3544       m = resolve_specific_s0 (c, sym);
3545       if (m == MATCH_YES)
3546         return SUCCESS;
3547       if (m == MATCH_ERROR)
3548         return FAILURE;
3549
3550       if (sym->ns->parent == NULL)
3551         break;
3552
3553       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3554
3555       if (sym == NULL)
3556         break;
3557     }
3558
3559   sym = c->symtree->n.sym;
3560   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3561              sym->name, &c->loc);
3562
3563   return FAILURE;
3564 }
3565
3566
3567 /* Resolve a subroutine call not known to be generic nor specific.  */
3568
3569 static gfc_try
3570 resolve_unknown_s (gfc_code *c)
3571 {
3572   gfc_symbol *sym;
3573
3574   sym = c->symtree->n.sym;
3575
3576   if (sym->attr.dummy)
3577     {
3578       sym->attr.proc = PROC_DUMMY;
3579       goto found;
3580     }
3581
3582   /* See if we have an intrinsic function reference.  */
3583
3584   if (gfc_is_intrinsic (sym, 1, c->loc))
3585     {
3586       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3587         return SUCCESS;
3588       return FAILURE;
3589     }
3590
3591   /* The reference is to an external name.  */
3592
3593 found:
3594   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3595
3596   c->resolved_sym = sym;
3597
3598   pure_subroutine (c, sym);
3599
3600   return SUCCESS;
3601 }
3602
3603
3604 /* Resolve a subroutine call.  Although it was tempting to use the same code
3605    for functions, subroutines and functions are stored differently and this
3606    makes things awkward.  */
3607
3608 static gfc_try
3609 resolve_call (gfc_code *c)
3610 {
3611   gfc_try t;
3612   procedure_type ptype = PROC_INTRINSIC;
3613   gfc_symbol *csym, *sym;
3614   bool no_formal_args;
3615
3616   csym = c->symtree ? c->symtree->n.sym : NULL;
3617
3618   if (csym && csym->ts.type != BT_UNKNOWN)
3619     {
3620       gfc_error ("'%s' at %L has a type, which is not consistent with "
3621                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3622       return FAILURE;
3623     }
3624
3625   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3626     {
3627       gfc_symtree *st;
3628       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3629       sym = st ? st->n.sym : NULL;
3630       if (sym && csym != sym
3631               && sym->ns == gfc_current_ns
3632               && sym->attr.flavor == FL_PROCEDURE
3633               && sym->attr.contained)
3634         {
3635           sym->refs++;
3636           if (csym->attr.generic)
3637             c->symtree->n.sym = sym;
3638           else
3639             c->symtree = st;
3640           csym = c->symtree->n.sym;
3641         }
3642     }
3643
3644   /* If this ia a deferred TBP with an abstract interface
3645      (which may of course be referenced), c->expr1 will be set.  */
3646   if (csym && csym->attr.abstract && !c->expr1)
3647     {
3648       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3649                  csym->name, &c->loc);
3650       return FAILURE;
3651     }
3652
3653   /* Subroutines without the RECURSIVE attribution are not allowed to
3654    * call themselves.  */
3655   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3656     {
3657       if (csym->attr.entry && csym->ns->entries)
3658         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3659                    " subroutine '%s' is not RECURSIVE",
3660                    csym->name, &c->loc, csym->ns->entries->sym->name);
3661       else
3662         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3663                    " is not RECURSIVE", csym->name, &c->loc);
3664
3665       t = FAILURE;
3666     }
3667
3668   /* Switch off assumed size checking and do this again for certain kinds
3669      of procedure, once the procedure itself is resolved.  */
3670   need_full_assumed_size++;
3671
3672   if (csym)
3673     ptype = csym->attr.proc;
3674
3675   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3676   if (resolve_actual_arglist (c->ext.actual, ptype,
3677                               no_formal_args) == FAILURE)
3678     return FAILURE;
3679
3680   /* Resume assumed_size checking.  */
3681   need_full_assumed_size--;
3682
3683   /* If external, check for usage.  */
3684   if (csym && is_external_proc (csym))
3685     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3686
3687   t = SUCCESS;
3688   if (c->resolved_sym == NULL)
3689     {
3690       c->resolved_isym = NULL;
3691       switch (procedure_kind (csym))
3692         {
3693         case PTYPE_GENERIC:
3694           t = resolve_generic_s (c);
3695           break;
3696
3697         case PTYPE_SPECIFIC:
3698           t = resolve_specific_s (c);
3699           break;
3700
3701         case PTYPE_UNKNOWN:
3702           t = resolve_unknown_s (c);
3703           break;
3704
3705         default:
3706           gfc_internal_error ("resolve_subroutine(): bad function type");
3707         }
3708     }
3709
3710   /* Some checks of elemental subroutine actual arguments.  */
3711   if (resolve_elemental_actual (NULL, c) == FAILURE)
3712     return FAILURE;
3713
3714   return t;
3715 }
3716
3717
3718 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3719    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3720    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3721    if their shapes do not match.  If either op1->shape or op2->shape is
3722    NULL, return SUCCESS.  */
3723
3724 static gfc_try
3725 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3726 {
3727   gfc_try t;
3728   int i;
3729
3730   t = SUCCESS;
3731
3732   if (op1->shape != NULL && op2->shape != NULL)
3733     {
3734       for (i = 0; i < op1->rank; i++)
3735         {
3736           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3737            {
3738              gfc_error ("Shapes for operands at %L and %L are not conformable",
3739                          &op1->where, &op2->where);
3740              t = FAILURE;
3741              break;
3742            }
3743         }
3744     }
3745
3746   return t;
3747 }
3748
3749
3750 /* Resolve an operator expression node.  This can involve replacing the
3751    operation with a user defined function call.  */
3752
3753 static gfc_try
3754 resolve_operator (gfc_expr *e)
3755 {
3756   gfc_expr *op1, *op2;
3757   char msg[200];
3758   bool dual_locus_error;
3759   gfc_try t;
3760
3761   /* Resolve all subnodes-- give them types.  */
3762
3763   switch (e->value.op.op)
3764     {
3765     default:
3766       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3767         return FAILURE;
3768
3769     /* Fall through...  */
3770
3771     case INTRINSIC_NOT:
3772     case INTRINSIC_UPLUS:
3773     case INTRINSIC_UMINUS:
3774     case INTRINSIC_PARENTHESES:
3775       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3776         return FAILURE;
3777       break;
3778     }
3779
3780   /* Typecheck the new node.  */
3781
3782   op1 = e->value.op.op1;
3783   op2 = e->value.op.op2;
3784   dual_locus_error = false;
3785
3786   if ((op1 && op1->expr_type == EXPR_NULL)
3787       || (op2 && op2->expr_type == EXPR_NULL))
3788     {
3789       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3790       goto bad_op;
3791     }
3792
3793   switch (e->value.op.op)
3794     {
3795     case INTRINSIC_UPLUS:
3796     case INTRINSIC_UMINUS:
3797       if (op1->ts.type == BT_INTEGER
3798           || op1->ts.type == BT_REAL
3799           || op1->ts.type == BT_COMPLEX)
3800         {
3801           e->ts = op1->ts;
3802           break;
3803         }
3804
3805       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3806                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3807       goto bad_op;
3808
3809     case INTRINSIC_PLUS:
3810     case INTRINSIC_MINUS:
3811     case INTRINSIC_TIMES:
3812     case INTRINSIC_DIVIDE:
3813     case INTRINSIC_POWER:
3814       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3815         {
3816           gfc_type_convert_binary (e, 1);
3817           break;
3818         }
3819
3820       sprintf (msg,
3821                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3822                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3823                gfc_typename (&op2->ts));
3824       goto bad_op;
3825
3826     case INTRINSIC_CONCAT:
3827       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3828           && op1->ts.kind == op2->ts.kind)
3829         {
3830           e->ts.type = BT_CHARACTER;
3831           e->ts.kind = op1->ts.kind;
3832           break;
3833         }
3834
3835       sprintf (msg,
3836                _("Operands of string concatenation operator at %%L are %s/%s"),
3837                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3838       goto bad_op;
3839
3840     case INTRINSIC_AND:
3841     case INTRINSIC_OR:
3842     case INTRINSIC_EQV:
3843     case INTRINSIC_NEQV:
3844       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3845         {
3846           e->ts.type = BT_LOGICAL;
3847           e->ts.kind = gfc_kind_max (op1, op2);
3848           if (op1->ts.kind < e->ts.kind)
3849             gfc_convert_type (op1, &e->ts, 2);
3850           else if (op2->ts.kind < e->ts.kind)
3851             gfc_convert_type (op2, &e->ts, 2);
3852           break;
3853         }
3854
3855       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3856                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3857                gfc_typename (&op2->ts));
3858
3859       goto bad_op;
3860
3861     case INTRINSIC_NOT:
3862       if (op1->ts.type == BT_LOGICAL)
3863         {
3864           e->ts.type = BT_LOGICAL;
3865           e->ts.kind = op1->ts.kind;
3866           break;
3867         }
3868
3869       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3870                gfc_typename (&op1->ts));
3871       goto bad_op;
3872
3873     case INTRINSIC_GT:
3874     case INTRINSIC_GT_OS:
3875     case INTRINSIC_GE:
3876     case INTRINSIC_GE_OS:
3877     case INTRINSIC_LT:
3878     case INTRINSIC_LT_OS:
3879     case INTRINSIC_LE:
3880     case INTRINSIC_LE_OS:
3881       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3882         {
3883           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3884           goto bad_op;
3885         }
3886
3887       /* Fall through...  */
3888
3889     case INTRINSIC_EQ:
3890     case INTRINSIC_EQ_OS:
3891     case INTRINSIC_NE:
3892     case INTRINSIC_NE_OS:
3893       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3894           && op1->ts.kind == op2->ts.kind)
3895         {
3896           e->ts.type = BT_LOGICAL;
3897           e->ts.kind = gfc_default_logical_kind;
3898           break;
3899         }
3900
3901       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3902         {
3903           gfc_type_convert_binary (e, 1);
3904
3905           e->ts.type = BT_LOGICAL;
3906           e->ts.kind = gfc_default_logical_kind;
3907           break;
3908         }
3909
3910       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3911         sprintf (msg,
3912                  _("Logicals at %%L must be compared with %s instead of %s"),
3913                  (e->value.op.op == INTRINSIC_EQ 
3914                   || e->value.op.op == INTRINSIC_EQ_OS)
3915                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3916       else
3917         sprintf (msg,
3918                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3919                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3920                  gfc_typename (&op2->ts));
3921
3922       goto bad_op;
3923
3924     case INTRINSIC_USER:
3925       if (e->value.op.uop->op == NULL)
3926         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3927       else if (op2 == NULL)
3928         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3929                  e->value.op.uop->name, gfc_typename (&op1->ts));
3930       else
3931         {
3932           sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3933                    e->value.op.uop->name, gfc_typename (&op1->ts),
3934                    gfc_typename (&op2->ts));
3935           e->value.op.uop->op->sym->attr.referenced = 1;
3936         }
3937
3938       goto bad_op;
3939
3940     case INTRINSIC_PARENTHESES:
3941       e->ts = op1->ts;
3942       if (e->ts.type == BT_CHARACTER)
3943         e->ts.u.cl = op1->ts.u.cl;
3944       break;
3945
3946     default:
3947       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3948     }
3949
3950   /* Deal with arrayness of an operand through an operator.  */
3951
3952   t = SUCCESS;
3953
3954   switch (e->value.op.op)
3955     {
3956     case INTRINSIC_PLUS:
3957     case INTRINSIC_MINUS:
3958     case INTRINSIC_TIMES:
3959     case INTRINSIC_DIVIDE:
3960     case INTRINSIC_POWER:
3961     case INTRINSIC_CONCAT:
3962     case INTRINSIC_AND:
3963     case INTRINSIC_OR:
3964     case INTRINSIC_EQV:
3965     case INTRINSIC_NEQV:
3966     case INTRINSIC_EQ:
3967     case INTRINSIC_EQ_OS:
3968     case INTRINSIC_NE:
3969     case INTRINSIC_NE_OS:
3970     case INTRINSIC_GT:
3971     case INTRINSIC_GT_OS:
3972     case INTRINSIC_GE:
3973     case INTRINSIC_GE_OS:
3974     case INTRINSIC_LT:
3975     case INTRINSIC_LT_OS:
3976     case INTRINSIC_LE:
3977     case INTRINSIC_LE_OS:
3978
3979       if (op1->rank == 0 && op2->rank == 0)
3980         e->rank = 0;
3981
3982       if (op1->rank == 0 && op2->rank != 0)
3983         {
3984           e->rank = op2->rank;
3985
3986           if (e->shape == NULL)
3987             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3988         }
3989
3990       if (op1->rank != 0 && op2->rank == 0)
3991         {
3992           e->rank = op1->rank;
3993
3994           if (e->shape == NULL)
3995             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3996         }
3997
3998       if (op1->rank != 0 && op2->rank != 0)
3999         {
4000           if (op1->rank == op2->rank)
4001             {
4002               e->rank = op1->rank;
4003               if (e->shape == NULL)
4004                 {
4005                   t = compare_shapes (op1, op2);
4006                   if (t == FAILURE)
4007                     e->shape = NULL;
4008                   else
4009                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
4010                 }
4011             }
4012           else
4013             {
4014               /* Allow higher level expressions to work.  */
4015               e->rank = 0;
4016
4017               /* Try user-defined operators, and otherwise throw an error.  */
4018               dual_locus_error = true;
4019               sprintf (msg,
4020                        _("Inconsistent ranks for operator at %%L and %%L"));
4021               goto bad_op;
4022             }
4023         }
4024
4025       break;
4026
4027     case INTRINSIC_PARENTHESES:
4028     case INTRINSIC_NOT:
4029     case INTRINSIC_UPLUS:
4030     case INTRINSIC_UMINUS:
4031       /* Simply copy arrayness attribute */
4032       e->rank = op1->rank;
4033
4034       if (e->shape == NULL)
4035         e->shape = gfc_copy_shape (op1->shape, op1->rank);
4036
4037       break;
4038
4039     default:
4040       break;
4041     }
4042
4043   /* Attempt to simplify the expression.  */
4044   if (t == SUCCESS)
4045     {
4046       t = gfc_simplify_expr (e, 0);
4047       /* Some calls do not succeed in simplification and return FAILURE
4048          even though there is no error; e.g. variable references to
4049          PARAMETER arrays.  */
4050       if (!gfc_is_constant_expr (e))
4051         t = SUCCESS;
4052     }
4053   return t;
4054
4055 bad_op:
4056
4057   {
4058     match m = gfc_extend_expr (e);
4059     if (m == MATCH_YES)
4060       return SUCCESS;
4061     if (m == MATCH_ERROR)
4062       return FAILURE;
4063   }
4064
4065   if (dual_locus_error)
4066     gfc_error (msg, &op1->where, &op2->where);
4067   else
4068     gfc_error (msg, &e->where);
4069
4070   return FAILURE;
4071 }
4072
4073
4074 /************** Array resolution subroutines **************/
4075
4076 typedef enum
4077 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
4078 comparison;
4079
4080 /* Compare two integer expressions.  */
4081
4082 static comparison
4083 compare_bound (gfc_expr *a, gfc_expr *b)
4084 {
4085   int i;
4086
4087   if (a == NULL || a->expr_type != EXPR_CONSTANT
4088       || b == NULL || b->expr_type != EXPR_CONSTANT)
4089     return CMP_UNKNOWN;
4090
4091   /* If either of the types isn't INTEGER, we must have
4092      raised an error earlier.  */
4093
4094   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
4095     return CMP_UNKNOWN;
4096
4097   i = mpz_cmp (a->value.integer, b->value.integer);
4098
4099   if (i < 0)
4100     return CMP_LT;
4101   if (i > 0)
4102     return CMP_GT;
4103   return CMP_EQ;
4104 }
4105
4106
4107 /* Compare an integer expression with an integer.  */
4108
4109 static comparison
4110 compare_bound_int (gfc_expr *a, int b)
4111 {
4112   int i;
4113
4114   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4115     return CMP_UNKNOWN;
4116
4117   if (a->ts.type != BT_INTEGER)
4118     gfc_internal_error ("compare_bound_int(): Bad expression");
4119
4120   i = mpz_cmp_si (a->value.integer, b);
4121
4122   if (i < 0)
4123     return CMP_LT;
4124   if (i > 0)
4125     return CMP_GT;
4126   return CMP_EQ;
4127 }
4128
4129
4130 /* Compare an integer expression with a mpz_t.  */
4131
4132 static comparison
4133 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
4134 {
4135   int i;
4136
4137   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4138     return CMP_UNKNOWN;
4139
4140   if (a->ts.type != BT_INTEGER)
4141     gfc_internal_error ("compare_bound_int(): Bad expression");
4142
4143   i = mpz_cmp (a->value.integer, b);
4144
4145   if (i < 0)
4146     return CMP_LT;
4147   if (i > 0)
4148     return CMP_GT;
4149   return CMP_EQ;
4150 }
4151
4152
4153 /* Compute the last value of a sequence given by a triplet.  
4154    Return 0 if it wasn't able to compute the last value, or if the
4155    sequence if empty, and 1 otherwise.  */
4156
4157 static int
4158 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
4159                                 gfc_expr *stride, mpz_t last)
4160 {
4161   mpz_t rem;
4162
4163   if (start == NULL || start->expr_type != EXPR_CONSTANT
4164       || end == NULL || end->expr_type != EXPR_CONSTANT
4165       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
4166     return 0;
4167
4168   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
4169       || (stride != NULL && stride->ts.type != BT_INTEGER))
4170     return 0;
4171
4172   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
4173     {
4174       if (compare_bound (start, end) == CMP_GT)
4175         return 0;
4176       mpz_set (last, end->value.integer);
4177       return 1;
4178     }
4179
4180   if (compare_bound_int (stride, 0) == CMP_GT)
4181     {
4182       /* Stride is positive */
4183       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
4184         return 0;
4185     }
4186   else
4187     {
4188       /* Stride is negative */
4189       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
4190         return 0;
4191     }
4192
4193   mpz_init (rem);
4194   mpz_sub (rem, end->value.integer, start->value.integer);
4195   mpz_tdiv_r (rem, rem, stride->value.integer);
4196   mpz_sub (last, end->value.integer, rem);
4197   mpz_clear (rem);
4198
4199   return 1;
4200 }
4201
4202
4203 /* Compare a single dimension of an array reference to the array
4204    specification.  */
4205
4206 static gfc_try
4207 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
4208 {
4209   mpz_t last_value;
4210
4211   if (ar->dimen_type[i] == DIMEN_STAR)
4212     {
4213       gcc_assert (ar->stride[i] == NULL);
4214       /* This implies [*] as [*:] and [*:3] are not possible.  */
4215       if (ar->start[i] == NULL)
4216         {
4217           gcc_assert (ar->end[i] == NULL);
4218           return SUCCESS;
4219         }
4220     }
4221
4222 /* Given start, end and stride values, calculate the minimum and
4223    maximum referenced indexes.  */
4224
4225   switch (ar->dimen_type[i])
4226     {
4227     case DIMEN_VECTOR:
4228     case DIMEN_THIS_IMAGE:
4229       break;
4230
4231     case DIMEN_STAR:
4232     case DIMEN_ELEMENT:
4233       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4234         {
4235           if (i < as->rank)
4236             gfc_warning ("Array reference at %L is out of bounds "
4237                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
4238                          mpz_get_si (ar->start[i]->value.integer),
4239                          mpz_get_si (as->lower[i]->value.integer), i+1);
4240           else
4241             gfc_warning ("Array reference at %L is out of bounds "
4242                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
4243                          mpz_get_si (ar->start[i]->value.integer),
4244                          mpz_get_si (as->lower[i]->value.integer),
4245                          i + 1 - as->rank);
4246           return SUCCESS;
4247         }
4248       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4249         {
4250           if (i < as->rank)
4251             gfc_warning ("Array reference at %L is out of bounds "
4252                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
4253                          mpz_get_si (ar->start[i]->value.integer),
4254                          mpz_get_si (as->upper[i]->value.integer), i+1);
4255           else
4256             gfc_warning ("Array reference at %L is out of bounds "
4257                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
4258                          mpz_get_si (ar->start[i]->value.integer),
4259                          mpz_get_si (as->upper[i]->value.integer),
4260                          i + 1 - as->rank);
4261           return SUCCESS;
4262         }
4263
4264       break;
4265
4266     case DIMEN_RANGE:
4267       {
4268 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4269 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4270
4271         comparison comp_start_end = compare_bound (AR_START, AR_END);
4272
4273         /* Check for zero stride, which is not allowed.  */
4274         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4275           {
4276             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4277             return FAILURE;
4278           }
4279
4280         /* if start == len || (stride > 0 && start < len)
4281                            || (stride < 0 && start > len),
4282            then the array section contains at least one element.  In this
4283            case, there is an out-of-bounds access if
4284            (start < lower || start > upper).  */
4285         if (compare_bound (AR_START, AR_END) == CMP_EQ
4286             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4287                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4288             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4289                 && comp_start_end == CMP_GT))
4290           {
4291             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4292               {
4293                 gfc_warning ("Lower array reference at %L is out of bounds "
4294                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4295                        mpz_get_si (AR_START->value.integer),
4296                        mpz_get_si (as->lower[i]->value.integer), i+1);
4297                 return SUCCESS;
4298               }
4299             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4300               {
4301                 gfc_warning ("Lower array reference at %L is out of bounds "
4302                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4303                        mpz_get_si (AR_START->value.integer),
4304                        mpz_get_si (as->upper[i]->value.integer), i+1);
4305                 return SUCCESS;
4306               }
4307           }
4308
4309         /* If we can compute the highest index of the array section,
4310            then it also has to be between lower and upper.  */
4311         mpz_init (last_value);
4312         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4313                                             last_value))
4314           {
4315             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4316               {
4317                 gfc_warning ("Upper array reference at %L is out of bounds "
4318                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4319                        mpz_get_si (last_value),
4320                        mpz_get_si (as->lower[i]->value.integer), i+1);
4321                 mpz_clear (last_value);
4322                 return SUCCESS;
4323               }
4324             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4325               {
4326                 gfc_warning ("Upper array reference at %L is out of bounds "
4327                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4328                        mpz_get_si (last_value),
4329                        mpz_get_si (as->upper[i]->value.integer), i+1);
4330                 mpz_clear (last_value);
4331                 return SUCCESS;
4332               }
4333           }
4334         mpz_clear (last_value);
4335
4336 #undef AR_START
4337 #undef AR_END
4338       }
4339       break;
4340
4341     default:
4342       gfc_internal_error ("check_dimension(): Bad array reference");
4343     }
4344
4345   return SUCCESS;
4346 }
4347
4348
4349 /* Compare an array reference with an array specification.  */
4350
4351 static gfc_try
4352 compare_spec_to_ref (gfc_array_ref *ar)
4353 {
4354   gfc_array_spec *as;
4355   int i;
4356
4357   as = ar->as;
4358   i = as->rank - 1;
4359   /* TODO: Full array sections are only allowed as actual parameters.  */
4360   if (as->type == AS_ASSUMED_SIZE
4361       && (/*ar->type == AR_FULL
4362           ||*/ (ar->type == AR_SECTION
4363               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4364     {
4365       gfc_error ("Rightmost upper bound of assumed size array section "
4366                  "not specified at %L", &ar->where);
4367       return FAILURE;
4368     }
4369
4370   if (ar->type == AR_FULL)
4371     return SUCCESS;
4372
4373   if (as->rank != ar->dimen)
4374     {
4375       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4376                  &ar->where, ar->dimen, as->rank);
4377       return FAILURE;
4378     }
4379
4380   /* ar->codimen == 0 is a local array.  */
4381   if (as->corank != ar->codimen && ar->codimen != 0)
4382     {
4383       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4384                  &ar->where, ar->codimen, as->corank);
4385       return FAILURE;
4386     }
4387
4388   for (i = 0; i < as->rank; i++)
4389     if (check_dimension (i, ar, as) == FAILURE)
4390       return FAILURE;
4391
4392   /* Local access has no coarray spec.  */
4393   if (ar->codimen != 0)
4394     for (i = as->rank; i < as->rank + as->corank; i++)
4395       {
4396         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate
4397             && ar->dimen_type[i] != DIMEN_THIS_IMAGE)
4398           {
4399             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4400                        i + 1 - as->rank, &ar->where);
4401             return FAILURE;
4402           }
4403         if (check_dimension (i, ar, as) == FAILURE)
4404           return FAILURE;
4405       }
4406
4407   return SUCCESS;
4408 }
4409
4410
4411 /* Resolve one part of an array index.  */
4412
4413 static gfc_try
4414 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4415                      int force_index_integer_kind)
4416 {
4417   gfc_typespec ts;
4418
4419   if (index == NULL)
4420     return SUCCESS;
4421
4422   if (gfc_resolve_expr (index) == FAILURE)
4423     return FAILURE;
4424
4425   if (check_scalar && index->rank != 0)
4426     {
4427       gfc_error ("Array index at %L must be scalar", &index->where);
4428       return FAILURE;
4429     }
4430
4431   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4432     {
4433       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4434                  &index->where, gfc_basic_typename (index->ts.type));
4435       return FAILURE;
4436     }
4437
4438   if (index->ts.type == BT_REAL)
4439     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4440                         &index->where) == FAILURE)
4441       return FAILURE;
4442
4443   if ((index->ts.kind != gfc_index_integer_kind
4444        && force_index_integer_kind)
4445       || index->ts.type != BT_INTEGER)
4446     {
4447       gfc_clear_ts (&ts);
4448       ts.type = BT_INTEGER;
4449       ts.kind = gfc_index_integer_kind;
4450
4451       gfc_convert_type_warn (index, &ts, 2, 0);
4452     }
4453
4454   return SUCCESS;
4455 }
4456
4457 /* Resolve one part of an array index.  */
4458
4459 gfc_try
4460 gfc_resolve_index (gfc_expr *index, int check_scalar)
4461 {
4462   return gfc_resolve_index_1 (index, check_scalar, 1);
4463 }
4464
4465 /* Resolve a dim argument to an intrinsic function.  */
4466
4467 gfc_try
4468 gfc_resolve_dim_arg (gfc_expr *dim)
4469 {
4470   if (dim == NULL)
4471     return SUCCESS;
4472
4473   if (gfc_resolve_expr (dim) == FAILURE)
4474     return FAILURE;
4475
4476   if (dim->rank != 0)
4477     {
4478       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4479       return FAILURE;
4480
4481     }
4482
4483   if (dim->ts.type != BT_INTEGER)
4484     {
4485       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4486       return FAILURE;
4487     }
4488
4489   if (dim->ts.kind != gfc_index_integer_kind)
4490     {
4491       gfc_typespec ts;
4492
4493       gfc_clear_ts (&ts);
4494       ts.type = BT_INTEGER;
4495       ts.kind = gfc_index_integer_kind;
4496
4497       gfc_convert_type_warn (dim, &ts, 2, 0);
4498     }
4499
4500   return SUCCESS;
4501 }
4502
4503 /* Given an expression that contains array references, update those array
4504    references to point to the right array specifications.  While this is
4505    filled in during matching, this information is difficult to save and load
4506    in a module, so we take care of it here.
4507
4508    The idea here is that the original array reference comes from the
4509    base symbol.  We traverse the list of reference structures, setting
4510    the stored reference to references.  Component references can
4511    provide an additional array specification.  */
4512
4513 static void
4514 find_array_spec (gfc_expr *e)
4515 {
4516   gfc_array_spec *as;
4517   gfc_component *c;
4518   gfc_ref *ref;
4519
4520   if (e->symtree->n.sym->ts.type == BT_CLASS)
4521     as = CLASS_DATA (e->symtree->n.sym)->as;
4522   else
4523     as = e->symtree->n.sym->as;
4524
4525   for (ref = e->ref; ref; ref = ref->next)
4526     switch (ref->type)
4527       {
4528       case REF_ARRAY:
4529         if (as == NULL)
4530           gfc_internal_error ("find_array_spec(): Missing spec");
4531
4532         ref->u.ar.as = as;
4533         as = NULL;
4534         break;
4535
4536       case REF_COMPONENT:
4537         c = ref->u.c.component;
4538         if (c->attr.dimension)
4539           {
4540             if (as != NULL)
4541               gfc_internal_error ("find_array_spec(): unused as(1)");
4542             as = c->as;
4543           }
4544
4545         break;
4546
4547       case REF_SUBSTRING:
4548         break;
4549       }
4550
4551   if (as != NULL)
4552     gfc_internal_error ("find_array_spec(): unused as(2)");
4553 }
4554
4555
4556 /* Resolve an array reference.  */
4557
4558 static gfc_try
4559 resolve_array_ref (gfc_array_ref *ar)
4560 {
4561   int i, check_scalar;
4562   gfc_expr *e;
4563
4564   for (i = 0; i < ar->dimen + ar->codimen; i++)
4565     {
4566       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4567
4568       /* Do not force gfc_index_integer_kind for the start.  We can
4569          do fine with any integer kind.  This avoids temporary arrays
4570          created for indexing with a vector.  */
4571       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4572         return FAILURE;
4573       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4574         return FAILURE;
4575       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4576         return FAILURE;
4577
4578       e = ar->start[i];
4579
4580       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4581         switch (e->rank)
4582           {
4583           case 0:
4584             ar->dimen_type[i] = DIMEN_ELEMENT;
4585             break;
4586
4587           case 1:
4588             ar->dimen_type[i] = DIMEN_VECTOR;
4589             if (e->expr_type == EXPR_VARIABLE
4590                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4591               ar->start[i] = gfc_get_parentheses (e);
4592             break;
4593
4594           default:
4595             gfc_error ("Array index at %L is an array of rank %d",
4596                        &ar->c_where[i], e->rank);
4597             return FAILURE;
4598           }
4599
4600       /* Fill in the upper bound, which may be lower than the
4601          specified one for something like a(2:10:5), which is
4602          identical to a(2:7:5).  Only relevant for strides not equal
4603          to one.  Don't try a division by zero.  */
4604       if (ar->dimen_type[i] == DIMEN_RANGE
4605           && ar->stride[i] != NULL && ar->stride[i]->expr_type == EXPR_CONSTANT
4606           && mpz_cmp_si (ar->stride[i]->value.integer, 1L) != 0
4607           && mpz_cmp_si (ar->stride[i]->value.integer, 0L) != 0)
4608         {
4609           mpz_t size, end;
4610
4611           if (gfc_ref_dimen_size (ar, i, &size, &end) == SUCCESS)
4612             {
4613               if (ar->end[i] == NULL)
4614                 {
4615                   ar->end[i] =
4616                     gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
4617                                            &ar->where);
4618                   mpz_set (ar->end[i]->value.integer, end);
4619                 }
4620               else if (ar->end[i]->ts.type == BT_INTEGER
4621                        && ar->end[i]->expr_type == EXPR_CONSTANT)
4622                 {
4623                   mpz_set (ar->end[i]->value.integer, end);
4624                 }
4625               else
4626                 gcc_unreachable ();
4627
4628               mpz_clear (size);
4629               mpz_clear (end);
4630             }
4631         }
4632     }
4633
4634   if (ar->type == AR_FULL)
4635     {
4636       if (ar->as->rank == 0)
4637         ar->type = AR_ELEMENT;
4638
4639       /* Make sure array is the same as array(:,:), this way
4640          we don't need to special case all the time.  */
4641       ar->dimen = ar->as->rank;
4642       for (i = 0; i < ar->dimen; i++)
4643         {
4644           ar->dimen_type[i] = DIMEN_RANGE;
4645
4646           gcc_assert (ar->start[i] == NULL);
4647           gcc_assert (ar->end[i] == NULL);
4648           gcc_assert (ar->stride[i] == NULL);
4649         }
4650     }
4651
4652   /* If the reference type is unknown, figure out what kind it is.  */
4653
4654   if (ar->type == AR_UNKNOWN)
4655     {
4656       ar->type = AR_ELEMENT;
4657       for (i = 0; i < ar->dimen; i++)
4658         if (ar->dimen_type[i] == DIMEN_RANGE
4659             || ar->dimen_type[i] == DIMEN_VECTOR)
4660           {
4661             ar->type = AR_SECTION;
4662             break;
4663           }
4664     }
4665
4666   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4667     return FAILURE;
4668
4669   if (ar->as->corank && ar->codimen == 0)
4670     {
4671       int n;
4672       ar->codimen = ar->as->corank;
4673       for (n = ar->dimen; n < ar->dimen + ar->codimen; n++)
4674         ar->dimen_type[n] = DIMEN_THIS_IMAGE;
4675     }
4676
4677   return SUCCESS;
4678 }
4679
4680
4681 static gfc_try
4682 resolve_substring (gfc_ref *ref)
4683 {
4684   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4685
4686   if (ref->u.ss.start != NULL)
4687     {
4688       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4689         return FAILURE;
4690
4691       if (ref->u.ss.start->ts.type != BT_INTEGER)
4692         {
4693           gfc_error ("Substring start index at %L must be of type INTEGER",
4694                      &ref->u.ss.start->where);
4695           return FAILURE;
4696         }
4697
4698       if (ref->u.ss.start->rank != 0)
4699         {
4700           gfc_error ("Substring start index at %L must be scalar",
4701                      &ref->u.ss.start->where);
4702           return FAILURE;
4703         }
4704
4705       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4706           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4707               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4708         {
4709           gfc_error ("Substring start index at %L is less than one",
4710                      &ref->u.ss.start->where);
4711           return FAILURE;
4712         }
4713     }
4714
4715   if (ref->u.ss.end != NULL)
4716     {
4717       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4718         return FAILURE;
4719
4720       if (ref->u.ss.end->ts.type != BT_INTEGER)
4721         {
4722           gfc_error ("Substring end index at %L must be of type INTEGER",
4723                      &ref->u.ss.end->where);
4724           return FAILURE;
4725         }
4726
4727       if (ref->u.ss.end->rank != 0)
4728         {
4729           gfc_error ("Substring end index at %L must be scalar",
4730                      &ref->u.ss.end->where);
4731           return FAILURE;
4732         }
4733
4734       if (ref->u.ss.length != NULL
4735           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4736           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4737               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4738         {
4739           gfc_error ("Substring end index at %L exceeds the string length",
4740                      &ref->u.ss.start->where);
4741           return FAILURE;
4742         }
4743
4744       if (compare_bound_mpz_t (ref->u.ss.end,
4745                                gfc_integer_kinds[k].huge) == CMP_GT
4746           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4747               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4748         {
4749           gfc_error ("Substring end index at %L is too large",
4750                      &ref->u.ss.end->where);
4751           return FAILURE;
4752         }
4753     }
4754
4755   return SUCCESS;
4756 }
4757
4758
4759 /* This function supplies missing substring charlens.  */
4760
4761 void
4762 gfc_resolve_substring_charlen (gfc_expr *e)
4763 {
4764   gfc_ref *char_ref;
4765   gfc_expr *start, *end;
4766
4767   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4768     if (char_ref->type == REF_SUBSTRING)
4769       break;
4770
4771   if (!char_ref)
4772     return;
4773
4774   gcc_assert (char_ref->next == NULL);
4775
4776   if (e->ts.u.cl)
4777     {
4778       if (e->ts.u.cl->length)
4779         gfc_free_expr (e->ts.u.cl->length);
4780       else if (e->expr_type == EXPR_VARIABLE
4781                  && e->symtree->n.sym->attr.dummy)
4782         return;
4783     }
4784
4785   e->ts.type = BT_CHARACTER;
4786   e->ts.kind = gfc_default_character_kind;
4787
4788   if (!e->ts.u.cl)
4789     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4790
4791   if (char_ref->u.ss.start)
4792     start = gfc_copy_expr (char_ref->u.ss.start);
4793   else
4794     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4795
4796   if (char_ref->u.ss.end)
4797     end = gfc_copy_expr (char_ref->u.ss.end);
4798   else if (e->expr_type == EXPR_VARIABLE)
4799     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4800   else
4801     end = NULL;
4802
4803   if (!start || !end)
4804     return;
4805
4806   /* Length = (end - start +1).  */
4807   e->ts.u.cl->length = gfc_subtract (end, start);
4808   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4809                                 gfc_get_int_expr (gfc_default_integer_kind,
4810                                                   NULL, 1));
4811
4812   e->ts.u.cl->length->ts.type = BT_INTEGER;
4813   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4814
4815   /* Make sure that the length is simplified.  */
4816   gfc_simplify_expr (e->ts.u.cl->length, 1);
4817   gfc_resolve_expr (e->ts.u.cl->length);
4818 }
4819
4820
4821 /* Resolve subtype references.  */
4822
4823 static gfc_try
4824 resolve_ref (gfc_expr *expr)
4825 {
4826   int current_part_dimension, n_components, seen_part_dimension;
4827   gfc_ref *ref;
4828
4829   for (ref = expr->ref; ref; ref = ref->next)
4830     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4831       {
4832         find_array_spec (expr);
4833         break;
4834       }
4835
4836   for (ref = expr->ref; ref; ref = ref->next)
4837     switch (ref->type)
4838       {
4839       case REF_ARRAY:
4840         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4841           return FAILURE;
4842         break;
4843
4844       case REF_COMPONENT:
4845         break;
4846
4847       case REF_SUBSTRING:
4848         if (resolve_substring (ref) == FAILURE)
4849           return FAILURE;
4850         break;
4851       }
4852
4853   /* Check constraints on part references.  */
4854
4855   current_part_dimension = 0;
4856   seen_part_dimension = 0;
4857   n_components = 0;
4858
4859   for (ref = expr->ref; ref; ref = ref->next)
4860     {
4861       switch (ref->type)
4862         {
4863         case REF_ARRAY:
4864           switch (ref->u.ar.type)
4865             {
4866             case AR_FULL:
4867               /* Coarray scalar.  */
4868               if (ref->u.ar.as->rank == 0)
4869                 {
4870                   current_part_dimension = 0;
4871                   break;
4872                 }
4873               /* Fall through.  */
4874             case AR_SECTION:
4875               current_part_dimension = 1;
4876               break;
4877
4878             case AR_ELEMENT:
4879               current_part_dimension = 0;
4880               break;
4881
4882             case AR_UNKNOWN:
4883               gfc_internal_error ("resolve_ref(): Bad array reference");
4884             }
4885
4886           break;
4887
4888         case REF_COMPONENT:
4889           if (current_part_dimension || seen_part_dimension)
4890             {
4891               /* F03:C614.  */
4892               if (ref->u.c.component->attr.pointer
4893                   || ref->u.c.component->attr.proc_pointer)
4894                 {
4895                   gfc_error ("Component to the right of a part reference "
4896                              "with nonzero rank must not have the POINTER "
4897                              "attribute at %L", &expr->where);
4898                   return FAILURE;
4899                 }
4900               else if (ref->u.c.component->attr.allocatable)
4901                 {
4902                   gfc_error ("Component to the right of a part reference "
4903                              "with nonzero rank must not have the ALLOCATABLE "
4904                              "attribute at %L", &expr->where);
4905                   return FAILURE;
4906                 }
4907             }
4908
4909           n_components++;
4910           break;
4911
4912         case REF_SUBSTRING:
4913           break;
4914         }
4915
4916       if (((ref->type == REF_COMPONENT && n_components > 1)
4917            || ref->next == NULL)
4918           && current_part_dimension
4919           && seen_part_dimension)
4920         {
4921           gfc_error ("Two or more part references with nonzero rank must "
4922                      "not be specified at %L", &expr->where);
4923           return FAILURE;
4924         }
4925
4926       if (ref->type == REF_COMPONENT)
4927         {
4928           if (current_part_dimension)
4929             seen_part_dimension = 1;
4930
4931           /* reset to make sure */
4932           current_part_dimension = 0;
4933         }
4934     }
4935
4936   return SUCCESS;
4937 }
4938
4939
4940 /* Given an expression, determine its shape.  This is easier than it sounds.
4941    Leaves the shape array NULL if it is not possible to determine the shape.  */
4942
4943 static void
4944 expression_shape (gfc_expr *e)
4945 {
4946   mpz_t array[GFC_MAX_DIMENSIONS];
4947   int i;
4948
4949   if (e->rank == 0 || e->shape != NULL)
4950     return;
4951
4952   for (i = 0; i < e->rank; i++)
4953     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4954       goto fail;
4955
4956   e->shape = gfc_get_shape (e->rank);
4957
4958   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4959
4960   return;
4961
4962 fail:
4963   for (i--; i >= 0; i--)
4964     mpz_clear (array[i]);
4965 }
4966
4967
4968 /* Given a variable expression node, compute the rank of the expression by
4969    examining the base symbol and any reference structures it may have.  */
4970
4971 static void
4972 expression_rank (gfc_expr *e)
4973 {
4974   gfc_ref *ref;
4975   int i, rank;
4976
4977   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4978      could lead to serious confusion...  */
4979   gcc_assert (e->expr_type != EXPR_COMPCALL);
4980
4981   if (e->ref == NULL)
4982     {
4983       if (e->expr_type == EXPR_ARRAY)
4984         goto done;
4985       /* Constructors can have a rank different from one via RESHAPE().  */
4986
4987       if (e->symtree == NULL)
4988         {
4989           e->rank = 0;
4990           goto done;
4991         }
4992
4993       e->rank = (e->symtree->n.sym->as == NULL)
4994                 ? 0 : e->symtree->n.sym->as->rank;
4995       goto done;
4996     }
4997
4998   rank = 0;
4999
5000   for (ref = e->ref; ref; ref = ref->next)
5001     {
5002       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.proc_pointer
5003           && ref->u.c.component->attr.function && !ref->next)
5004         rank = ref->u.c.component->as ? ref->u.c.component->as->rank : 0;
5005
5006       if (ref->type != REF_ARRAY)
5007         continue;
5008
5009       if (ref->u.ar.type == AR_FULL)
5010         {
5011           rank = ref->u.ar.as->rank;
5012           break;
5013         }
5014
5015       if (ref->u.ar.type == AR_SECTION)
5016         {
5017           /* Figure out the rank of the section.  */
5018           if (rank != 0)
5019             gfc_internal_error ("expression_rank(): Two array specs");
5020
5021           for (i = 0; i < ref->u.ar.dimen; i++)
5022             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
5023                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
5024               rank++;
5025
5026           break;
5027         }
5028     }
5029
5030   e->rank = rank;
5031
5032 done:
5033   expression_shape (e);
5034 }
5035
5036
5037 /* Resolve a variable expression.  */
5038
5039 static gfc_try
5040 resolve_variable (gfc_expr *e)
5041 {
5042   gfc_symbol *sym;
5043   gfc_try t;
5044
5045   t = SUCCESS;
5046
5047   if (e->symtree == NULL)
5048     return FAILURE;
5049   sym = e->symtree->n.sym;
5050
5051   /* If this is an associate-name, it may be parsed with an array reference
5052      in error even though the target is scalar.  Fail directly in this case.  */
5053   if (sym->assoc && !sym->attr.dimension && e->ref && e->ref->type == REF_ARRAY)
5054     return FAILURE;
5055
5056   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.generic)
5057     sym->ts.u.derived = gfc_find_dt_in_generic (sym->ts.u.derived);
5058
5059   /* On the other hand, the parser may not have known this is an array;
5060      in this case, we have to add a FULL reference.  */
5061   if (sym->assoc && sym->attr.dimension && !e->ref)
5062     {
5063       e->ref = gfc_get_ref ();
5064       e->ref->type = REF_ARRAY;
5065       e->ref->u.ar.type = AR_FULL;
5066       e->ref->u.ar.dimen = 0;
5067     }
5068
5069   if (e->ref && resolve_ref (e) == FAILURE)
5070     return FAILURE;
5071
5072   if (sym->attr.flavor == FL_PROCEDURE
5073       && (!sym->attr.function
5074           || (sym->attr.function && sym->result
5075               && sym->result->attr.proc_pointer
5076               && !sym->result->attr.function)))
5077     {
5078       e->ts.type = BT_PROCEDURE;
5079       goto resolve_procedure;
5080     }
5081
5082   if (sym->ts.type != BT_UNKNOWN)
5083     gfc_variable_attr (e, &e->ts);
5084   else
5085     {
5086       /* Must be a simple variable reference.  */
5087       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
5088         return FAILURE;
5089       e->ts = sym->ts;
5090     }
5091
5092   if (check_assumed_size_reference (sym, e))
5093     return FAILURE;
5094
5095   /* Deal with forward references to entries during resolve_code, to
5096      satisfy, at least partially, 12.5.2.5.  */
5097   if (gfc_current_ns->entries
5098       && current_entry_id == sym->entry_id
5099       && cs_base
5100       && cs_base->current
5101       && cs_base->current->op != EXEC_ENTRY)
5102     {
5103       gfc_entry_list *entry;
5104       gfc_formal_arglist *formal;
5105       int n;
5106       bool seen;
5107
5108       /* If the symbol is a dummy...  */
5109       if (sym->attr.dummy && sym->ns == gfc_current_ns)
5110         {
5111           entry = gfc_current_ns->entries;
5112           seen = false;
5113
5114           /* ...test if the symbol is a parameter of previous entries.  */
5115           for (; entry && entry->id <= current_entry_id; entry = entry->next)
5116             for (formal = entry->sym->formal; formal; formal = formal->next)
5117               {
5118                 if (formal->sym && sym->name == formal->sym->name)
5119                   seen = true;
5120               }
5121
5122           /*  If it has not been seen as a dummy, this is an error.  */
5123           if (!seen)
5124             {
5125               if (specification_expr)
5126                 gfc_error ("Variable '%s', used in a specification expression"
5127                            ", is referenced at %L before the ENTRY statement "
5128                            "in which it is a parameter",
5129                            sym->name, &cs_base->current->loc);
5130               else
5131                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
5132                            "statement in which it is a parameter",
5133                            sym->name, &cs_base->current->loc);
5134               t = FAILURE;
5135             }
5136         }
5137
5138       /* Now do the same check on the specification expressions.  */
5139       specification_expr = 1;
5140       if (sym->ts.type == BT_CHARACTER
5141           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
5142         t = FAILURE;
5143
5144       if (sym->as)
5145         for (n = 0; n < sym->as->rank; n++)
5146           {
5147              specification_expr = 1;
5148              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
5149                t = FAILURE;
5150              specification_expr = 1;
5151              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
5152                t = FAILURE;
5153           }
5154       specification_expr = 0;
5155
5156       if (t == SUCCESS)
5157         /* Update the symbol's entry level.  */
5158         sym->entry_id = current_entry_id + 1;
5159     }
5160
5161   /* If a symbol has been host_associated mark it.  This is used latter,
5162      to identify if aliasing is possible via host association.  */
5163   if (sym->attr.flavor == FL_VARIABLE
5164         && gfc_current_ns->parent
5165         && (gfc_current_ns->parent == sym->ns
5166               || (gfc_current_ns->parent->parent
5167                     && gfc_current_ns->parent->parent == sym->ns)))
5168     sym->attr.host_assoc = 1;
5169
5170 resolve_procedure:
5171   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
5172     t = FAILURE;
5173
5174   /* F2008, C617 and C1229.  */
5175   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5176       && gfc_is_coindexed (e))
5177     {
5178       gfc_ref *ref, *ref2 = NULL;
5179
5180       for (ref = e->ref; ref; ref = ref->next)
5181         {
5182           if (ref->type == REF_COMPONENT)
5183             ref2 = ref;
5184           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5185             break;
5186         }
5187
5188       for ( ; ref; ref = ref->next)
5189         if (ref->type == REF_COMPONENT)
5190           break;
5191
5192       /* Expression itself is not coindexed object.  */
5193       if (ref && e->ts.type == BT_CLASS)
5194         {
5195           gfc_error ("Polymorphic subobject of coindexed object at %L",
5196                      &e->where);
5197           t = FAILURE;
5198         }
5199
5200       /* Expression itself is coindexed object.  */
5201       if (ref == NULL)
5202         {
5203           gfc_component *c;
5204           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5205           for ( ; c; c = c->next)
5206             if (c->attr.allocatable && c->ts.type == BT_CLASS)
5207               {
5208                 gfc_error ("Coindexed object with polymorphic allocatable "
5209                          "subcomponent at %L", &e->where);
5210                 t = FAILURE;
5211                 break;
5212               }
5213         }
5214     }
5215
5216   return t;
5217 }
5218
5219
5220 /* Checks to see that the correct symbol has been host associated.
5221    The only situation where this arises is that in which a twice
5222    contained function is parsed after the host association is made.
5223    Therefore, on detecting this, change the symbol in the expression
5224    and convert the array reference into an actual arglist if the old
5225    symbol is a variable.  */
5226 static bool
5227 check_host_association (gfc_expr *e)
5228 {
5229   gfc_symbol *sym, *old_sym;
5230   gfc_symtree *st;
5231   int n;
5232   gfc_ref *ref;
5233   gfc_actual_arglist *arg, *tail = NULL;
5234   bool retval = e->expr_type == EXPR_FUNCTION;
5235
5236   /*  If the expression is the result of substitution in
5237       interface.c(gfc_extend_expr) because there is no way in
5238       which the host association can be wrong.  */
5239   if (e->symtree == NULL
5240         || e->symtree->n.sym == NULL
5241         || e->user_operator)
5242     return retval;
5243
5244   old_sym = e->symtree->n.sym;
5245
5246   if (gfc_current_ns->parent
5247         && old_sym->ns != gfc_current_ns)
5248     {
5249       /* Use the 'USE' name so that renamed module symbols are
5250          correctly handled.  */
5251       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5252
5253       if (sym && old_sym != sym
5254               && sym->ts.type == old_sym->ts.type
5255               && sym->attr.flavor == FL_PROCEDURE
5256               && sym->attr.contained)
5257         {
5258           /* Clear the shape, since it might not be valid.  */
5259           gfc_free_shape (&e->shape, e->rank);
5260
5261           /* Give the expression the right symtree!  */
5262           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5263           gcc_assert (st != NULL);
5264
5265           if (old_sym->attr.flavor == FL_PROCEDURE
5266                 || e->expr_type == EXPR_FUNCTION)
5267             {
5268               /* Original was function so point to the new symbol, since
5269                  the actual argument list is already attached to the
5270                  expression. */
5271               e->value.function.esym = NULL;
5272               e->symtree = st;
5273             }
5274           else
5275             {
5276               /* Original was variable so convert array references into
5277                  an actual arglist. This does not need any checking now
5278                  since resolve_function will take care of it.  */
5279               e->value.function.actual = NULL;
5280               e->expr_type = EXPR_FUNCTION;
5281               e->symtree = st;
5282
5283               /* Ambiguity will not arise if the array reference is not
5284                  the last reference.  */
5285               for (ref = e->ref; ref; ref = ref->next)
5286                 if (ref->type == REF_ARRAY && ref->next == NULL)
5287                   break;
5288
5289               gcc_assert (ref->type == REF_ARRAY);
5290
5291               /* Grab the start expressions from the array ref and
5292                  copy them into actual arguments.  */
5293               for (n = 0; n < ref->u.ar.dimen; n++)
5294                 {
5295                   arg = gfc_get_actual_arglist ();
5296                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5297                   if (e->value.function.actual == NULL)
5298                     tail = e->value.function.actual = arg;
5299                   else
5300                     {
5301                       tail->next = arg;
5302                       tail = arg;
5303                     }
5304                 }
5305
5306               /* Dump the reference list and set the rank.  */
5307               gfc_free_ref_list (e->ref);
5308               e->ref = NULL;
5309               e->rank = sym->as ? sym->as->rank : 0;
5310             }
5311
5312           gfc_resolve_expr (e);
5313           sym->refs++;
5314         }
5315     }
5316   /* This might have changed!  */
5317   return e->expr_type == EXPR_FUNCTION;
5318 }
5319
5320
5321 static void
5322 gfc_resolve_character_operator (gfc_expr *e)
5323 {
5324   gfc_expr *op1 = e->value.op.op1;
5325   gfc_expr *op2 = e->value.op.op2;
5326   gfc_expr *e1 = NULL;
5327   gfc_expr *e2 = NULL;
5328
5329   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5330
5331   if (op1->ts.u.cl && op1->ts.u.cl->length)
5332     e1 = gfc_copy_expr (op1->ts.u.cl->length);
5333   else if (op1->expr_type == EXPR_CONSTANT)
5334     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5335                            op1->value.character.length);
5336
5337   if (op2->ts.u.cl && op2->ts.u.cl->length)
5338     e2 = gfc_copy_expr (op2->ts.u.cl->length);
5339   else if (op2->expr_type == EXPR_CONSTANT)
5340     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5341                            op2->value.character.length);
5342
5343   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5344
5345   if (!e1 || !e2)
5346     return;
5347
5348   e->ts.u.cl->length = gfc_add (e1, e2);
5349   e->ts.u.cl->length->ts.type = BT_INTEGER;
5350   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5351   gfc_simplify_expr (e->ts.u.cl->length, 0);
5352   gfc_resolve_expr (e->ts.u.cl->length);
5353
5354   return;
5355 }
5356
5357
5358 /*  Ensure that an character expression has a charlen and, if possible, a
5359     length expression.  */
5360
5361 static void
5362 fixup_charlen (gfc_expr *e)
5363 {
5364   /* The cases fall through so that changes in expression type and the need
5365      for multiple fixes are picked up.  In all circumstances, a charlen should
5366      be available for the middle end to hang a backend_decl on.  */
5367   switch (e->expr_type)
5368     {
5369     case EXPR_OP:
5370       gfc_resolve_character_operator (e);
5371
5372     case EXPR_ARRAY:
5373       if (e->expr_type == EXPR_ARRAY)
5374         gfc_resolve_character_array_constructor (e);
5375
5376     case EXPR_SUBSTRING:
5377       if (!e->ts.u.cl && e->ref)
5378         gfc_resolve_substring_charlen (e);
5379
5380     default:
5381       if (!e->ts.u.cl)
5382         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5383
5384       break;
5385     }
5386 }
5387
5388
5389 /* Update an actual argument to include the passed-object for type-bound
5390    procedures at the right position.  */
5391
5392 static gfc_actual_arglist*
5393 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5394                      const char *name)
5395 {
5396   gcc_assert (argpos > 0);
5397
5398   if (argpos == 1)
5399     {
5400       gfc_actual_arglist* result;
5401
5402       result = gfc_get_actual_arglist ();
5403       result->expr = po;
5404       result->next = lst;
5405       if (name)
5406         result->name = name;
5407
5408       return result;
5409     }
5410
5411   if (lst)
5412     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5413   else
5414     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5415   return lst;
5416 }
5417
5418
5419 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5420
5421 static gfc_expr*
5422 extract_compcall_passed_object (gfc_expr* e)
5423 {
5424   gfc_expr* po;
5425
5426   gcc_assert (e->expr_type == EXPR_COMPCALL);
5427
5428   if (e->value.compcall.base_object)
5429     po = gfc_copy_expr (e->value.compcall.base_object);
5430   else
5431     {
5432       po = gfc_get_expr ();
5433       po->expr_type = EXPR_VARIABLE;
5434       po->symtree = e->symtree;
5435       po->ref = gfc_copy_ref (e->ref);
5436       po->where = e->where;
5437     }
5438
5439   if (gfc_resolve_expr (po) == FAILURE)
5440     return NULL;
5441
5442   return po;
5443 }
5444
5445
5446 /* Update the arglist of an EXPR_COMPCALL expression to include the
5447    passed-object.  */
5448
5449 static gfc_try
5450 update_compcall_arglist (gfc_expr* e)
5451 {
5452   gfc_expr* po;
5453   gfc_typebound_proc* tbp;
5454
5455   tbp = e->value.compcall.tbp;
5456
5457   if (tbp->error)
5458     return FAILURE;
5459
5460   po = extract_compcall_passed_object (e);
5461   if (!po)
5462     return FAILURE;
5463
5464   if (tbp->nopass || e->value.compcall.ignore_pass)
5465     {
5466       gfc_free_expr (po);
5467       return SUCCESS;
5468     }
5469
5470   gcc_assert (tbp->pass_arg_num > 0);
5471   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5472                                                   tbp->pass_arg_num,
5473                                                   tbp->pass_arg);
5474
5475   return SUCCESS;
5476 }
5477
5478
5479 /* Extract the passed object from a PPC call (a copy of it).  */
5480
5481 static gfc_expr*
5482 extract_ppc_passed_object (gfc_expr *e)
5483 {
5484   gfc_expr *po;
5485   gfc_ref **ref;
5486
5487   po = gfc_get_expr ();
5488   po->expr_type = EXPR_VARIABLE;
5489   po->symtree = e->symtree;
5490   po->ref = gfc_copy_ref (e->ref);
5491   po->where = e->where;
5492
5493   /* Remove PPC reference.  */
5494   ref = &po->ref;
5495   while ((*ref)->next)
5496     ref = &(*ref)->next;
5497   gfc_free_ref_list (*ref);
5498   *ref = NULL;
5499
5500   if (gfc_resolve_expr (po) == FAILURE)
5501     return NULL;
5502
5503   return po;
5504 }
5505
5506
5507 /* Update the actual arglist of a procedure pointer component to include the
5508    passed-object.  */
5509
5510 static gfc_try
5511 update_ppc_arglist (gfc_expr* e)
5512 {
5513   gfc_expr* po;
5514   gfc_component *ppc;
5515   gfc_typebound_proc* tb;
5516
5517   if (!gfc_is_proc_ptr_comp (e, &ppc))
5518     return FAILURE;
5519
5520   tb = ppc->tb;
5521
5522   if (tb->error)
5523     return FAILURE;
5524   else if (tb->nopass)
5525     return SUCCESS;
5526
5527   po = extract_ppc_passed_object (e);
5528   if (!po)
5529     return FAILURE;
5530
5531   /* F08:R739.  */
5532   if (po->rank > 0)
5533     {
5534       gfc_error ("Passed-object at %L must be scalar", &e->where);
5535       return FAILURE;
5536     }
5537
5538   /* F08:C611.  */
5539   if (po->ts.type == BT_DERIVED && po->ts.u.derived->attr.abstract)
5540     {
5541       gfc_error ("Base object for procedure-pointer component call at %L is of"
5542                  " ABSTRACT type '%s'", &e->where, po->ts.u.derived->name);
5543       return FAILURE;
5544     }
5545
5546   gcc_assert (tb->pass_arg_num > 0);
5547   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5548                                                   tb->pass_arg_num,
5549                                                   tb->pass_arg);
5550
5551   return SUCCESS;
5552 }
5553
5554
5555 /* Check that the object a TBP is called on is valid, i.e. it must not be
5556    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5557
5558 static gfc_try
5559 check_typebound_baseobject (gfc_expr* e)
5560 {
5561   gfc_expr* base;
5562   gfc_try return_value = FAILURE;
5563
5564   base = extract_compcall_passed_object (e);
5565   if (!base)
5566     return FAILURE;
5567
5568   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5569
5570   /* F08:C611.  */
5571   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5572     {
5573       gfc_error ("Base object for type-bound procedure call at %L is of"
5574                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5575       goto cleanup;
5576     }
5577
5578   /* F08:C1230. If the procedure called is NOPASS,
5579      the base object must be scalar.  */
5580   if (e->value.compcall.tbp->nopass && base->rank > 0)
5581     {
5582       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5583                  " be scalar", &e->where);
5584       goto cleanup;
5585     }
5586
5587   return_value = SUCCESS;
5588
5589 cleanup:
5590   gfc_free_expr (base);
5591   return return_value;
5592 }
5593
5594
5595 /* Resolve a call to a type-bound procedure, either function or subroutine,
5596    statically from the data in an EXPR_COMPCALL expression.  The adapted
5597    arglist and the target-procedure symtree are returned.  */
5598
5599 static gfc_try
5600 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5601                           gfc_actual_arglist** actual)
5602 {
5603   gcc_assert (e->expr_type == EXPR_COMPCALL);
5604   gcc_assert (!e->value.compcall.tbp->is_generic);
5605
5606   /* Update the actual arglist for PASS.  */
5607   if (update_compcall_arglist (e) == FAILURE)
5608     return FAILURE;
5609
5610   *actual = e->value.compcall.actual;
5611   *target = e->value.compcall.tbp->u.specific;
5612
5613   gfc_free_ref_list (e->ref);
5614   e->ref = NULL;
5615   e->value.compcall.actual = NULL;
5616
5617   /* If we find a deferred typebound procedure, check for derived types
5618      that an over-riding typebound procedure has not been missed.  */
5619   if (e->value.compcall.tbp->deferred
5620         && e->value.compcall.name
5621         && !e->value.compcall.tbp->non_overridable
5622         && e->value.compcall.base_object
5623         && e->value.compcall.base_object->ts.type == BT_DERIVED)
5624     {
5625       gfc_symtree *st;
5626       gfc_symbol *derived;
5627
5628       /* Use the derived type of the base_object.  */
5629       derived = e->value.compcall.base_object->ts.u.derived;
5630       st = NULL;
5631
5632       /* If necessary, go throught the inheritance chain.  */
5633       while (!st && derived)
5634         {
5635           /* Look for the typebound procedure 'name'.  */
5636           if (derived->f2k_derived && derived->f2k_derived->tb_sym_root)
5637             st = gfc_find_symtree (derived->f2k_derived->tb_sym_root,
5638                                    e->value.compcall.name);
5639           if (!st)
5640             derived = gfc_get_derived_super_type (derived);
5641         }
5642
5643       /* Now find the specific name in the derived type namespace.  */
5644       if (st && st->n.tb && st->n.tb->u.specific)
5645         gfc_find_sym_tree (st->n.tb->u.specific->name,
5646                            derived->ns, 1, &st);
5647       if (st)
5648         *target = st;
5649     }
5650   return SUCCESS;
5651 }
5652
5653
5654 /* Get the ultimate declared type from an expression.  In addition,
5655    return the last class/derived type reference and the copy of the
5656    reference list.  If check_types is set true, derived types are
5657    identified as well as class references.  */
5658 static gfc_symbol*
5659 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5660                         gfc_expr *e, bool check_types)
5661 {
5662   gfc_symbol *declared;
5663   gfc_ref *ref;
5664
5665   declared = NULL;
5666   if (class_ref)
5667     *class_ref = NULL;
5668   if (new_ref)
5669     *new_ref = gfc_copy_ref (e->ref);
5670
5671   for (ref = e->ref; ref; ref = ref->next)
5672     {
5673       if (ref->type != REF_COMPONENT)
5674         continue;
5675
5676       if ((ref->u.c.component->ts.type == BT_CLASS
5677              || (check_types && ref->u.c.component->ts.type == BT_DERIVED))
5678           && ref->u.c.component->attr.flavor != FL_PROCEDURE)
5679         {
5680           declared = ref->u.c.component->ts.u.derived;
5681           if (class_ref)
5682             *class_ref = ref;
5683         }
5684     }
5685
5686   if (declared == NULL)
5687     declared = e->symtree->n.sym->ts.u.derived;
5688
5689   return declared;
5690 }
5691
5692
5693 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5694    which of the specific bindings (if any) matches the arglist and transform
5695    the expression into a call of that binding.  */
5696
5697 static gfc_try
5698 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5699 {
5700   gfc_typebound_proc* genproc;
5701   const char* genname;
5702   gfc_symtree *st;
5703   gfc_symbol *derived;
5704
5705   gcc_assert (e->expr_type == EXPR_COMPCALL);
5706   genname = e->value.compcall.name;
5707   genproc = e->value.compcall.tbp;
5708
5709   if (!genproc->is_generic)
5710     return SUCCESS;
5711
5712   /* Try the bindings on this type and in the inheritance hierarchy.  */
5713   for (; genproc; genproc = genproc->overridden)
5714     {
5715       gfc_tbp_generic* g;
5716
5717       gcc_assert (genproc->is_generic);
5718       for (g = genproc->u.generic; g; g = g->next)
5719         {
5720           gfc_symbol* target;
5721           gfc_actual_arglist* args;
5722           bool matches;
5723
5724           gcc_assert (g->specific);
5725
5726           if (g->specific->error)
5727             continue;
5728
5729           target = g->specific->u.specific->n.sym;
5730
5731           /* Get the right arglist by handling PASS/NOPASS.  */
5732           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5733           if (!g->specific->nopass)
5734             {
5735               gfc_expr* po;
5736               po = extract_compcall_passed_object (e);
5737               if (!po)
5738                 return FAILURE;
5739
5740               gcc_assert (g->specific->pass_arg_num > 0);
5741               gcc_assert (!g->specific->error);
5742               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5743                                           g->specific->pass_arg);
5744             }
5745           resolve_actual_arglist (args, target->attr.proc,
5746                                   is_external_proc (target) && !target->formal);
5747
5748           /* Check if this arglist matches the formal.  */
5749           matches = gfc_arglist_matches_symbol (&args, target);
5750
5751           /* Clean up and break out of the loop if we've found it.  */
5752           gfc_free_actual_arglist (args);
5753           if (matches)
5754             {
5755               e->value.compcall.tbp = g->specific;
5756               genname = g->specific_st->name;
5757               /* Pass along the name for CLASS methods, where the vtab
5758                  procedure pointer component has to be referenced.  */
5759               if (name)
5760                 *name = genname;
5761               goto success;
5762             }
5763         }
5764     }
5765
5766   /* Nothing matching found!  */
5767   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5768              " '%s' at %L", genname, &e->where);
5769   return FAILURE;
5770
5771 success:
5772   /* Make sure that we have the right specific instance for the name.  */
5773   derived = get_declared_from_expr (NULL, NULL, e, true);
5774
5775   st = gfc_find_typebound_proc (derived, NULL, genname, true, &e->where);
5776   if (st)
5777     e->value.compcall.tbp = st->n.tb;
5778
5779   return SUCCESS;
5780 }
5781
5782
5783 /* Resolve a call to a type-bound subroutine.  */
5784
5785 static gfc_try
5786 resolve_typebound_call (gfc_code* c, const char **name)
5787 {
5788   gfc_actual_arglist* newactual;
5789   gfc_symtree* target;
5790
5791   /* Check that's really a SUBROUTINE.  */
5792   if (!c->expr1->value.compcall.tbp->subroutine)
5793     {
5794       gfc_error ("'%s' at %L should be a SUBROUTINE",
5795                  c->expr1->value.compcall.name, &c->loc);
5796       return FAILURE;
5797     }
5798
5799   if (check_typebound_baseobject (c->expr1) == FAILURE)
5800     return FAILURE;
5801
5802   /* Pass along the name for CLASS methods, where the vtab
5803      procedure pointer component has to be referenced.  */
5804   if (name)
5805     *name = c->expr1->value.compcall.name;
5806
5807   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5808     return FAILURE;
5809
5810   /* Transform into an ordinary EXEC_CALL for now.  */
5811
5812   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5813     return FAILURE;
5814
5815   c->ext.actual = newactual;
5816   c->symtree = target;
5817   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5818
5819   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5820
5821   gfc_free_expr (c->expr1);
5822   c->expr1 = gfc_get_expr ();
5823   c->expr1->expr_type = EXPR_FUNCTION;
5824   c->expr1->symtree = target;
5825   c->expr1->where = c->loc;
5826
5827   return resolve_call (c);
5828 }
5829
5830
5831 /* Resolve a component-call expression.  */
5832 static gfc_try
5833 resolve_compcall (gfc_expr* e, const char **name)
5834 {
5835   gfc_actual_arglist* newactual;
5836   gfc_symtree* target;
5837
5838   /* Check that's really a FUNCTION.  */
5839   if (!e->value.compcall.tbp->function)
5840     {
5841       gfc_error ("'%s' at %L should be a FUNCTION",
5842                  e->value.compcall.name, &e->where);
5843       return FAILURE;
5844     }
5845
5846   /* These must not be assign-calls!  */
5847   gcc_assert (!e->value.compcall.assign);
5848
5849   if (check_typebound_baseobject (e) == FAILURE)
5850     return FAILURE;
5851
5852   /* Pass along the name for CLASS methods, where the vtab
5853      procedure pointer component has to be referenced.  */
5854   if (name)
5855     *name = e->value.compcall.name;
5856
5857   if (resolve_typebound_generic_call (e, name) == FAILURE)
5858     return FAILURE;
5859   gcc_assert (!e->value.compcall.tbp->is_generic);
5860
5861   /* Take the rank from the function's symbol.  */
5862   if (e->value.compcall.tbp->u.specific->n.sym->as)
5863     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5864
5865   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5866      arglist to the TBP's binding target.  */
5867
5868   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5869     return FAILURE;
5870
5871   e->value.function.actual = newactual;
5872   e->value.function.name = NULL;
5873   e->value.function.esym = target->n.sym;
5874   e->value.function.isym = NULL;
5875   e->symtree = target;
5876   e->ts = target->n.sym->ts;
5877   e->expr_type = EXPR_FUNCTION;
5878
5879   /* Resolution is not necessary if this is a class subroutine; this
5880      function only has to identify the specific proc. Resolution of
5881      the call will be done next in resolve_typebound_call.  */
5882   return gfc_resolve_expr (e);
5883 }
5884
5885
5886
5887 /* Resolve a typebound function, or 'method'. First separate all
5888    the non-CLASS references by calling resolve_compcall directly.  */
5889
5890 static gfc_try
5891 resolve_typebound_function (gfc_expr* e)
5892 {
5893   gfc_symbol *declared;
5894   gfc_component *c;
5895   gfc_ref *new_ref;
5896   gfc_ref *class_ref;
5897   gfc_symtree *st;
5898   const char *name;
5899   gfc_typespec ts;
5900   gfc_expr *expr;
5901   bool overridable;
5902
5903   st = e->symtree;
5904
5905   /* Deal with typebound operators for CLASS objects.  */
5906   expr = e->value.compcall.base_object;
5907   overridable = !e->value.compcall.tbp->non_overridable;
5908   if (expr && expr->ts.type == BT_CLASS && e->value.compcall.name)
5909     {
5910       /* If the base_object is not a variable, the corresponding actual
5911          argument expression must be stored in e->base_expression so
5912          that the corresponding tree temporary can be used as the base
5913          object in gfc_conv_procedure_call.  */
5914       if (expr->expr_type != EXPR_VARIABLE)
5915         {
5916           gfc_actual_arglist *args;
5917
5918           for (args= e->value.function.actual; args; args = args->next)
5919             {
5920               if (expr == args->expr)
5921                 expr = args->expr;
5922             }
5923         }
5924
5925       /* Since the typebound operators are generic, we have to ensure
5926          that any delays in resolution are corrected and that the vtab
5927          is present.  */
5928       ts = expr->ts;
5929       declared = ts.u.derived;
5930       c = gfc_find_component (declared, "_vptr", true, true);
5931       if (c->ts.u.derived == NULL)
5932         c->ts.u.derived = gfc_find_derived_vtab (declared);
5933
5934       if (resolve_compcall (e, &name) == FAILURE)
5935         return FAILURE;
5936
5937       /* Use the generic name if it is there.  */
5938       name = name ? name : e->value.function.esym->name;
5939       e->symtree = expr->symtree;
5940       e->ref = gfc_copy_ref (expr->ref);
5941       get_declared_from_expr (&class_ref, NULL, e, false);
5942
5943       /* Trim away the extraneous references that emerge from nested
5944          use of interface.c (extend_expr).  */
5945       if (class_ref && class_ref->next)
5946         {
5947           gfc_free_ref_list (class_ref->next);
5948           class_ref->next = NULL;
5949         }
5950       else if (e->ref && !class_ref)
5951         {
5952           gfc_free_ref_list (e->ref);
5953           e->ref = NULL;
5954         }
5955
5956       gfc_add_vptr_component (e);
5957       gfc_add_component_ref (e, name);
5958       e->value.function.esym = NULL;
5959       if (expr->expr_type != EXPR_VARIABLE)
5960         e->base_expr = expr;
5961       return SUCCESS;
5962     }
5963
5964   if (st == NULL)
5965     return resolve_compcall (e, NULL);
5966
5967   if (resolve_ref (e) == FAILURE)
5968     return FAILURE;
5969
5970   /* Get the CLASS declared type.  */
5971   declared = get_declared_from_expr (&class_ref, &new_ref, e, true);
5972
5973   /* Weed out cases of the ultimate component being a derived type.  */
5974   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5975          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5976     {
5977       gfc_free_ref_list (new_ref);
5978       return resolve_compcall (e, NULL);
5979     }
5980
5981   c = gfc_find_component (declared, "_data", true, true);
5982   declared = c->ts.u.derived;
5983
5984   /* Treat the call as if it is a typebound procedure, in order to roll
5985      out the correct name for the specific function.  */
5986   if (resolve_compcall (e, &name) == FAILURE)
5987     return FAILURE;
5988   ts = e->ts;
5989
5990   if (overridable)
5991     {
5992       /* Convert the expression to a procedure pointer component call.  */
5993       e->value.function.esym = NULL;
5994       e->symtree = st;
5995
5996       if (new_ref)  
5997         e->ref = new_ref;
5998
5999       /* '_vptr' points to the vtab, which contains the procedure pointers.  */
6000       gfc_add_vptr_component (e);
6001       gfc_add_component_ref (e, name);
6002
6003       /* Recover the typespec for the expression.  This is really only
6004         necessary for generic procedures, where the additional call
6005         to gfc_add_component_ref seems to throw the collection of the
6006         correct typespec.  */
6007       e->ts = ts;
6008     }
6009
6010   return SUCCESS;
6011 }
6012
6013 /* Resolve a typebound subroutine, or 'method'. First separate all
6014    the non-CLASS references by calling resolve_typebound_call
6015    directly.  */
6016
6017 static gfc_try
6018 resolve_typebound_subroutine (gfc_code *code)
6019 {
6020   gfc_symbol *declared;
6021   gfc_component *c;
6022   gfc_ref *new_ref;
6023   gfc_ref *class_ref;
6024   gfc_symtree *st;
6025   const char *name;
6026   gfc_typespec ts;
6027   gfc_expr *expr;
6028   bool overridable;
6029
6030   st = code->expr1->symtree;
6031
6032   /* Deal with typebound operators for CLASS objects.  */
6033   expr = code->expr1->value.compcall.base_object;
6034   overridable = !code->expr1->value.compcall.tbp->non_overridable;
6035   if (expr && expr->ts.type == BT_CLASS && code->expr1->value.compcall.name)
6036     {
6037       /* If the base_object is not a variable, the corresponding actual
6038          argument expression must be stored in e->base_expression so
6039          that the corresponding tree temporary can be used as the base
6040          object in gfc_conv_procedure_call.  */
6041       if (expr->expr_type != EXPR_VARIABLE)
6042         {
6043           gfc_actual_arglist *args;
6044
6045           args= code->expr1->value.function.actual;
6046           for (; args; args = args->next)
6047             if (expr == args->expr)
6048               expr = args->expr;
6049         }
6050
6051       /* Since the typebound operators are generic, we have to ensure
6052          that any delays in resolution are corrected and that the vtab
6053          is present.  */
6054       declared = expr->ts.u.derived;
6055       c = gfc_find_component (declared, "_vptr", true, true);
6056       if (c->ts.u.derived == NULL)
6057         c->ts.u.derived = gfc_find_derived_vtab (declared);
6058
6059       if (resolve_typebound_call (code, &name) == FAILURE)
6060         return FAILURE;
6061
6062       /* Use the generic name if it is there.  */
6063       name = name ? name : code->expr1->value.function.esym->name;
6064       code->expr1->symtree = expr->symtree;
6065       code->expr1->ref = gfc_copy_ref (expr->ref);
6066
6067       /* Trim away the extraneous references that emerge from nested
6068          use of interface.c (extend_expr).  */
6069       get_declared_from_expr (&class_ref, NULL, code->expr1, false);
6070       if (class_ref && class_ref->next)
6071         {
6072           gfc_free_ref_list (class_ref->next);
6073           class_ref->next = NULL;
6074         }
6075       else if (code->expr1->ref && !class_ref)
6076         {
6077           gfc_free_ref_list (code->expr1->ref);
6078           code->expr1->ref = NULL;
6079         }
6080
6081       /* Now use the procedure in the vtable.  */
6082       gfc_add_vptr_component (code->expr1);
6083       gfc_add_component_ref (code->expr1, name);
6084       code->expr1->value.function.esym = NULL;
6085       if (expr->expr_type != EXPR_VARIABLE)
6086         code->expr1->base_expr = expr;
6087       return SUCCESS;
6088     }
6089
6090   if (st == NULL)
6091     return resolve_typebound_call (code, NULL);
6092
6093   if (resolve_ref (code->expr1) == FAILURE)
6094     return FAILURE;
6095
6096   /* Get the CLASS declared type.  */
6097   get_declared_from_expr (&class_ref, &new_ref, code->expr1, true);
6098
6099   /* Weed out cases of the ultimate component being a derived type.  */
6100   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
6101          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
6102     {
6103       gfc_free_ref_list (new_ref);
6104       return resolve_typebound_call (code, NULL);
6105     }
6106
6107   if (resolve_typebound_call (code, &name) == FAILURE)
6108     return FAILURE;
6109   ts = code->expr1->ts;
6110
6111   if (overridable)
6112     {
6113       /* Convert the expression to a procedure pointer component call.  */
6114       code->expr1->value.function.esym = NULL;
6115       code->expr1->symtree = st;
6116
6117       if (new_ref)
6118         code->expr1->ref = new_ref;
6119
6120       /* '_vptr' points to the vtab, which contains the procedure pointers.  */
6121       gfc_add_vptr_component (code->expr1);
6122       gfc_add_component_ref (code->expr1, name);
6123
6124       /* Recover the typespec for the expression.  This is really only
6125         necessary for generic procedures, where the additional call
6126         to gfc_add_component_ref seems to throw the collection of the
6127         correct typespec.  */
6128       code->expr1->ts = ts;
6129     }
6130
6131   return SUCCESS;
6132 }
6133
6134
6135 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
6136
6137 static gfc_try
6138 resolve_ppc_call (gfc_code* c)
6139 {
6140   gfc_component *comp;
6141   bool b;
6142
6143   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
6144   gcc_assert (b);
6145
6146   c->resolved_sym = c->expr1->symtree->n.sym;
6147   c->expr1->expr_type = EXPR_VARIABLE;
6148
6149   if (!comp->attr.subroutine)
6150     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
6151
6152   if (resolve_ref (c->expr1) == FAILURE)
6153     return FAILURE;
6154
6155   if (update_ppc_arglist (c->expr1) == FAILURE)
6156     return FAILURE;
6157
6158   c->ext.actual = c->expr1->value.compcall.actual;
6159
6160   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
6161                               comp->formal == NULL) == FAILURE)
6162     return FAILURE;
6163
6164   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
6165
6166   return SUCCESS;
6167 }
6168
6169
6170 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
6171
6172 static gfc_try
6173 resolve_expr_ppc (gfc_expr* e)
6174 {
6175   gfc_component *comp;
6176   bool b;
6177
6178   b = gfc_is_proc_ptr_comp (e, &comp);
6179   gcc_assert (b);
6180
6181   /* Convert to EXPR_FUNCTION.  */
6182   e->expr_type = EXPR_FUNCTION;
6183   e->value.function.isym = NULL;
6184   e->value.function.actual = e->value.compcall.actual;
6185   e->ts = comp->ts;
6186   if (comp->as != NULL)
6187     e->rank = comp->as->rank;
6188
6189   if (!comp->attr.function)
6190     gfc_add_function (&comp->attr, comp->name, &e->where);
6191
6192   if (resolve_ref (e) == FAILURE)
6193     return FAILURE;
6194
6195   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
6196                               comp->formal == NULL) == FAILURE)
6197     return FAILURE;
6198
6199   if (update_ppc_arglist (e) == FAILURE)
6200     return FAILURE;
6201
6202   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
6203
6204   return SUCCESS;
6205 }
6206
6207
6208 static bool
6209 gfc_is_expandable_expr (gfc_expr *e)
6210 {
6211   gfc_constructor *con;
6212
6213   if (e->expr_type == EXPR_ARRAY)
6214     {
6215       /* Traverse the constructor looking for variables that are flavor
6216          parameter.  Parameters must be expanded since they are fully used at
6217          compile time.  */
6218       con = gfc_constructor_first (e->value.constructor);
6219       for (; con; con = gfc_constructor_next (con))
6220         {
6221           if (con->expr->expr_type == EXPR_VARIABLE
6222               && con->expr->symtree
6223               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
6224               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
6225             return true;
6226           if (con->expr->expr_type == EXPR_ARRAY
6227               && gfc_is_expandable_expr (con->expr))
6228             return true;
6229         }
6230     }
6231
6232   return false;
6233 }
6234
6235 /* Resolve an expression.  That is, make sure that types of operands agree
6236    with their operators, intrinsic operators are converted to function calls
6237    for overloaded types and unresolved function references are resolved.  */
6238
6239 gfc_try
6240 gfc_resolve_expr (gfc_expr *e)
6241 {
6242   gfc_try t;
6243   bool inquiry_save;
6244
6245   if (e == NULL)
6246     return SUCCESS;
6247
6248   /* inquiry_argument only applies to variables.  */
6249   inquiry_save = inquiry_argument;
6250   if (e->expr_type != EXPR_VARIABLE)
6251     inquiry_argument = false;
6252
6253   switch (e->expr_type)
6254     {
6255     case EXPR_OP:
6256       t = resolve_operator (e);
6257       break;
6258
6259     case EXPR_FUNCTION:
6260     case EXPR_VARIABLE:
6261
6262       if (check_host_association (e))
6263         t = resolve_function (e);
6264       else
6265         {
6266           t = resolve_variable (e);
6267           if (t == SUCCESS)
6268             expression_rank (e);
6269         }
6270
6271       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6272           && e->ref->type != REF_SUBSTRING)
6273         gfc_resolve_substring_charlen (e);
6274
6275       break;
6276
6277     case EXPR_COMPCALL:
6278       t = resolve_typebound_function (e);
6279       break;
6280
6281     case EXPR_SUBSTRING:
6282       t = resolve_ref (e);
6283       break;
6284
6285     case EXPR_CONSTANT:
6286     case EXPR_NULL:
6287       t = SUCCESS;
6288       break;
6289
6290     case EXPR_PPC:
6291       t = resolve_expr_ppc (e);
6292       break;
6293
6294     case EXPR_ARRAY:
6295       t = FAILURE;
6296       if (resolve_ref (e) == FAILURE)
6297         break;
6298
6299       t = gfc_resolve_array_constructor (e);
6300       /* Also try to expand a constructor.  */
6301       if (t == SUCCESS)
6302         {
6303           expression_rank (e);
6304           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6305             gfc_expand_constructor (e, false);
6306         }
6307
6308       /* This provides the opportunity for the length of constructors with
6309          character valued function elements to propagate the string length
6310          to the expression.  */
6311       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
6312         {
6313           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6314              here rather then add a duplicate test for it above.  */ 
6315           gfc_expand_constructor (e, false);
6316           t = gfc_resolve_character_array_constructor (e);
6317         }
6318
6319       break;
6320
6321     case EXPR_STRUCTURE:
6322       t = resolve_ref (e);
6323       if (t == FAILURE)
6324         break;
6325
6326       t = resolve_structure_cons (e, 0);
6327       if (t == FAILURE)
6328         break;
6329
6330       t = gfc_simplify_expr (e, 0);
6331       break;
6332
6333     default:
6334       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6335     }
6336
6337   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
6338     fixup_charlen (e);
6339
6340   inquiry_argument = inquiry_save;
6341
6342   return t;
6343 }
6344
6345
6346 /* Resolve an expression from an iterator.  They must be scalar and have
6347    INTEGER or (optionally) REAL type.  */
6348
6349 static gfc_try
6350 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6351                            const char *name_msgid)
6352 {
6353   if (gfc_resolve_expr (expr) == FAILURE)
6354     return FAILURE;
6355
6356   if (expr->rank != 0)
6357     {
6358       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6359       return FAILURE;
6360     }
6361
6362   if (expr->ts.type != BT_INTEGER)
6363     {
6364       if (expr->ts.type == BT_REAL)
6365         {
6366           if (real_ok)
6367             return gfc_notify_std (GFC_STD_F95_DEL,
6368                                    "Deleted feature: %s at %L must be integer",
6369                                    _(name_msgid), &expr->where);
6370           else
6371             {
6372               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6373                          &expr->where);
6374               return FAILURE;
6375             }
6376         }
6377       else
6378         {
6379           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6380           return FAILURE;
6381         }
6382     }
6383   return SUCCESS;
6384 }
6385
6386
6387 /* Resolve the expressions in an iterator structure.  If REAL_OK is
6388    false allow only INTEGER type iterators, otherwise allow REAL types.  */
6389
6390 gfc_try
6391 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
6392 {
6393   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
6394       == FAILURE)
6395     return FAILURE;
6396
6397   if (gfc_check_vardef_context (iter->var, false, false, _("iterator variable"))
6398       == FAILURE)
6399     return FAILURE;
6400
6401   if (gfc_resolve_iterator_expr (iter->start, real_ok,
6402                                  "Start expression in DO loop") == FAILURE)
6403     return FAILURE;
6404
6405   if (gfc_resolve_iterator_expr (iter->end, real_ok,
6406                                  "End expression in DO loop") == FAILURE)
6407     return FAILURE;
6408
6409   if (gfc_resolve_iterator_expr (iter->step, real_ok,
6410                                  "Step expression in DO loop") == FAILURE)
6411     return FAILURE;
6412
6413   if (iter->step->expr_type == EXPR_CONSTANT)
6414     {
6415       if ((iter->step->ts.type == BT_INTEGER
6416            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6417           || (iter->step->ts.type == BT_REAL
6418               && mpfr_sgn (iter->step->value.real) == 0))
6419         {
6420           gfc_error ("Step expression in DO loop at %L cannot be zero",
6421                      &iter->step->where);
6422           return FAILURE;
6423         }
6424     }
6425
6426   /* Convert start, end, and step to the same type as var.  */
6427   if (iter->start->ts.kind != iter->var->ts.kind
6428       || iter->start->ts.type != iter->var->ts.type)
6429     gfc_convert_type (iter->start, &iter->var->ts, 2);
6430
6431   if (iter->end->ts.kind != iter->var->ts.kind
6432       || iter->end->ts.type != iter->var->ts.type)
6433     gfc_convert_type (iter->end, &iter->var->ts, 2);
6434
6435   if (iter->step->ts.kind != iter->var->ts.kind
6436       || iter->step->ts.type != iter->var->ts.type)
6437     gfc_convert_type (iter->step, &iter->var->ts, 2);
6438
6439   if (iter->start->expr_type == EXPR_CONSTANT
6440       && iter->end->expr_type == EXPR_CONSTANT
6441       && iter->step->expr_type == EXPR_CONSTANT)
6442     {
6443       int sgn, cmp;
6444       if (iter->start->ts.type == BT_INTEGER)
6445         {
6446           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6447           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6448         }
6449       else
6450         {
6451           sgn = mpfr_sgn (iter->step->value.real);
6452           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6453         }
6454       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
6455         gfc_warning ("DO loop at %L will be executed zero times",
6456                      &iter->step->where);
6457     }
6458
6459   return SUCCESS;
6460 }
6461
6462
6463 /* Traversal function for find_forall_index.  f == 2 signals that
6464    that variable itself is not to be checked - only the references.  */
6465
6466 static bool
6467 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6468 {
6469   if (expr->expr_type != EXPR_VARIABLE)
6470     return false;
6471   
6472   /* A scalar assignment  */
6473   if (!expr->ref || *f == 1)
6474     {
6475       if (expr->symtree->n.sym == sym)
6476         return true;
6477       else
6478         return false;
6479     }
6480
6481   if (*f == 2)
6482     *f = 1;
6483   return false;
6484 }
6485
6486
6487 /* Check whether the FORALL index appears in the expression or not.
6488    Returns SUCCESS if SYM is found in EXPR.  */
6489
6490 gfc_try
6491 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6492 {
6493   if (gfc_traverse_expr (expr, sym, forall_index, f))
6494     return SUCCESS;
6495   else
6496     return FAILURE;
6497 }
6498
6499
6500 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6501    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6502    INTEGERs, and if stride is a constant it must be nonzero.
6503    Furthermore "A subscript or stride in a forall-triplet-spec shall
6504    not contain a reference to any index-name in the
6505    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6506
6507 static void
6508 resolve_forall_iterators (gfc_forall_iterator *it)
6509 {
6510   gfc_forall_iterator *iter, *iter2;
6511
6512   for (iter = it; iter; iter = iter->next)
6513     {
6514       if (gfc_resolve_expr (iter->var) == SUCCESS
6515           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6516         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6517                    &iter->var->where);
6518
6519       if (gfc_resolve_expr (iter->start) == SUCCESS
6520           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6521         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6522                    &iter->start->where);
6523       if (iter->var->ts.kind != iter->start->ts.kind)
6524         gfc_convert_type (iter->start, &iter->var->ts, 1);
6525
6526       if (gfc_resolve_expr (iter->end) == SUCCESS
6527           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6528         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6529                    &iter->end->where);
6530       if (iter->var->ts.kind != iter->end->ts.kind)
6531         gfc_convert_type (iter->end, &iter->var->ts, 1);
6532
6533       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6534         {
6535           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6536             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6537                        &iter->stride->where, "INTEGER");
6538
6539           if (iter->stride->expr_type == EXPR_CONSTANT
6540               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6541             gfc_error ("FORALL stride expression at %L cannot be zero",
6542                        &iter->stride->where);
6543         }
6544       if (iter->var->ts.kind != iter->stride->ts.kind)
6545         gfc_convert_type (iter->stride, &iter->var->ts, 1);
6546     }
6547
6548   for (iter = it; iter; iter = iter->next)
6549     for (iter2 = iter; iter2; iter2 = iter2->next)
6550       {
6551         if (find_forall_index (iter2->start,
6552                                iter->var->symtree->n.sym, 0) == SUCCESS
6553             || find_forall_index (iter2->end,
6554                                   iter->var->symtree->n.sym, 0) == SUCCESS
6555             || find_forall_index (iter2->stride,
6556                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6557           gfc_error ("FORALL index '%s' may not appear in triplet "
6558                      "specification at %L", iter->var->symtree->name,
6559                      &iter2->start->where);
6560       }
6561 }
6562
6563
6564 /* Given a pointer to a symbol that is a derived type, see if it's
6565    inaccessible, i.e. if it's defined in another module and the components are
6566    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6567    inaccessible components are found, nonzero otherwise.  */
6568
6569 static int
6570 derived_inaccessible (gfc_symbol *sym)
6571 {
6572   gfc_component *c;
6573
6574   if (sym->attr.use_assoc && sym->attr.private_comp)
6575     return 1;
6576
6577   for (c = sym->components; c; c = c->next)
6578     {
6579         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6580           return 1;
6581     }
6582
6583   return 0;
6584 }
6585
6586
6587 /* Resolve the argument of a deallocate expression.  The expression must be
6588    a pointer or a full array.  */
6589
6590 static gfc_try
6591 resolve_deallocate_expr (gfc_expr *e)
6592 {
6593   symbol_attribute attr;
6594   int allocatable, pointer;
6595   gfc_ref *ref;
6596   gfc_symbol *sym;
6597   gfc_component *c;
6598
6599   if (gfc_resolve_expr (e) == FAILURE)
6600     return FAILURE;
6601
6602   if (e->expr_type != EXPR_VARIABLE)
6603     goto bad;
6604
6605   sym = e->symtree->n.sym;
6606
6607   if (sym->ts.type == BT_CLASS)
6608     {
6609       allocatable = CLASS_DATA (sym)->attr.allocatable;
6610       pointer = CLASS_DATA (sym)->attr.class_pointer;
6611     }
6612   else
6613     {
6614       allocatable = sym->attr.allocatable;
6615       pointer = sym->attr.pointer;
6616     }
6617   for (ref = e->ref; ref; ref = ref->next)
6618     {
6619       switch (ref->type)
6620         {
6621         case REF_ARRAY:
6622           if (ref->u.ar.type != AR_FULL
6623               && !(ref->u.ar.type == AR_ELEMENT && ref->u.ar.as->rank == 0
6624                    && ref->u.ar.codimen && gfc_ref_this_image (ref)))
6625             allocatable = 0;
6626           break;
6627
6628         case REF_COMPONENT:
6629           c = ref->u.c.component;
6630           if (c->ts.type == BT_CLASS)
6631             {
6632               allocatable = CLASS_DATA (c)->attr.allocatable;
6633               pointer = CLASS_DATA (c)->attr.class_pointer;
6634             }
6635           else
6636             {
6637               allocatable = c->attr.allocatable;
6638               pointer = c->attr.pointer;
6639             }
6640           break;
6641
6642         case REF_SUBSTRING:
6643           allocatable = 0;
6644           break;
6645         }
6646     }
6647
6648   attr = gfc_expr_attr (e);
6649
6650   if (allocatable == 0 && attr.pointer == 0)
6651     {
6652     bad:
6653       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6654                  &e->where);
6655       return FAILURE;
6656     }
6657
6658   /* F2008, C644.  */
6659   if (gfc_is_coindexed (e))
6660     {
6661       gfc_error ("Coindexed allocatable object at %L", &e->where);
6662       return FAILURE;
6663     }
6664
6665   if (pointer
6666       && gfc_check_vardef_context (e, true, true, _("DEALLOCATE object"))
6667          == FAILURE)
6668     return FAILURE;
6669   if (gfc_check_vardef_context (e, false, true, _("DEALLOCATE object"))
6670       == FAILURE)
6671     return FAILURE;
6672
6673   return SUCCESS;
6674 }
6675
6676
6677 /* Returns true if the expression e contains a reference to the symbol sym.  */
6678 static bool
6679 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6680 {
6681   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6682     return true;
6683
6684   return false;
6685 }
6686
6687 bool
6688 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6689 {
6690   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6691 }
6692
6693
6694 /* Given the expression node e for an allocatable/pointer of derived type to be
6695    allocated, get the expression node to be initialized afterwards (needed for
6696    derived types with default initializers, and derived types with allocatable
6697    components that need nullification.)  */
6698
6699 gfc_expr *
6700 gfc_expr_to_initialize (gfc_expr *e)
6701 {
6702   gfc_expr *result;
6703   gfc_ref *ref;
6704   int i;
6705
6706   result = gfc_copy_expr (e);
6707
6708   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6709   for (ref = result->ref; ref; ref = ref->next)
6710     if (ref->type == REF_ARRAY && ref->next == NULL)
6711       {
6712         ref->u.ar.type = AR_FULL;
6713
6714         for (i = 0; i < ref->u.ar.dimen; i++)
6715           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6716
6717         break;
6718       }
6719
6720   gfc_free_shape (&result->shape, result->rank);
6721
6722   /* Recalculate rank, shape, etc.  */
6723   gfc_resolve_expr (result);
6724   return result;
6725 }
6726
6727
6728 /* If the last ref of an expression is an array ref, return a copy of the
6729    expression with that one removed.  Otherwise, a copy of the original
6730    expression.  This is used for allocate-expressions and pointer assignment
6731    LHS, where there may be an array specification that needs to be stripped
6732    off when using gfc_check_vardef_context.  */
6733
6734 static gfc_expr*
6735 remove_last_array_ref (gfc_expr* e)
6736 {
6737   gfc_expr* e2;
6738   gfc_ref** r;
6739
6740   e2 = gfc_copy_expr (e);
6741   for (r = &e2->ref; *r; r = &(*r)->next)
6742     if ((*r)->type == REF_ARRAY && !(*r)->next)
6743       {
6744         gfc_free_ref_list (*r);
6745         *r = NULL;
6746         break;
6747       }
6748
6749   return e2;
6750 }
6751
6752
6753 /* Used in resolve_allocate_expr to check that a allocation-object and
6754    a source-expr are conformable.  This does not catch all possible 
6755    cases; in particular a runtime checking is needed.  */
6756
6757 static gfc_try
6758 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6759 {
6760   gfc_ref *tail;
6761   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6762   
6763   /* First compare rank.  */
6764   if (tail && e1->rank != tail->u.ar.as->rank)
6765     {
6766       gfc_error ("Source-expr at %L must be scalar or have the "
6767                  "same rank as the allocate-object at %L",
6768                  &e1->where, &e2->where);
6769       return FAILURE;
6770     }
6771
6772   if (e1->shape)
6773     {
6774       int i;
6775       mpz_t s;
6776
6777       mpz_init (s);
6778
6779       for (i = 0; i < e1->rank; i++)
6780         {
6781           if (tail->u.ar.end[i])
6782             {
6783               mpz_set (s, tail->u.ar.end[i]->value.integer);
6784               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6785               mpz_add_ui (s, s, 1);
6786             }
6787           else
6788             {
6789               mpz_set (s, tail->u.ar.start[i]->value.integer);
6790             }
6791
6792           if (mpz_cmp (e1->shape[i], s) != 0)
6793             {
6794               gfc_error ("Source-expr at %L and allocate-object at %L must "
6795                          "have the same shape", &e1->where, &e2->where);
6796               mpz_clear (s);
6797               return FAILURE;
6798             }
6799         }
6800
6801       mpz_clear (s);
6802     }
6803
6804   return SUCCESS;
6805 }
6806
6807
6808 /* Resolve the expression in an ALLOCATE statement, doing the additional
6809    checks to see whether the expression is OK or not.  The expression must
6810    have a trailing array reference that gives the size of the array.  */
6811
6812 static gfc_try
6813 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6814 {
6815   int i, pointer, allocatable, dimension, is_abstract;
6816   int codimension;
6817   bool coindexed;
6818   symbol_attribute attr;
6819   gfc_ref *ref, *ref2;
6820   gfc_expr *e2;
6821   gfc_array_ref *ar;
6822   gfc_symbol *sym = NULL;
6823   gfc_alloc *a;
6824   gfc_component *c;
6825   gfc_try t;
6826
6827   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6828      checking of coarrays.  */
6829   for (ref = e->ref; ref; ref = ref->next)
6830     if (ref->next == NULL)
6831       break;
6832
6833   if (ref && ref->type == REF_ARRAY)
6834     ref->u.ar.in_allocate = true;
6835
6836   if (gfc_resolve_expr (e) == FAILURE)
6837     goto failure;
6838
6839   /* Make sure the expression is allocatable or a pointer.  If it is
6840      pointer, the next-to-last reference must be a pointer.  */
6841
6842   ref2 = NULL;
6843   if (e->symtree)
6844     sym = e->symtree->n.sym;
6845
6846   /* Check whether ultimate component is abstract and CLASS.  */
6847   is_abstract = 0;
6848
6849   if (e->expr_type != EXPR_VARIABLE)
6850     {
6851       allocatable = 0;
6852       attr = gfc_expr_attr (e);
6853       pointer = attr.pointer;
6854       dimension = attr.dimension;
6855       codimension = attr.codimension;
6856     }
6857   else
6858     {
6859       if (sym->ts.type == BT_CLASS && CLASS_DATA (sym))
6860         {
6861           allocatable = CLASS_DATA (sym)->attr.allocatable;
6862           pointer = CLASS_DATA (sym)->attr.class_pointer;
6863           dimension = CLASS_DATA (sym)->attr.dimension;
6864           codimension = CLASS_DATA (sym)->attr.codimension;
6865           is_abstract = CLASS_DATA (sym)->attr.abstract;
6866         }
6867       else
6868         {
6869           allocatable = sym->attr.allocatable;
6870           pointer = sym->attr.pointer;
6871           dimension = sym->attr.dimension;
6872           codimension = sym->attr.codimension;
6873         }
6874
6875       coindexed = false;
6876
6877       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6878         {
6879           switch (ref->type)
6880             {
6881               case REF_ARRAY:
6882                 if (ref->u.ar.codimen > 0)
6883                   {
6884                     int n;
6885                     for (n = ref->u.ar.dimen;
6886                          n < ref->u.ar.dimen + ref->u.ar.codimen; n++)
6887                       if (ref->u.ar.dimen_type[n] != DIMEN_THIS_IMAGE)
6888                         {
6889                           coindexed = true;
6890                           break;
6891                         }
6892                    }
6893
6894                 if (ref->next != NULL)
6895                   pointer = 0;
6896                 break;
6897
6898               case REF_COMPONENT:
6899                 /* F2008, C644.  */
6900                 if (coindexed)
6901                   {
6902                     gfc_error ("Coindexed allocatable object at %L",
6903                                &e->where);
6904                     goto failure;
6905                   }
6906
6907                 c = ref->u.c.component;
6908                 if (c->ts.type == BT_CLASS)
6909                   {
6910                     allocatable = CLASS_DATA (c)->attr.allocatable;
6911                     pointer = CLASS_DATA (c)->attr.class_pointer;
6912                     dimension = CLASS_DATA (c)->attr.dimension;
6913                     codimension = CLASS_DATA (c)->attr.codimension;
6914                     is_abstract = CLASS_DATA (c)->attr.abstract;
6915                   }
6916                 else
6917                   {
6918                     allocatable = c->attr.allocatable;
6919                     pointer = c->attr.pointer;
6920                     dimension = c->attr.dimension;
6921                     codimension = c->attr.codimension;
6922                     is_abstract = c->attr.abstract;
6923                   }
6924                 break;
6925
6926               case REF_SUBSTRING:
6927                 allocatable = 0;
6928                 pointer = 0;
6929                 break;
6930             }
6931         }
6932     }
6933
6934   if (allocatable == 0 && pointer == 0)
6935     {
6936       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6937                  &e->where);
6938       goto failure;
6939     }
6940
6941   /* Some checks for the SOURCE tag.  */
6942   if (code->expr3)
6943     {
6944       /* Check F03:C631.  */
6945       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6946         {
6947           gfc_error ("Type of entity at %L is type incompatible with "
6948                       "source-expr at %L", &e->where, &code->expr3->where);
6949           goto failure;
6950         }
6951
6952       /* Check F03:C632 and restriction following Note 6.18.  */
6953       if (code->expr3->rank > 0
6954           && conformable_arrays (code->expr3, e) == FAILURE)
6955         goto failure;
6956
6957       /* Check F03:C633.  */
6958       if (code->expr3->ts.kind != e->ts.kind)
6959         {
6960           gfc_error ("The allocate-object at %L and the source-expr at %L "
6961                       "shall have the same kind type parameter",
6962                       &e->where, &code->expr3->where);
6963           goto failure;
6964         }
6965
6966       /* Check F2008, C642.  */
6967       if (code->expr3->ts.type == BT_DERIVED
6968           && ((codimension && gfc_expr_attr (code->expr3).lock_comp)
6969               || (code->expr3->ts.u.derived->from_intmod
6970                      == INTMOD_ISO_FORTRAN_ENV
6971                   && code->expr3->ts.u.derived->intmod_sym_id
6972                      == ISOFORTRAN_LOCK_TYPE)))
6973         {
6974           gfc_error ("The source-expr at %L shall neither be of type "
6975                      "LOCK_TYPE nor have a LOCK_TYPE component if "
6976                       "allocate-object at %L is a coarray",
6977                       &code->expr3->where, &e->where);
6978           goto failure;
6979         }
6980     }
6981
6982   /* Check F08:C629.  */
6983   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
6984       && !code->expr3)
6985     {
6986       gcc_assert (e->ts.type == BT_CLASS);
6987       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6988                  "type-spec or source-expr", sym->name, &e->where);
6989       goto failure;
6990     }
6991
6992   /* In the variable definition context checks, gfc_expr_attr is used
6993      on the expression.  This is fooled by the array specification
6994      present in e, thus we have to eliminate that one temporarily.  */
6995   e2 = remove_last_array_ref (e);
6996   t = SUCCESS;
6997   if (t == SUCCESS && pointer)
6998     t = gfc_check_vardef_context (e2, true, true, _("ALLOCATE object"));
6999   if (t == SUCCESS)
7000     t = gfc_check_vardef_context (e2, false, true, _("ALLOCATE object"));
7001   gfc_free_expr (e2);
7002   if (t == FAILURE)
7003     goto failure;
7004
7005   if (e->ts.type == BT_CLASS && CLASS_DATA (e)->attr.dimension
7006         && !code->expr3 && code->ext.alloc.ts.type == BT_DERIVED)
7007     {
7008       /* For class arrays, the initialization with SOURCE is done
7009          using _copy and trans_call. It is convenient to exploit that
7010          when the allocated type is different from the declared type but
7011          no SOURCE exists by setting expr3.  */
7012       code->expr3 = gfc_default_initializer (&code->ext.alloc.ts); 
7013     }
7014   else if (!code->expr3)
7015     {
7016       /* Set up default initializer if needed.  */
7017       gfc_typespec ts;
7018       gfc_expr *init_e;
7019
7020       if (code->ext.alloc.ts.type == BT_DERIVED)
7021         ts = code->ext.alloc.ts;
7022       else
7023         ts = e->ts;
7024
7025       if (ts.type == BT_CLASS)
7026         ts = ts.u.derived->components->ts;
7027
7028       if (ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&ts)))
7029         {
7030           gfc_code *init_st = gfc_get_code ();
7031           init_st->loc = code->loc;
7032           init_st->op = EXEC_INIT_ASSIGN;
7033           init_st->expr1 = gfc_expr_to_initialize (e);
7034           init_st->expr2 = init_e;
7035           init_st->next = code->next;
7036           code->next = init_st;
7037         }
7038     }
7039   else if (code->expr3->mold && code->expr3->ts.type == BT_DERIVED)
7040     {
7041       /* Default initialization via MOLD (non-polymorphic).  */
7042       gfc_expr *rhs = gfc_default_initializer (&code->expr3->ts);
7043       gfc_resolve_expr (rhs);
7044       gfc_free_expr (code->expr3);
7045       code->expr3 = rhs;
7046     }
7047
7048   if (e->ts.type == BT_CLASS)
7049     {
7050       /* Make sure the vtab symbol is present when
7051          the module variables are generated.  */
7052       gfc_typespec ts = e->ts;
7053       if (code->expr3)
7054         ts = code->expr3->ts;
7055       else if (code->ext.alloc.ts.type == BT_DERIVED)
7056         ts = code->ext.alloc.ts;
7057       gfc_find_derived_vtab (ts.u.derived);
7058       if (dimension)
7059         e = gfc_expr_to_initialize (e);
7060     }
7061
7062   if (dimension == 0 && codimension == 0)
7063     goto success;
7064
7065   /* Make sure the last reference node is an array specifiction.  */
7066
7067   if (!ref2 || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
7068       || (dimension && ref2->u.ar.dimen == 0))
7069     {
7070       gfc_error ("Array specification required in ALLOCATE statement "
7071                  "at %L", &e->where);
7072       goto failure;
7073     }
7074
7075   /* Make sure that the array section reference makes sense in the
7076     context of an ALLOCATE specification.  */
7077
7078   ar = &ref2->u.ar;
7079
7080   if (codimension)
7081     for (i = ar->dimen; i < ar->dimen + ar->codimen; i++)
7082       if (ar->dimen_type[i] == DIMEN_THIS_IMAGE)
7083         {
7084           gfc_error ("Coarray specification required in ALLOCATE statement "
7085                      "at %L", &e->where);
7086           goto failure;
7087         }
7088
7089   for (i = 0; i < ar->dimen; i++)
7090     {
7091       if (ref2->u.ar.type == AR_ELEMENT)
7092         goto check_symbols;
7093
7094       switch (ar->dimen_type[i])
7095         {
7096         case DIMEN_ELEMENT:
7097           break;
7098
7099         case DIMEN_RANGE:
7100           if (ar->start[i] != NULL
7101               && ar->end[i] != NULL
7102               && ar->stride[i] == NULL)
7103             break;
7104
7105           /* Fall Through...  */
7106
7107         case DIMEN_UNKNOWN:
7108         case DIMEN_VECTOR:
7109         case DIMEN_STAR:
7110         case DIMEN_THIS_IMAGE:
7111           gfc_error ("Bad array specification in ALLOCATE statement at %L",
7112                      &e->where);
7113           goto failure;
7114         }
7115
7116 check_symbols:
7117       for (a = code->ext.alloc.list; a; a = a->next)
7118         {
7119           sym = a->expr->symtree->n.sym;
7120
7121           /* TODO - check derived type components.  */
7122           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
7123             continue;
7124
7125           if ((ar->start[i] != NULL
7126                && gfc_find_sym_in_expr (sym, ar->start[i]))
7127               || (ar->end[i] != NULL
7128                   && gfc_find_sym_in_expr (sym, ar->end[i])))
7129             {
7130               gfc_error ("'%s' must not appear in the array specification at "
7131                          "%L in the same ALLOCATE statement where it is "
7132                          "itself allocated", sym->name, &ar->where);
7133               goto failure;
7134             }
7135         }
7136     }
7137
7138   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
7139     {
7140       if (ar->dimen_type[i] == DIMEN_ELEMENT
7141           || ar->dimen_type[i] == DIMEN_RANGE)
7142         {
7143           if (i == (ar->dimen + ar->codimen - 1))
7144             {
7145               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
7146                          "statement at %L", &e->where);
7147               goto failure;
7148             }
7149           break;
7150         }
7151
7152       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
7153           && ar->stride[i] == NULL)
7154         break;
7155
7156       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
7157                  &e->where);
7158       goto failure;
7159     }
7160
7161 success:
7162   return SUCCESS;
7163
7164 failure:
7165   return FAILURE;
7166 }
7167
7168 static void
7169 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
7170 {
7171   gfc_expr *stat, *errmsg, *pe, *qe;
7172   gfc_alloc *a, *p, *q;
7173
7174   stat = code->expr1;
7175   errmsg = code->expr2;
7176
7177   /* Check the stat variable.  */
7178   if (stat)
7179     {
7180       gfc_check_vardef_context (stat, false, false, _("STAT variable"));
7181
7182       if ((stat->ts.type != BT_INTEGER
7183            && !(stat->ref && (stat->ref->type == REF_ARRAY
7184                               || stat->ref->type == REF_COMPONENT)))
7185           || stat->rank > 0)
7186         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
7187                    "variable", &stat->where);
7188
7189       for (p = code->ext.alloc.list; p; p = p->next)
7190         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
7191           {
7192             gfc_ref *ref1, *ref2;
7193             bool found = true;
7194
7195             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
7196                  ref1 = ref1->next, ref2 = ref2->next)
7197               {
7198                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7199                   continue;
7200                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7201                   {
7202                     found = false;
7203                     break;
7204                   }
7205               }
7206
7207             if (found)
7208               {
7209                 gfc_error ("Stat-variable at %L shall not be %sd within "
7210                            "the same %s statement", &stat->where, fcn, fcn);
7211                 break;
7212               }
7213           }
7214     }
7215
7216   /* Check the errmsg variable.  */
7217   if (errmsg)
7218     {
7219       if (!stat)
7220         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
7221                      &errmsg->where);
7222
7223       gfc_check_vardef_context (errmsg, false, false, _("ERRMSG variable"));
7224
7225       if ((errmsg->ts.type != BT_CHARACTER
7226            && !(errmsg->ref
7227                 && (errmsg->ref->type == REF_ARRAY
7228                     || errmsg->ref->type == REF_COMPONENT)))
7229           || errmsg->rank > 0 )
7230         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
7231                    "variable", &errmsg->where);
7232
7233       for (p = code->ext.alloc.list; p; p = p->next)
7234         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
7235           {
7236             gfc_ref *ref1, *ref2;
7237             bool found = true;
7238
7239             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
7240                  ref1 = ref1->next, ref2 = ref2->next)
7241               {
7242                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7243                   continue;
7244                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7245                   {
7246                     found = false;
7247                     break;
7248                   }
7249               }
7250
7251             if (found)
7252               {
7253                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
7254                            "the same %s statement", &errmsg->where, fcn, fcn);
7255                 break;
7256               }
7257           }
7258     }
7259
7260   /* Check that an allocate-object appears only once in the statement.  
7261      FIXME: Checking derived types is disabled.  */
7262   for (p = code->ext.alloc.list; p; p = p->next)
7263     {
7264       pe = p->expr;
7265       for (q = p->next; q; q = q->next)
7266         {
7267           qe = q->expr;
7268           if (pe->symtree->n.sym->name == qe->symtree->n.sym->name)
7269             {
7270               /* This is a potential collision.  */
7271               gfc_ref *pr = pe->ref;
7272               gfc_ref *qr = qe->ref;
7273               
7274               /* Follow the references  until
7275                  a) They start to differ, in which case there is no error;
7276                  you can deallocate a%b and a%c in a single statement
7277                  b) Both of them stop, which is an error
7278                  c) One of them stops, which is also an error.  */
7279               while (1)
7280                 {
7281                   if (pr == NULL && qr == NULL)
7282                     {
7283                       gfc_error ("Allocate-object at %L also appears at %L",
7284                                  &pe->where, &qe->where);
7285                       break;
7286                     }
7287                   else if (pr != NULL && qr == NULL)
7288                     {
7289                       gfc_error ("Allocate-object at %L is subobject of"
7290                                  " object at %L", &pe->where, &qe->where);
7291                       break;
7292                     }
7293                   else if (pr == NULL && qr != NULL)
7294                     {
7295                       gfc_error ("Allocate-object at %L is subobject of"
7296                                  " object at %L", &qe->where, &pe->where);
7297                       break;
7298                     }
7299                   /* Here, pr != NULL && qr != NULL  */
7300                   gcc_assert(pr->type == qr->type);
7301                   if (pr->type == REF_ARRAY)
7302                     {
7303                       /* Handle cases like allocate(v(3)%x(3), v(2)%x(3)),
7304                          which are legal.  */
7305                       gcc_assert (qr->type == REF_ARRAY);
7306
7307                       if (pr->next && qr->next)
7308                         {
7309                           gfc_array_ref *par = &(pr->u.ar);
7310                           gfc_array_ref *qar = &(qr->u.ar);
7311                           if (gfc_dep_compare_expr (par->start[0],
7312                                                     qar->start[0]) != 0)
7313                               break;
7314                         }
7315                     }
7316                   else
7317                     {
7318                       if (pr->u.c.component->name != qr->u.c.component->name)
7319                         break;
7320                     }
7321                   
7322                   pr = pr->next;
7323                   qr = qr->next;
7324                 }
7325             }
7326         }
7327     }
7328
7329   if (strcmp (fcn, "ALLOCATE") == 0)
7330     {
7331       for (a = code->ext.alloc.list; a; a = a->next)
7332         resolve_allocate_expr (a->expr, code);
7333     }
7334   else
7335     {
7336       for (a = code->ext.alloc.list; a; a = a->next)
7337         resolve_deallocate_expr (a->expr);
7338     }
7339 }
7340
7341
7342 /************ SELECT CASE resolution subroutines ************/
7343
7344 /* Callback function for our mergesort variant.  Determines interval
7345    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7346    op1 > op2.  Assumes we're not dealing with the default case.  
7347    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7348    There are nine situations to check.  */
7349
7350 static int
7351 compare_cases (const gfc_case *op1, const gfc_case *op2)
7352 {
7353   int retval;
7354
7355   if (op1->low == NULL) /* op1 = (:L)  */
7356     {
7357       /* op2 = (:N), so overlap.  */
7358       retval = 0;
7359       /* op2 = (M:) or (M:N),  L < M  */
7360       if (op2->low != NULL
7361           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7362         retval = -1;
7363     }
7364   else if (op1->high == NULL) /* op1 = (K:)  */
7365     {
7366       /* op2 = (M:), so overlap.  */
7367       retval = 0;
7368       /* op2 = (:N) or (M:N), K > N  */
7369       if (op2->high != NULL
7370           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7371         retval = 1;
7372     }
7373   else /* op1 = (K:L)  */
7374     {
7375       if (op2->low == NULL)       /* op2 = (:N), K > N  */
7376         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7377                  ? 1 : 0;
7378       else if (op2->high == NULL) /* op2 = (M:), L < M  */
7379         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7380                  ? -1 : 0;
7381       else                      /* op2 = (M:N)  */
7382         {
7383           retval =  0;
7384           /* L < M  */
7385           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7386             retval =  -1;
7387           /* K > N  */
7388           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7389             retval =  1;
7390         }
7391     }
7392
7393   return retval;
7394 }
7395
7396
7397 /* Merge-sort a double linked case list, detecting overlap in the
7398    process.  LIST is the head of the double linked case list before it
7399    is sorted.  Returns the head of the sorted list if we don't see any
7400    overlap, or NULL otherwise.  */
7401
7402 static gfc_case *
7403 check_case_overlap (gfc_case *list)
7404 {
7405   gfc_case *p, *q, *e, *tail;
7406   int insize, nmerges, psize, qsize, cmp, overlap_seen;
7407
7408   /* If the passed list was empty, return immediately.  */
7409   if (!list)
7410     return NULL;
7411
7412   overlap_seen = 0;
7413   insize = 1;
7414
7415   /* Loop unconditionally.  The only exit from this loop is a return
7416      statement, when we've finished sorting the case list.  */
7417   for (;;)
7418     {
7419       p = list;
7420       list = NULL;
7421       tail = NULL;
7422
7423       /* Count the number of merges we do in this pass.  */
7424       nmerges = 0;
7425
7426       /* Loop while there exists a merge to be done.  */
7427       while (p)
7428         {
7429           int i;
7430
7431           /* Count this merge.  */
7432           nmerges++;
7433
7434           /* Cut the list in two pieces by stepping INSIZE places
7435              forward in the list, starting from P.  */
7436           psize = 0;
7437           q = p;
7438           for (i = 0; i < insize; i++)
7439             {
7440               psize++;
7441               q = q->right;
7442               if (!q)
7443                 break;
7444             }
7445           qsize = insize;
7446
7447           /* Now we have two lists.  Merge them!  */
7448           while (psize > 0 || (qsize > 0 && q != NULL))
7449             {
7450               /* See from which the next case to merge comes from.  */
7451               if (psize == 0)
7452                 {
7453                   /* P is empty so the next case must come from Q.  */
7454                   e = q;
7455                   q = q->right;
7456                   qsize--;
7457                 }
7458               else if (qsize == 0 || q == NULL)
7459                 {
7460                   /* Q is empty.  */
7461                   e = p;
7462                   p = p->right;
7463                   psize--;
7464                 }
7465               else
7466                 {
7467                   cmp = compare_cases (p, q);
7468                   if (cmp < 0)
7469                     {
7470                       /* The whole case range for P is less than the
7471                          one for Q.  */
7472                       e = p;
7473                       p = p->right;
7474                       psize--;
7475                     }
7476                   else if (cmp > 0)
7477                     {
7478                       /* The whole case range for Q is greater than
7479                          the case range for P.  */
7480                       e = q;
7481                       q = q->right;
7482                       qsize--;
7483                     }
7484                   else
7485                     {
7486                       /* The cases overlap, or they are the same
7487                          element in the list.  Either way, we must
7488                          issue an error and get the next case from P.  */
7489                       /* FIXME: Sort P and Q by line number.  */
7490                       gfc_error ("CASE label at %L overlaps with CASE "
7491                                  "label at %L", &p->where, &q->where);
7492                       overlap_seen = 1;
7493                       e = p;
7494                       p = p->right;
7495                       psize--;
7496                     }
7497                 }
7498
7499                 /* Add the next element to the merged list.  */
7500               if (tail)
7501                 tail->right = e;
7502               else
7503                 list = e;
7504               e->left = tail;
7505               tail = e;
7506             }
7507
7508           /* P has now stepped INSIZE places along, and so has Q.  So
7509              they're the same.  */
7510           p = q;
7511         }
7512       tail->right = NULL;
7513
7514       /* If we have done only one merge or none at all, we've
7515          finished sorting the cases.  */
7516       if (nmerges <= 1)
7517         {
7518           if (!overlap_seen)
7519             return list;
7520           else
7521             return NULL;
7522         }
7523
7524       /* Otherwise repeat, merging lists twice the size.  */
7525       insize *= 2;
7526     }
7527 }
7528
7529
7530 /* Check to see if an expression is suitable for use in a CASE statement.
7531    Makes sure that all case expressions are scalar constants of the same
7532    type.  Return FAILURE if anything is wrong.  */
7533
7534 static gfc_try
7535 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7536 {
7537   if (e == NULL) return SUCCESS;
7538
7539   if (e->ts.type != case_expr->ts.type)
7540     {
7541       gfc_error ("Expression in CASE statement at %L must be of type %s",
7542                  &e->where, gfc_basic_typename (case_expr->ts.type));
7543       return FAILURE;
7544     }
7545
7546   /* C805 (R808) For a given case-construct, each case-value shall be of
7547      the same type as case-expr.  For character type, length differences
7548      are allowed, but the kind type parameters shall be the same.  */
7549
7550   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7551     {
7552       gfc_error ("Expression in CASE statement at %L must be of kind %d",
7553                  &e->where, case_expr->ts.kind);
7554       return FAILURE;
7555     }
7556
7557   /* Convert the case value kind to that of case expression kind,
7558      if needed */
7559
7560   if (e->ts.kind != case_expr->ts.kind)
7561     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7562
7563   if (e->rank != 0)
7564     {
7565       gfc_error ("Expression in CASE statement at %L must be scalar",
7566                  &e->where);
7567       return FAILURE;
7568     }
7569
7570   return SUCCESS;
7571 }
7572
7573
7574 /* Given a completely parsed select statement, we:
7575
7576      - Validate all expressions and code within the SELECT.
7577      - Make sure that the selection expression is not of the wrong type.
7578      - Make sure that no case ranges overlap.
7579      - Eliminate unreachable cases and unreachable code resulting from
7580        removing case labels.
7581
7582    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7583    they are a hassle for code generation, and to prevent that, we just
7584    cut them out here.  This is not necessary for overlapping cases
7585    because they are illegal and we never even try to generate code.
7586
7587    We have the additional caveat that a SELECT construct could have
7588    been a computed GOTO in the source code. Fortunately we can fairly
7589    easily work around that here: The case_expr for a "real" SELECT CASE
7590    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7591    we have to do is make sure that the case_expr is a scalar integer
7592    expression.  */
7593
7594 static void
7595 resolve_select (gfc_code *code)
7596 {
7597   gfc_code *body;
7598   gfc_expr *case_expr;
7599   gfc_case *cp, *default_case, *tail, *head;
7600   int seen_unreachable;
7601   int seen_logical;
7602   int ncases;
7603   bt type;
7604   gfc_try t;
7605
7606   if (code->expr1 == NULL)
7607     {
7608       /* This was actually a computed GOTO statement.  */
7609       case_expr = code->expr2;
7610       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7611         gfc_error ("Selection expression in computed GOTO statement "
7612                    "at %L must be a scalar integer expression",
7613                    &case_expr->where);
7614
7615       /* Further checking is not necessary because this SELECT was built
7616          by the compiler, so it should always be OK.  Just move the
7617          case_expr from expr2 to expr so that we can handle computed
7618          GOTOs as normal SELECTs from here on.  */
7619       code->expr1 = code->expr2;
7620       code->expr2 = NULL;
7621       return;
7622     }
7623
7624   case_expr = code->expr1;
7625
7626   type = case_expr->ts.type;
7627   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7628     {
7629       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7630                  &case_expr->where, gfc_typename (&case_expr->ts));
7631
7632       /* Punt. Going on here just produce more garbage error messages.  */
7633       return;
7634     }
7635
7636   /* Raise a warning if an INTEGER case value exceeds the range of
7637      the case-expr. Later, all expressions will be promoted to the
7638      largest kind of all case-labels.  */
7639
7640   if (type == BT_INTEGER)
7641     for (body = code->block; body; body = body->block)
7642       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7643         {
7644           if (cp->low
7645               && gfc_check_integer_range (cp->low->value.integer,
7646                                           case_expr->ts.kind) != ARITH_OK)
7647             gfc_warning ("Expression in CASE statement at %L is "
7648                          "not in the range of %s", &cp->low->where,
7649                          gfc_typename (&case_expr->ts));
7650
7651           if (cp->high
7652               && cp->low != cp->high
7653               && gfc_check_integer_range (cp->high->value.integer,
7654                                           case_expr->ts.kind) != ARITH_OK)
7655             gfc_warning ("Expression in CASE statement at %L is "
7656                          "not in the range of %s", &cp->high->where,
7657                          gfc_typename (&case_expr->ts));
7658         }
7659
7660   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7661      of the SELECT CASE expression and its CASE values.  Walk the lists
7662      of case values, and if we find a mismatch, promote case_expr to
7663      the appropriate kind.  */
7664
7665   if (type == BT_LOGICAL || type == BT_INTEGER)
7666     {
7667       for (body = code->block; body; body = body->block)
7668         {
7669           /* Walk the case label list.  */
7670           for (cp = body->ext.block.case_list; cp; cp = cp->next)
7671             {
7672               /* Intercept the DEFAULT case.  It does not have a kind.  */
7673               if (cp->low == NULL && cp->high == NULL)
7674                 continue;
7675
7676               /* Unreachable case ranges are discarded, so ignore.  */
7677               if (cp->low != NULL && cp->high != NULL
7678                   && cp->low != cp->high
7679                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7680                 continue;
7681
7682               if (cp->low != NULL
7683                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7684                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7685
7686               if (cp->high != NULL
7687                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7688                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7689             }
7690          }
7691     }
7692
7693   /* Assume there is no DEFAULT case.  */
7694   default_case = NULL;
7695   head = tail = NULL;
7696   ncases = 0;
7697   seen_logical = 0;
7698
7699   for (body = code->block; body; body = body->block)
7700     {
7701       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7702       t = SUCCESS;
7703       seen_unreachable = 0;
7704
7705       /* Walk the case label list, making sure that all case labels
7706          are legal.  */
7707       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7708         {
7709           /* Count the number of cases in the whole construct.  */
7710           ncases++;
7711
7712           /* Intercept the DEFAULT case.  */
7713           if (cp->low == NULL && cp->high == NULL)
7714             {
7715               if (default_case != NULL)
7716                 {
7717                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7718                              "by a second DEFAULT CASE at %L",
7719                              &default_case->where, &cp->where);
7720                   t = FAILURE;
7721                   break;
7722                 }
7723               else
7724                 {
7725                   default_case = cp;
7726                   continue;
7727                 }
7728             }
7729
7730           /* Deal with single value cases and case ranges.  Errors are
7731              issued from the validation function.  */
7732           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7733               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7734             {
7735               t = FAILURE;
7736               break;
7737             }
7738
7739           if (type == BT_LOGICAL
7740               && ((cp->low == NULL || cp->high == NULL)
7741                   || cp->low != cp->high))
7742             {
7743               gfc_error ("Logical range in CASE statement at %L is not "
7744                          "allowed", &cp->low->where);
7745               t = FAILURE;
7746               break;
7747             }
7748
7749           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7750             {
7751               int value;
7752               value = cp->low->value.logical == 0 ? 2 : 1;
7753               if (value & seen_logical)
7754                 {
7755                   gfc_error ("Constant logical value in CASE statement "
7756                              "is repeated at %L",
7757                              &cp->low->where);
7758                   t = FAILURE;
7759                   break;
7760                 }
7761               seen_logical |= value;
7762             }
7763
7764           if (cp->low != NULL && cp->high != NULL
7765               && cp->low != cp->high
7766               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7767             {
7768               if (gfc_option.warn_surprising)
7769                 gfc_warning ("Range specification at %L can never "
7770                              "be matched", &cp->where);
7771
7772               cp->unreachable = 1;
7773               seen_unreachable = 1;
7774             }
7775           else
7776             {
7777               /* If the case range can be matched, it can also overlap with
7778                  other cases.  To make sure it does not, we put it in a
7779                  double linked list here.  We sort that with a merge sort
7780                  later on to detect any overlapping cases.  */
7781               if (!head)
7782                 {
7783                   head = tail = cp;
7784                   head->right = head->left = NULL;
7785                 }
7786               else
7787                 {
7788                   tail->right = cp;
7789                   tail->right->left = tail;
7790                   tail = tail->right;
7791                   tail->right = NULL;
7792                 }
7793             }
7794         }
7795
7796       /* It there was a failure in the previous case label, give up
7797          for this case label list.  Continue with the next block.  */
7798       if (t == FAILURE)
7799         continue;
7800
7801       /* See if any case labels that are unreachable have been seen.
7802          If so, we eliminate them.  This is a bit of a kludge because
7803          the case lists for a single case statement (label) is a
7804          single forward linked lists.  */
7805       if (seen_unreachable)
7806       {
7807         /* Advance until the first case in the list is reachable.  */
7808         while (body->ext.block.case_list != NULL
7809                && body->ext.block.case_list->unreachable)
7810           {
7811             gfc_case *n = body->ext.block.case_list;
7812             body->ext.block.case_list = body->ext.block.case_list->next;
7813             n->next = NULL;
7814             gfc_free_case_list (n);
7815           }
7816
7817         /* Strip all other unreachable cases.  */
7818         if (body->ext.block.case_list)
7819           {
7820             for (cp = body->ext.block.case_list; cp->next; cp = cp->next)
7821               {
7822                 if (cp->next->unreachable)
7823                   {
7824                     gfc_case *n = cp->next;
7825                     cp->next = cp->next->next;
7826                     n->next = NULL;
7827                     gfc_free_case_list (n);
7828                   }
7829               }
7830           }
7831       }
7832     }
7833
7834   /* See if there were overlapping cases.  If the check returns NULL,
7835      there was overlap.  In that case we don't do anything.  If head
7836      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7837      then used during code generation for SELECT CASE constructs with
7838      a case expression of a CHARACTER type.  */
7839   if (head)
7840     {
7841       head = check_case_overlap (head);
7842
7843       /* Prepend the default_case if it is there.  */
7844       if (head != NULL && default_case)
7845         {
7846           default_case->left = NULL;
7847           default_case->right = head;
7848           head->left = default_case;
7849         }
7850     }
7851
7852   /* Eliminate dead blocks that may be the result if we've seen
7853      unreachable case labels for a block.  */
7854   for (body = code; body && body->block; body = body->block)
7855     {
7856       if (body->block->ext.block.case_list == NULL)
7857         {
7858           /* Cut the unreachable block from the code chain.  */
7859           gfc_code *c = body->block;
7860           body->block = c->block;
7861
7862           /* Kill the dead block, but not the blocks below it.  */
7863           c->block = NULL;
7864           gfc_free_statements (c);
7865         }
7866     }
7867
7868   /* More than two cases is legal but insane for logical selects.
7869      Issue a warning for it.  */
7870   if (gfc_option.warn_surprising && type == BT_LOGICAL
7871       && ncases > 2)
7872     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7873                  &code->loc);
7874 }
7875
7876
7877 /* Check if a derived type is extensible.  */
7878
7879 bool
7880 gfc_type_is_extensible (gfc_symbol *sym)
7881 {
7882   return !(sym->attr.is_bind_c || sym->attr.sequence);
7883 }
7884
7885
7886 /* Resolve an associate name:  Resolve target and ensure the type-spec is
7887    correct as well as possibly the array-spec.  */
7888
7889 static void
7890 resolve_assoc_var (gfc_symbol* sym, bool resolve_target)
7891 {
7892   gfc_expr* target;
7893
7894   gcc_assert (sym->assoc);
7895   gcc_assert (sym->attr.flavor == FL_VARIABLE);
7896
7897   /* If this is for SELECT TYPE, the target may not yet be set.  In that
7898      case, return.  Resolution will be called later manually again when
7899      this is done.  */
7900   target = sym->assoc->target;
7901   if (!target)
7902     return;
7903   gcc_assert (!sym->assoc->dangling);
7904
7905   if (resolve_target && gfc_resolve_expr (target) != SUCCESS)
7906     return;
7907
7908   /* For variable targets, we get some attributes from the target.  */
7909   if (target->expr_type == EXPR_VARIABLE)
7910     {
7911       gfc_symbol* tsym;
7912
7913       gcc_assert (target->symtree);
7914       tsym = target->symtree->n.sym;
7915
7916       sym->attr.asynchronous = tsym->attr.asynchronous;
7917       sym->attr.volatile_ = tsym->attr.volatile_;
7918
7919       if (tsym->ts.type == BT_CLASS)
7920         sym->attr.target = tsym->attr.target || CLASS_DATA (tsym)->attr.pointer;
7921       else
7922         sym->attr.target = tsym->attr.target || tsym->attr.pointer;
7923
7924       if (sym->ts.type == BT_DERIVED && tsym->ts.type == BT_CLASS)
7925         target->rank = sym->as ? sym->as->rank : 0;
7926     }
7927
7928   /* Get type if this was not already set.  Note that it can be
7929      some other type than the target in case this is a SELECT TYPE
7930      selector!  So we must not update when the type is already there.  */
7931   if (sym->ts.type == BT_UNKNOWN)
7932     sym->ts = target->ts;
7933   gcc_assert (sym->ts.type != BT_UNKNOWN);
7934
7935   /* See if this is a valid association-to-variable.  */
7936   sym->assoc->variable = (target->expr_type == EXPR_VARIABLE
7937                           && !gfc_has_vector_subscript (target));
7938
7939   /* Finally resolve if this is an array or not.  */
7940   if (sym->attr.dimension
7941         && (target->ts.type == BT_CLASS
7942               ? !CLASS_DATA (target)->attr.dimension
7943               : target->rank == 0))
7944     {
7945       gfc_error ("Associate-name '%s' at %L is used as array",
7946                  sym->name, &sym->declared_at);
7947       sym->attr.dimension = 0;
7948       return;
7949     }
7950   if (target->rank > 0)
7951     sym->attr.dimension = 1;
7952
7953   if (sym->attr.dimension)
7954     {
7955       sym->as = gfc_get_array_spec ();
7956       sym->as->rank = target->rank;
7957       sym->as->type = AS_DEFERRED;
7958
7959       /* Target must not be coindexed, thus the associate-variable
7960          has no corank.  */
7961       sym->as->corank = 0;
7962     }
7963 }
7964
7965
7966 /* Resolve a SELECT TYPE statement.  */
7967
7968 static void
7969 resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
7970 {
7971   gfc_symbol *selector_type;
7972   gfc_code *body, *new_st, *if_st, *tail;
7973   gfc_code *class_is = NULL, *default_case = NULL;
7974   gfc_case *c;
7975   gfc_symtree *st;
7976   char name[GFC_MAX_SYMBOL_LEN];
7977   gfc_namespace *ns;
7978   int error = 0;
7979
7980   ns = code->ext.block.ns;
7981   gfc_resolve (ns);
7982
7983   /* Check for F03:C813.  */
7984   if (code->expr1->ts.type != BT_CLASS
7985       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
7986     {
7987       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
7988                  "at %L", &code->loc);
7989       return;
7990     }
7991
7992   if (!code->expr1->symtree->n.sym->attr.class_ok)
7993     return;
7994
7995   if (code->expr2)
7996     {
7997       if (code->expr1->symtree->n.sym->attr.untyped)
7998         code->expr1->symtree->n.sym->ts = code->expr2->ts;
7999       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
8000     }
8001   else
8002     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
8003
8004   /* Loop over TYPE IS / CLASS IS cases.  */
8005   for (body = code->block; body; body = body->block)
8006     {
8007       c = body->ext.block.case_list;
8008
8009       /* Check F03:C815.  */
8010       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
8011           && !gfc_type_is_extensible (c->ts.u.derived))
8012         {
8013           gfc_error ("Derived type '%s' at %L must be extensible",
8014                      c->ts.u.derived->name, &c->where);
8015           error++;
8016           continue;
8017         }
8018
8019       /* Check F03:C816.  */
8020       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
8021           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
8022         {
8023           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
8024                      c->ts.u.derived->name, &c->where, selector_type->name);
8025           error++;
8026           continue;
8027         }
8028
8029       /* Intercept the DEFAULT case.  */
8030       if (c->ts.type == BT_UNKNOWN)
8031         {
8032           /* Check F03:C818.  */
8033           if (default_case)
8034             {
8035               gfc_error ("The DEFAULT CASE at %L cannot be followed "
8036                          "by a second DEFAULT CASE at %L",
8037                          &default_case->ext.block.case_list->where, &c->where);
8038               error++;
8039               continue;
8040             }
8041
8042           default_case = body;
8043         }
8044     }
8045     
8046   if (error > 0)
8047     return;
8048
8049   /* Transform SELECT TYPE statement to BLOCK and associate selector to
8050      target if present.  If there are any EXIT statements referring to the
8051      SELECT TYPE construct, this is no problem because the gfc_code
8052      reference stays the same and EXIT is equally possible from the BLOCK
8053      it is changed to.  */
8054   code->op = EXEC_BLOCK;
8055   if (code->expr2)
8056     {
8057       gfc_association_list* assoc;
8058
8059       assoc = gfc_get_association_list ();
8060       assoc->st = code->expr1->symtree;
8061       assoc->target = gfc_copy_expr (code->expr2);
8062       assoc->target->where = code->expr2->where;
8063       /* assoc->variable will be set by resolve_assoc_var.  */
8064       
8065       code->ext.block.assoc = assoc;
8066       code->expr1->symtree->n.sym->assoc = assoc;
8067
8068       resolve_assoc_var (code->expr1->symtree->n.sym, false);
8069     }
8070   else
8071     code->ext.block.assoc = NULL;
8072
8073   /* Add EXEC_SELECT to switch on type.  */
8074   new_st = gfc_get_code ();
8075   new_st->op = code->op;
8076   new_st->expr1 = code->expr1;
8077   new_st->expr2 = code->expr2;
8078   new_st->block = code->block;
8079   code->expr1 = code->expr2 =  NULL;
8080   code->block = NULL;
8081   if (!ns->code)
8082     ns->code = new_st;
8083   else
8084     ns->code->next = new_st;
8085   code = new_st;
8086   code->op = EXEC_SELECT;
8087   gfc_add_vptr_component (code->expr1);
8088   gfc_add_hash_component (code->expr1);
8089
8090   /* Loop over TYPE IS / CLASS IS cases.  */
8091   for (body = code->block; body; body = body->block)
8092     {
8093       c = body->ext.block.case_list;
8094
8095       if (c->ts.type == BT_DERIVED)
8096         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
8097                                              c->ts.u.derived->hash_value);
8098
8099       else if (c->ts.type == BT_UNKNOWN)
8100         continue;
8101
8102       /* Associate temporary to selector.  This should only be done
8103          when this case is actually true, so build a new ASSOCIATE
8104          that does precisely this here (instead of using the
8105          'global' one).  */
8106
8107       if (c->ts.type == BT_CLASS)
8108         sprintf (name, "__tmp_class_%s", c->ts.u.derived->name);
8109       else
8110         sprintf (name, "__tmp_type_%s", c->ts.u.derived->name);
8111       st = gfc_find_symtree (ns->sym_root, name);
8112       gcc_assert (st->n.sym->assoc);
8113       st->n.sym->assoc->target = gfc_get_variable_expr (code->expr1->symtree);
8114       st->n.sym->assoc->target->where = code->expr1->where;
8115       if (c->ts.type == BT_DERIVED)
8116         gfc_add_data_component (st->n.sym->assoc->target);
8117
8118       new_st = gfc_get_code ();
8119       new_st->op = EXEC_BLOCK;
8120       new_st->ext.block.ns = gfc_build_block_ns (ns);
8121       new_st->ext.block.ns->code = body->next;
8122       body->next = new_st;
8123
8124       /* Chain in the new list only if it is marked as dangling.  Otherwise
8125          there is a CASE label overlap and this is already used.  Just ignore,
8126          the error is diagonsed elsewhere.  */
8127       if (st->n.sym->assoc->dangling)
8128         {
8129           new_st->ext.block.assoc = st->n.sym->assoc;
8130           st->n.sym->assoc->dangling = 0;
8131         }
8132
8133       resolve_assoc_var (st->n.sym, false);
8134     }
8135     
8136   /* Take out CLASS IS cases for separate treatment.  */
8137   body = code;
8138   while (body && body->block)
8139     {
8140       if (body->block->ext.block.case_list->ts.type == BT_CLASS)
8141         {
8142           /* Add to class_is list.  */
8143           if (class_is == NULL)
8144             { 
8145               class_is = body->block;
8146               tail = class_is;
8147             }
8148           else
8149             {
8150               for (tail = class_is; tail->block; tail = tail->block) ;
8151               tail->block = body->block;
8152               tail = tail->block;
8153             }
8154           /* Remove from EXEC_SELECT list.  */
8155           body->block = body->block->block;
8156           tail->block = NULL;
8157         }
8158       else
8159         body = body->block;
8160     }
8161
8162   if (class_is)
8163     {
8164       gfc_symbol *vtab;
8165       
8166       if (!default_case)
8167         {
8168           /* Add a default case to hold the CLASS IS cases.  */
8169           for (tail = code; tail->block; tail = tail->block) ;
8170           tail->block = gfc_get_code ();
8171           tail = tail->block;
8172           tail->op = EXEC_SELECT_TYPE;
8173           tail->ext.block.case_list = gfc_get_case ();
8174           tail->ext.block.case_list->ts.type = BT_UNKNOWN;
8175           tail->next = NULL;
8176           default_case = tail;
8177         }
8178
8179       /* More than one CLASS IS block?  */
8180       if (class_is->block)
8181         {
8182           gfc_code **c1,*c2;
8183           bool swapped;
8184           /* Sort CLASS IS blocks by extension level.  */
8185           do
8186             {
8187               swapped = false;
8188               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
8189                 {
8190                   c2 = (*c1)->block;
8191                   /* F03:C817 (check for doubles).  */
8192                   if ((*c1)->ext.block.case_list->ts.u.derived->hash_value
8193                       == c2->ext.block.case_list->ts.u.derived->hash_value)
8194                     {
8195                       gfc_error ("Double CLASS IS block in SELECT TYPE "
8196                                  "statement at %L",
8197                                  &c2->ext.block.case_list->where);
8198                       return;
8199                     }
8200                   if ((*c1)->ext.block.case_list->ts.u.derived->attr.extension
8201                       < c2->ext.block.case_list->ts.u.derived->attr.extension)
8202                     {
8203                       /* Swap.  */
8204                       (*c1)->block = c2->block;
8205                       c2->block = *c1;
8206                       *c1 = c2;
8207                       swapped = true;
8208                     }
8209                 }
8210             }
8211           while (swapped);
8212         }
8213         
8214       /* Generate IF chain.  */
8215       if_st = gfc_get_code ();
8216       if_st->op = EXEC_IF;
8217       new_st = if_st;
8218       for (body = class_is; body; body = body->block)
8219         {
8220           new_st->block = gfc_get_code ();
8221           new_st = new_st->block;
8222           new_st->op = EXEC_IF;
8223           /* Set up IF condition: Call _gfortran_is_extension_of.  */
8224           new_st->expr1 = gfc_get_expr ();
8225           new_st->expr1->expr_type = EXPR_FUNCTION;
8226           new_st->expr1->ts.type = BT_LOGICAL;
8227           new_st->expr1->ts.kind = 4;
8228           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
8229           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
8230           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
8231           /* Set up arguments.  */
8232           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
8233           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
8234           new_st->expr1->value.function.actual->expr->where = code->loc;
8235           gfc_add_vptr_component (new_st->expr1->value.function.actual->expr);
8236           vtab = gfc_find_derived_vtab (body->ext.block.case_list->ts.u.derived);
8237           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
8238           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
8239           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
8240           new_st->next = body->next;
8241         }
8242         if (default_case->next)
8243           {
8244             new_st->block = gfc_get_code ();
8245             new_st = new_st->block;
8246             new_st->op = EXEC_IF;
8247             new_st->next = default_case->next;
8248           }
8249           
8250         /* Replace CLASS DEFAULT code by the IF chain.  */
8251         default_case->next = if_st;
8252     }
8253
8254   /* Resolve the internal code.  This can not be done earlier because
8255      it requires that the sym->assoc of selectors is set already.  */
8256   gfc_current_ns = ns;
8257   gfc_resolve_blocks (code->block, gfc_current_ns);
8258   gfc_current_ns = old_ns;
8259
8260   resolve_select (code);
8261 }
8262
8263
8264 /* Resolve a transfer statement. This is making sure that:
8265    -- a derived type being transferred has only non-pointer components
8266    -- a derived type being transferred doesn't have private components, unless 
8267       it's being transferred from the module where the type was defined
8268    -- we're not trying to transfer a whole assumed size array.  */
8269
8270 static void
8271 resolve_transfer (gfc_code *code)
8272 {
8273   gfc_typespec *ts;
8274   gfc_symbol *sym;
8275   gfc_ref *ref;
8276   gfc_expr *exp;
8277
8278   exp = code->expr1;
8279
8280   while (exp != NULL && exp->expr_type == EXPR_OP
8281          && exp->value.op.op == INTRINSIC_PARENTHESES)
8282     exp = exp->value.op.op1;
8283
8284   if (exp && exp->expr_type == EXPR_NULL && exp->ts.type == BT_UNKNOWN)
8285     {
8286       gfc_error ("NULL intrinsic at %L in data transfer statement requires "
8287                  "MOLD=", &exp->where);
8288       return;
8289     }
8290
8291   if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
8292                       && exp->expr_type != EXPR_FUNCTION))
8293     return;
8294
8295   /* If we are reading, the variable will be changed.  Note that
8296      code->ext.dt may be NULL if the TRANSFER is related to
8297      an INQUIRE statement -- but in this case, we are not reading, either.  */
8298   if (code->ext.dt && code->ext.dt->dt_io_kind->value.iokind == M_READ
8299       && gfc_check_vardef_context (exp, false, false, _("item in READ"))
8300          == FAILURE)
8301     return;
8302
8303   sym = exp->symtree->n.sym;
8304   ts = &sym->ts;
8305
8306   /* Go to actual component transferred.  */
8307   for (ref = exp->ref; ref; ref = ref->next)
8308     if (ref->type == REF_COMPONENT)
8309       ts = &ref->u.c.component->ts;
8310
8311   if (ts->type == BT_CLASS)
8312     {
8313       /* FIXME: Test for defined input/output.  */
8314       gfc_error ("Data transfer element at %L cannot be polymorphic unless "
8315                 "it is processed by a defined input/output procedure",
8316                 &code->loc);
8317       return;
8318     }
8319
8320   if (ts->type == BT_DERIVED)
8321     {
8322       /* Check that transferred derived type doesn't contain POINTER
8323          components.  */
8324       if (ts->u.derived->attr.pointer_comp)
8325         {
8326           gfc_error ("Data transfer element at %L cannot have POINTER "
8327                      "components unless it is processed by a defined "
8328                      "input/output procedure", &code->loc);
8329           return;
8330         }
8331
8332       /* F08:C935.  */
8333       if (ts->u.derived->attr.proc_pointer_comp)
8334         {
8335           gfc_error ("Data transfer element at %L cannot have "
8336                      "procedure pointer components", &code->loc);
8337           return;
8338         }
8339
8340       if (ts->u.derived->attr.alloc_comp)
8341         {
8342           gfc_error ("Data transfer element at %L cannot have ALLOCATABLE "
8343                      "components unless it is processed by a defined "
8344                      "input/output procedure", &code->loc);
8345           return;
8346         }
8347
8348       if (derived_inaccessible (ts->u.derived))
8349         {
8350           gfc_error ("Data transfer element at %L cannot have "
8351                      "PRIVATE components",&code->loc);
8352           return;
8353         }
8354     }
8355
8356   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE && exp->ref
8357       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
8358     {
8359       gfc_error ("Data transfer element at %L cannot be a full reference to "
8360                  "an assumed-size array", &code->loc);
8361       return;
8362     }
8363 }
8364
8365
8366 /*********** Toplevel code resolution subroutines ***********/
8367
8368 /* Find the set of labels that are reachable from this block.  We also
8369    record the last statement in each block.  */
8370      
8371 static void
8372 find_reachable_labels (gfc_code *block)
8373 {
8374   gfc_code *c;
8375
8376   if (!block)
8377     return;
8378
8379   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
8380
8381   /* Collect labels in this block.  We don't keep those corresponding
8382      to END {IF|SELECT}, these are checked in resolve_branch by going
8383      up through the code_stack.  */
8384   for (c = block; c; c = c->next)
8385     {
8386       if (c->here && c->op != EXEC_END_NESTED_BLOCK)
8387         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
8388     }
8389
8390   /* Merge with labels from parent block.  */
8391   if (cs_base->prev)
8392     {
8393       gcc_assert (cs_base->prev->reachable_labels);
8394       bitmap_ior_into (cs_base->reachable_labels,
8395                        cs_base->prev->reachable_labels);
8396     }
8397 }
8398
8399
8400 static void
8401 resolve_lock_unlock (gfc_code *code)
8402 {
8403   if (code->expr1->ts.type != BT_DERIVED
8404       || code->expr1->expr_type != EXPR_VARIABLE
8405       || code->expr1->ts.u.derived->from_intmod != INTMOD_ISO_FORTRAN_ENV
8406       || code->expr1->ts.u.derived->intmod_sym_id != ISOFORTRAN_LOCK_TYPE
8407       || code->expr1->rank != 0
8408       || (!gfc_is_coarray (code->expr1) && !gfc_is_coindexed (code->expr1)))
8409     gfc_error ("Lock variable at %L must be a scalar of type LOCK_TYPE",
8410                &code->expr1->where);
8411
8412   /* Check STAT.  */
8413   if (code->expr2
8414       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8415           || code->expr2->expr_type != EXPR_VARIABLE))
8416     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8417                &code->expr2->where);
8418
8419   if (code->expr2
8420       && gfc_check_vardef_context (code->expr2, false, false,
8421                                    _("STAT variable")) == FAILURE)
8422     return;
8423
8424   /* Check ERRMSG.  */
8425   if (code->expr3
8426       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8427           || code->expr3->expr_type != EXPR_VARIABLE))
8428     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8429                &code->expr3->where);
8430
8431   if (code->expr3
8432       && gfc_check_vardef_context (code->expr3, false, false,
8433                                    _("ERRMSG variable")) == FAILURE)
8434     return;
8435
8436   /* Check ACQUIRED_LOCK.  */
8437   if (code->expr4
8438       && (code->expr4->ts.type != BT_LOGICAL || code->expr4->rank != 0
8439           || code->expr4->expr_type != EXPR_VARIABLE))
8440     gfc_error ("ACQUIRED_LOCK= argument at %L must be a scalar LOGICAL "
8441                "variable", &code->expr4->where);
8442
8443   if (code->expr4
8444       && gfc_check_vardef_context (code->expr4, false, false,
8445                                    _("ACQUIRED_LOCK variable")) == FAILURE)
8446     return;
8447 }
8448
8449
8450 static void
8451 resolve_sync (gfc_code *code)
8452 {
8453   /* Check imageset. The * case matches expr1 == NULL.  */
8454   if (code->expr1)
8455     {
8456       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
8457         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
8458                    "INTEGER expression", &code->expr1->where);
8459       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
8460           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
8461         gfc_error ("Imageset argument at %L must between 1 and num_images()",
8462                    &code->expr1->where);
8463       else if (code->expr1->expr_type == EXPR_ARRAY
8464                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
8465         {
8466            gfc_constructor *cons;
8467            cons = gfc_constructor_first (code->expr1->value.constructor);
8468            for (; cons; cons = gfc_constructor_next (cons))
8469              if (cons->expr->expr_type == EXPR_CONSTANT
8470                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
8471                gfc_error ("Imageset argument at %L must between 1 and "
8472                           "num_images()", &cons->expr->where);
8473         }
8474     }
8475
8476   /* Check STAT.  */
8477   if (code->expr2
8478       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8479           || code->expr2->expr_type != EXPR_VARIABLE))
8480     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8481                &code->expr2->where);
8482
8483   /* Check ERRMSG.  */
8484   if (code->expr3
8485       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8486           || code->expr3->expr_type != EXPR_VARIABLE))
8487     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8488                &code->expr3->where);
8489 }
8490
8491
8492 /* Given a branch to a label, see if the branch is conforming.
8493    The code node describes where the branch is located.  */
8494
8495 static void
8496 resolve_branch (gfc_st_label *label, gfc_code *code)
8497 {
8498   code_stack *stack;
8499
8500   if (label == NULL)
8501     return;
8502
8503   /* Step one: is this a valid branching target?  */
8504
8505   if (label->defined == ST_LABEL_UNKNOWN)
8506     {
8507       gfc_error ("Label %d referenced at %L is never defined", label->value,
8508                  &label->where);
8509       return;
8510     }
8511
8512   if (label->defined != ST_LABEL_TARGET)
8513     {
8514       gfc_error ("Statement at %L is not a valid branch target statement "
8515                  "for the branch statement at %L", &label->where, &code->loc);
8516       return;
8517     }
8518
8519   /* Step two: make sure this branch is not a branch to itself ;-)  */
8520
8521   if (code->here == label)
8522     {
8523       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
8524       return;
8525     }
8526
8527   /* Step three:  See if the label is in the same block as the
8528      branching statement.  The hard work has been done by setting up
8529      the bitmap reachable_labels.  */
8530
8531   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8532     {
8533       /* Check now whether there is a CRITICAL construct; if so, check
8534          whether the label is still visible outside of the CRITICAL block,
8535          which is invalid.  */
8536       for (stack = cs_base; stack; stack = stack->prev)
8537         {
8538           if (stack->current->op == EXEC_CRITICAL
8539               && bitmap_bit_p (stack->reachable_labels, label->value))
8540             gfc_error ("GOTO statement at %L leaves CRITICAL construct for "
8541                       "label at %L", &code->loc, &label->where);
8542           else if (stack->current->op == EXEC_DO_CONCURRENT
8543                    && bitmap_bit_p (stack->reachable_labels, label->value))
8544             gfc_error ("GOTO statement at %L leaves DO CONCURRENT construct "
8545                       "for label at %L", &code->loc, &label->where);
8546         }
8547
8548       return;
8549     }
8550
8551   /* Step four:  If we haven't found the label in the bitmap, it may
8552     still be the label of the END of the enclosing block, in which
8553     case we find it by going up the code_stack.  */
8554
8555   for (stack = cs_base; stack; stack = stack->prev)
8556     {
8557       if (stack->current->next && stack->current->next->here == label)
8558         break;
8559       if (stack->current->op == EXEC_CRITICAL)
8560         {
8561           /* Note: A label at END CRITICAL does not leave the CRITICAL
8562              construct as END CRITICAL is still part of it.  */
8563           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8564                       " at %L", &code->loc, &label->where);
8565           return;
8566         }
8567       else if (stack->current->op == EXEC_DO_CONCURRENT)
8568         {
8569           gfc_error ("GOTO statement at %L leaves DO CONCURRENT construct for "
8570                      "label at %L", &code->loc, &label->where);
8571           return;
8572         }
8573     }
8574
8575   if (stack)
8576     {
8577       gcc_assert (stack->current->next->op == EXEC_END_NESTED_BLOCK);
8578       return;
8579     }
8580
8581   /* The label is not in an enclosing block, so illegal.  This was
8582      allowed in Fortran 66, so we allow it as extension.  No
8583      further checks are necessary in this case.  */
8584   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
8585                   "as the GOTO statement at %L", &label->where,
8586                   &code->loc);
8587   return;
8588 }
8589
8590
8591 /* Check whether EXPR1 has the same shape as EXPR2.  */
8592
8593 static gfc_try
8594 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8595 {
8596   mpz_t shape[GFC_MAX_DIMENSIONS];
8597   mpz_t shape2[GFC_MAX_DIMENSIONS];
8598   gfc_try result = FAILURE;
8599   int i;
8600
8601   /* Compare the rank.  */
8602   if (expr1->rank != expr2->rank)
8603     return result;
8604
8605   /* Compare the size of each dimension.  */
8606   for (i=0; i<expr1->rank; i++)
8607     {
8608       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
8609         goto ignore;
8610
8611       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
8612         goto ignore;
8613
8614       if (mpz_cmp (shape[i], shape2[i]))
8615         goto over;
8616     }
8617
8618   /* When either of the two expression is an assumed size array, we
8619      ignore the comparison of dimension sizes.  */
8620 ignore:
8621   result = SUCCESS;
8622
8623 over:
8624   gfc_clear_shape (shape, i);
8625   gfc_clear_shape (shape2, i);
8626   return result;
8627 }
8628
8629
8630 /* Check whether a WHERE assignment target or a WHERE mask expression
8631    has the same shape as the outmost WHERE mask expression.  */
8632
8633 static void
8634 resolve_where (gfc_code *code, gfc_expr *mask)
8635 {
8636   gfc_code *cblock;
8637   gfc_code *cnext;
8638   gfc_expr *e = NULL;
8639
8640   cblock = code->block;
8641
8642   /* Store the first WHERE mask-expr of the WHERE statement or construct.
8643      In case of nested WHERE, only the outmost one is stored.  */
8644   if (mask == NULL) /* outmost WHERE */
8645     e = cblock->expr1;
8646   else /* inner WHERE */
8647     e = mask;
8648
8649   while (cblock)
8650     {
8651       if (cblock->expr1)
8652         {
8653           /* Check if the mask-expr has a consistent shape with the
8654              outmost WHERE mask-expr.  */
8655           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
8656             gfc_error ("WHERE mask at %L has inconsistent shape",
8657                        &cblock->expr1->where);
8658          }
8659
8660       /* the assignment statement of a WHERE statement, or the first
8661          statement in where-body-construct of a WHERE construct */
8662       cnext = cblock->next;
8663       while (cnext)
8664         {
8665           switch (cnext->op)
8666             {
8667             /* WHERE assignment statement */
8668             case EXEC_ASSIGN:
8669
8670               /* Check shape consistent for WHERE assignment target.  */
8671               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
8672                gfc_error ("WHERE assignment target at %L has "
8673                           "inconsistent shape", &cnext->expr1->where);
8674               break;
8675
8676   
8677             case EXEC_ASSIGN_CALL:
8678               resolve_call (cnext);
8679               if (!cnext->resolved_sym->attr.elemental)
8680                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8681                           &cnext->ext.actual->expr->where);
8682               break;
8683
8684             /* WHERE or WHERE construct is part of a where-body-construct */
8685             case EXEC_WHERE:
8686               resolve_where (cnext, e);
8687               break;
8688
8689             default:
8690               gfc_error ("Unsupported statement inside WHERE at %L",
8691                          &cnext->loc);
8692             }
8693          /* the next statement within the same where-body-construct */
8694          cnext = cnext->next;
8695        }
8696     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8697     cblock = cblock->block;
8698   }
8699 }
8700
8701
8702 /* Resolve assignment in FORALL construct.
8703    NVAR is the number of FORALL index variables, and VAR_EXPR records the
8704    FORALL index variables.  */
8705
8706 static void
8707 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8708 {
8709   int n;
8710
8711   for (n = 0; n < nvar; n++)
8712     {
8713       gfc_symbol *forall_index;
8714
8715       forall_index = var_expr[n]->symtree->n.sym;
8716
8717       /* Check whether the assignment target is one of the FORALL index
8718          variable.  */
8719       if ((code->expr1->expr_type == EXPR_VARIABLE)
8720           && (code->expr1->symtree->n.sym == forall_index))
8721         gfc_error ("Assignment to a FORALL index variable at %L",
8722                    &code->expr1->where);
8723       else
8724         {
8725           /* If one of the FORALL index variables doesn't appear in the
8726              assignment variable, then there could be a many-to-one
8727              assignment.  Emit a warning rather than an error because the
8728              mask could be resolving this problem.  */
8729           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
8730             gfc_warning ("The FORALL with index '%s' is not used on the "
8731                          "left side of the assignment at %L and so might "
8732                          "cause multiple assignment to this object",
8733                          var_expr[n]->symtree->name, &code->expr1->where);
8734         }
8735     }
8736 }
8737
8738
8739 /* Resolve WHERE statement in FORALL construct.  */
8740
8741 static void
8742 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
8743                                   gfc_expr **var_expr)
8744 {
8745   gfc_code *cblock;
8746   gfc_code *cnext;
8747
8748   cblock = code->block;
8749   while (cblock)
8750     {
8751       /* the assignment statement of a WHERE statement, or the first
8752          statement in where-body-construct of a WHERE construct */
8753       cnext = cblock->next;
8754       while (cnext)
8755         {
8756           switch (cnext->op)
8757             {
8758             /* WHERE assignment statement */
8759             case EXEC_ASSIGN:
8760               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
8761               break;
8762   
8763             /* WHERE operator assignment statement */
8764             case EXEC_ASSIGN_CALL:
8765               resolve_call (cnext);
8766               if (!cnext->resolved_sym->attr.elemental)
8767                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8768                           &cnext->ext.actual->expr->where);
8769               break;
8770
8771             /* WHERE or WHERE construct is part of a where-body-construct */
8772             case EXEC_WHERE:
8773               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
8774               break;
8775
8776             default:
8777               gfc_error ("Unsupported statement inside WHERE at %L",
8778                          &cnext->loc);
8779             }
8780           /* the next statement within the same where-body-construct */
8781           cnext = cnext->next;
8782         }
8783       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8784       cblock = cblock->block;
8785     }
8786 }
8787
8788
8789 /* Traverse the FORALL body to check whether the following errors exist:
8790    1. For assignment, check if a many-to-one assignment happens.
8791    2. For WHERE statement, check the WHERE body to see if there is any
8792       many-to-one assignment.  */
8793
8794 static void
8795 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
8796 {
8797   gfc_code *c;
8798
8799   c = code->block->next;
8800   while (c)
8801     {
8802       switch (c->op)
8803         {
8804         case EXEC_ASSIGN:
8805         case EXEC_POINTER_ASSIGN:
8806           gfc_resolve_assign_in_forall (c, nvar, var_expr);
8807           break;
8808
8809         case EXEC_ASSIGN_CALL:
8810           resolve_call (c);
8811           break;
8812
8813         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
8814            there is no need to handle it here.  */
8815         case EXEC_FORALL:
8816           break;
8817         case EXEC_WHERE:
8818           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
8819           break;
8820         default:
8821           break;
8822         }
8823       /* The next statement in the FORALL body.  */
8824       c = c->next;
8825     }
8826 }
8827
8828
8829 /* Counts the number of iterators needed inside a forall construct, including
8830    nested forall constructs. This is used to allocate the needed memory 
8831    in gfc_resolve_forall.  */
8832
8833 static int 
8834 gfc_count_forall_iterators (gfc_code *code)
8835 {
8836   int max_iters, sub_iters, current_iters;
8837   gfc_forall_iterator *fa;
8838
8839   gcc_assert(code->op == EXEC_FORALL);
8840   max_iters = 0;
8841   current_iters = 0;
8842
8843   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8844     current_iters ++;
8845   
8846   code = code->block->next;
8847
8848   while (code)
8849     {          
8850       if (code->op == EXEC_FORALL)
8851         {
8852           sub_iters = gfc_count_forall_iterators (code);
8853           if (sub_iters > max_iters)
8854             max_iters = sub_iters;
8855         }
8856       code = code->next;
8857     }
8858
8859   return current_iters + max_iters;
8860 }
8861
8862
8863 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8864    gfc_resolve_forall_body to resolve the FORALL body.  */
8865
8866 static void
8867 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8868 {
8869   static gfc_expr **var_expr;
8870   static int total_var = 0;
8871   static int nvar = 0;
8872   int old_nvar, tmp;
8873   gfc_forall_iterator *fa;
8874   int i;
8875
8876   old_nvar = nvar;
8877
8878   /* Start to resolve a FORALL construct   */
8879   if (forall_save == 0)
8880     {
8881       /* Count the total number of FORALL index in the nested FORALL
8882          construct in order to allocate the VAR_EXPR with proper size.  */
8883       total_var = gfc_count_forall_iterators (code);
8884
8885       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8886       var_expr = XCNEWVEC (gfc_expr *, total_var);
8887     }
8888
8889   /* The information about FORALL iterator, including FORALL index start, end
8890      and stride. The FORALL index can not appear in start, end or stride.  */
8891   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8892     {
8893       /* Check if any outer FORALL index name is the same as the current
8894          one.  */
8895       for (i = 0; i < nvar; i++)
8896         {
8897           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8898             {
8899               gfc_error ("An outer FORALL construct already has an index "
8900                          "with this name %L", &fa->var->where);
8901             }
8902         }
8903
8904       /* Record the current FORALL index.  */
8905       var_expr[nvar] = gfc_copy_expr (fa->var);
8906
8907       nvar++;
8908
8909       /* No memory leak.  */
8910       gcc_assert (nvar <= total_var);
8911     }
8912
8913   /* Resolve the FORALL body.  */
8914   gfc_resolve_forall_body (code, nvar, var_expr);
8915
8916   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8917   gfc_resolve_blocks (code->block, ns);
8918
8919   tmp = nvar;
8920   nvar = old_nvar;
8921   /* Free only the VAR_EXPRs allocated in this frame.  */
8922   for (i = nvar; i < tmp; i++)
8923      gfc_free_expr (var_expr[i]);
8924
8925   if (nvar == 0)
8926     {
8927       /* We are in the outermost FORALL construct.  */
8928       gcc_assert (forall_save == 0);
8929
8930       /* VAR_EXPR is not needed any more.  */
8931       free (var_expr);
8932       total_var = 0;
8933     }
8934 }
8935
8936
8937 /* Resolve a BLOCK construct statement.  */
8938
8939 static void
8940 resolve_block_construct (gfc_code* code)
8941 {
8942   /* Resolve the BLOCK's namespace.  */
8943   gfc_resolve (code->ext.block.ns);
8944
8945   /* For an ASSOCIATE block, the associations (and their targets) are already
8946      resolved during resolve_symbol.  */
8947 }
8948
8949
8950 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
8951    DO code nodes.  */
8952
8953 static void resolve_code (gfc_code *, gfc_namespace *);
8954
8955 void
8956 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8957 {
8958   gfc_try t;
8959
8960   for (; b; b = b->block)
8961     {
8962       t = gfc_resolve_expr (b->expr1);
8963       if (gfc_resolve_expr (b->expr2) == FAILURE)
8964         t = FAILURE;
8965
8966       switch (b->op)
8967         {
8968         case EXEC_IF:
8969           if (t == SUCCESS && b->expr1 != NULL
8970               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8971             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8972                        &b->expr1->where);
8973           break;
8974
8975         case EXEC_WHERE:
8976           if (t == SUCCESS
8977               && b->expr1 != NULL
8978               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8979             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8980                        &b->expr1->where);
8981           break;
8982
8983         case EXEC_GOTO:
8984           resolve_branch (b->label1, b);
8985           break;
8986
8987         case EXEC_BLOCK:
8988           resolve_block_construct (b);
8989           break;
8990
8991         case EXEC_SELECT:
8992         case EXEC_SELECT_TYPE:
8993         case EXEC_FORALL:
8994         case EXEC_DO:
8995         case EXEC_DO_WHILE:
8996         case EXEC_DO_CONCURRENT:
8997         case EXEC_CRITICAL:
8998         case EXEC_READ:
8999         case EXEC_WRITE:
9000         case EXEC_IOLENGTH:
9001         case EXEC_WAIT:
9002           break;
9003
9004         case EXEC_OMP_ATOMIC:
9005         case EXEC_OMP_CRITICAL:
9006         case EXEC_OMP_DO:
9007         case EXEC_OMP_MASTER:
9008         case EXEC_OMP_ORDERED:
9009         case EXEC_OMP_PARALLEL:
9010         case EXEC_OMP_PARALLEL_DO:
9011         case EXEC_OMP_PARALLEL_SECTIONS:
9012         case EXEC_OMP_PARALLEL_WORKSHARE:
9013         case EXEC_OMP_SECTIONS:
9014         case EXEC_OMP_SINGLE:
9015         case EXEC_OMP_TASK:
9016         case EXEC_OMP_TASKWAIT:
9017         case EXEC_OMP_TASKYIELD:
9018         case EXEC_OMP_WORKSHARE:
9019           break;
9020
9021         default:
9022           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
9023         }
9024
9025       resolve_code (b->next, ns);
9026     }
9027 }
9028
9029
9030 /* Does everything to resolve an ordinary assignment.  Returns true
9031    if this is an interface assignment.  */
9032 static bool
9033 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
9034 {
9035   bool rval = false;
9036   gfc_expr *lhs;
9037   gfc_expr *rhs;
9038   int llen = 0;
9039   int rlen = 0;
9040   int n;
9041   gfc_ref *ref;
9042
9043   if (gfc_extend_assign (code, ns) == SUCCESS)
9044     {
9045       gfc_expr** rhsptr;
9046
9047       if (code->op == EXEC_ASSIGN_CALL)
9048         {
9049           lhs = code->ext.actual->expr;
9050           rhsptr = &code->ext.actual->next->expr;
9051         }
9052       else
9053         {
9054           gfc_actual_arglist* args;
9055           gfc_typebound_proc* tbp;
9056
9057           gcc_assert (code->op == EXEC_COMPCALL);
9058
9059           args = code->expr1->value.compcall.actual;
9060           lhs = args->expr;
9061           rhsptr = &args->next->expr;
9062
9063           tbp = code->expr1->value.compcall.tbp;
9064           gcc_assert (!tbp->is_generic);
9065         }
9066
9067       /* Make a temporary rhs when there is a default initializer
9068          and rhs is the same symbol as the lhs.  */
9069       if ((*rhsptr)->expr_type == EXPR_VARIABLE
9070             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
9071             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
9072             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
9073         *rhsptr = gfc_get_parentheses (*rhsptr);
9074
9075       return true;
9076     }
9077
9078   lhs = code->expr1;
9079   rhs = code->expr2;
9080
9081   if (rhs->is_boz
9082       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
9083                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
9084                          &code->loc) == FAILURE)
9085     return false;
9086
9087   /* Handle the case of a BOZ literal on the RHS.  */
9088   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
9089     {
9090       int rc;
9091       if (gfc_option.warn_surprising)
9092         gfc_warning ("BOZ literal at %L is bitwise transferred "
9093                      "non-integer symbol '%s'", &code->loc,
9094                      lhs->symtree->n.sym->name);
9095
9096       if (!gfc_convert_boz (rhs, &lhs->ts))
9097         return false;
9098       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
9099         {
9100           if (rc == ARITH_UNDERFLOW)
9101             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
9102                        ". This check can be disabled with the option "
9103                        "-fno-range-check", &rhs->where);
9104           else if (rc == ARITH_OVERFLOW)
9105             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
9106                        ". This check can be disabled with the option "
9107                        "-fno-range-check", &rhs->where);
9108           else if (rc == ARITH_NAN)
9109             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
9110                        ". This check can be disabled with the option "
9111                        "-fno-range-check", &rhs->where);
9112           return false;
9113         }
9114     }
9115
9116   if (lhs->ts.type == BT_CHARACTER
9117         && gfc_option.warn_character_truncation)
9118     {
9119       if (lhs->ts.u.cl != NULL
9120             && lhs->ts.u.cl->length != NULL
9121             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9122         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
9123
9124       if (rhs->expr_type == EXPR_CONSTANT)
9125         rlen = rhs->value.character.length;
9126
9127       else if (rhs->ts.u.cl != NULL
9128                  && rhs->ts.u.cl->length != NULL
9129                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9130         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
9131
9132       if (rlen && llen && rlen > llen)
9133         gfc_warning_now ("CHARACTER expression will be truncated "
9134                          "in assignment (%d/%d) at %L",
9135                          llen, rlen, &code->loc);
9136     }
9137
9138   /* Ensure that a vector index expression for the lvalue is evaluated
9139      to a temporary if the lvalue symbol is referenced in it.  */
9140   if (lhs->rank)
9141     {
9142       for (ref = lhs->ref; ref; ref= ref->next)
9143         if (ref->type == REF_ARRAY)
9144           {
9145             for (n = 0; n < ref->u.ar.dimen; n++)
9146               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
9147                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
9148                                            ref->u.ar.start[n]))
9149                 ref->u.ar.start[n]
9150                         = gfc_get_parentheses (ref->u.ar.start[n]);
9151           }
9152     }
9153
9154   if (gfc_pure (NULL))
9155     {
9156       if (lhs->ts.type == BT_DERIVED
9157             && lhs->expr_type == EXPR_VARIABLE
9158             && lhs->ts.u.derived->attr.pointer_comp
9159             && rhs->expr_type == EXPR_VARIABLE
9160             && (gfc_impure_variable (rhs->symtree->n.sym)
9161                 || gfc_is_coindexed (rhs)))
9162         {
9163           /* F2008, C1283.  */
9164           if (gfc_is_coindexed (rhs))
9165             gfc_error ("Coindexed expression at %L is assigned to "
9166                         "a derived type variable with a POINTER "
9167                         "component in a PURE procedure",
9168                         &rhs->where);
9169           else
9170             gfc_error ("The impure variable at %L is assigned to "
9171                         "a derived type variable with a POINTER "
9172                         "component in a PURE procedure (12.6)",
9173                         &rhs->where);
9174           return rval;
9175         }
9176
9177       /* Fortran 2008, C1283.  */
9178       if (gfc_is_coindexed (lhs))
9179         {
9180           gfc_error ("Assignment to coindexed variable at %L in a PURE "
9181                      "procedure", &rhs->where);
9182           return rval;
9183         }
9184     }
9185
9186   if (gfc_implicit_pure (NULL))
9187     {
9188       if (lhs->expr_type == EXPR_VARIABLE
9189             && lhs->symtree->n.sym != gfc_current_ns->proc_name
9190             && lhs->symtree->n.sym->ns != gfc_current_ns)
9191         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9192
9193       if (lhs->ts.type == BT_DERIVED
9194             && lhs->expr_type == EXPR_VARIABLE
9195             && lhs->ts.u.derived->attr.pointer_comp
9196             && rhs->expr_type == EXPR_VARIABLE
9197             && (gfc_impure_variable (rhs->symtree->n.sym)
9198                 || gfc_is_coindexed (rhs)))
9199         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9200
9201       /* Fortran 2008, C1283.  */
9202       if (gfc_is_coindexed (lhs))
9203         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9204     }
9205
9206   /* F03:7.4.1.2.  */
9207   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
9208      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
9209   if (lhs->ts.type == BT_CLASS)
9210     {
9211       gfc_error ("Variable must not be polymorphic in intrinsic assignment at "
9212                  "%L - check that there is a matching specific subroutine "
9213                  "for '=' operator", &lhs->where);
9214       return false;
9215     }
9216
9217   /* F2008, Section 7.2.1.2.  */
9218   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
9219     {
9220       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
9221                  "component in assignment at %L", &lhs->where);
9222       return false;
9223     }
9224
9225   gfc_check_assign (lhs, rhs, 1);
9226   return false;
9227 }
9228
9229
9230 /* Given a block of code, recursively resolve everything pointed to by this
9231    code block.  */
9232
9233 static void
9234 resolve_code (gfc_code *code, gfc_namespace *ns)
9235 {
9236   int omp_workshare_save;
9237   int forall_save, do_concurrent_save;
9238   code_stack frame;
9239   gfc_try t;
9240
9241   frame.prev = cs_base;
9242   frame.head = code;
9243   cs_base = &frame;
9244
9245   find_reachable_labels (code);
9246
9247   for (; code; code = code->next)
9248     {
9249       frame.current = code;
9250       forall_save = forall_flag;
9251       do_concurrent_save = do_concurrent_flag;
9252
9253       if (code->op == EXEC_FORALL)
9254         {
9255           forall_flag = 1;
9256           gfc_resolve_forall (code, ns, forall_save);
9257           forall_flag = 2;
9258         }
9259       else if (code->block)
9260         {
9261           omp_workshare_save = -1;
9262           switch (code->op)
9263             {
9264             case EXEC_OMP_PARALLEL_WORKSHARE:
9265               omp_workshare_save = omp_workshare_flag;
9266               omp_workshare_flag = 1;
9267               gfc_resolve_omp_parallel_blocks (code, ns);
9268               break;
9269             case EXEC_OMP_PARALLEL:
9270             case EXEC_OMP_PARALLEL_DO:
9271             case EXEC_OMP_PARALLEL_SECTIONS:
9272             case EXEC_OMP_TASK:
9273               omp_workshare_save = omp_workshare_flag;
9274               omp_workshare_flag = 0;
9275               gfc_resolve_omp_parallel_blocks (code, ns);
9276               break;
9277             case EXEC_OMP_DO:
9278               gfc_resolve_omp_do_blocks (code, ns);
9279               break;
9280             case EXEC_SELECT_TYPE:
9281               /* Blocks are handled in resolve_select_type because we have
9282                  to transform the SELECT TYPE into ASSOCIATE first.  */
9283               break;
9284             case EXEC_DO_CONCURRENT:
9285               do_concurrent_flag = 1;
9286               gfc_resolve_blocks (code->block, ns);
9287               do_concurrent_flag = 2;
9288               break;
9289             case EXEC_OMP_WORKSHARE:
9290               omp_workshare_save = omp_workshare_flag;
9291               omp_workshare_flag = 1;
9292               /* FALLTHROUGH */
9293             default:
9294               gfc_resolve_blocks (code->block, ns);
9295               break;
9296             }
9297
9298           if (omp_workshare_save != -1)
9299             omp_workshare_flag = omp_workshare_save;
9300         }
9301
9302       t = SUCCESS;
9303       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
9304         t = gfc_resolve_expr (code->expr1);
9305       forall_flag = forall_save;
9306       do_concurrent_flag = do_concurrent_save;
9307
9308       if (gfc_resolve_expr (code->expr2) == FAILURE)
9309         t = FAILURE;
9310
9311       if (code->op == EXEC_ALLOCATE
9312           && gfc_resolve_expr (code->expr3) == FAILURE)
9313         t = FAILURE;
9314
9315       switch (code->op)
9316         {
9317         case EXEC_NOP:
9318         case EXEC_END_BLOCK:
9319         case EXEC_END_NESTED_BLOCK:
9320         case EXEC_CYCLE:
9321         case EXEC_PAUSE:
9322         case EXEC_STOP:
9323         case EXEC_ERROR_STOP:
9324         case EXEC_EXIT:
9325         case EXEC_CONTINUE:
9326         case EXEC_DT_END:
9327         case EXEC_ASSIGN_CALL:
9328         case EXEC_CRITICAL:
9329           break;
9330
9331         case EXEC_SYNC_ALL:
9332         case EXEC_SYNC_IMAGES:
9333         case EXEC_SYNC_MEMORY:
9334           resolve_sync (code);
9335           break;
9336
9337         case EXEC_LOCK:
9338         case EXEC_UNLOCK:
9339           resolve_lock_unlock (code);
9340           break;
9341
9342         case EXEC_ENTRY:
9343           /* Keep track of which entry we are up to.  */
9344           current_entry_id = code->ext.entry->id;
9345           break;
9346
9347         case EXEC_WHERE:
9348           resolve_where (code, NULL);
9349           break;
9350
9351         case EXEC_GOTO:
9352           if (code->expr1 != NULL)
9353             {
9354               if (code->expr1->ts.type != BT_INTEGER)
9355                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
9356                            "INTEGER variable", &code->expr1->where);
9357               else if (code->expr1->symtree->n.sym->attr.assign != 1)
9358                 gfc_error ("Variable '%s' has not been assigned a target "
9359                            "label at %L", code->expr1->symtree->n.sym->name,
9360                            &code->expr1->where);
9361             }
9362           else
9363             resolve_branch (code->label1, code);
9364           break;
9365
9366         case EXEC_RETURN:
9367           if (code->expr1 != NULL
9368                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
9369             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
9370                        "INTEGER return specifier", &code->expr1->where);
9371           break;
9372
9373         case EXEC_INIT_ASSIGN:
9374         case EXEC_END_PROCEDURE:
9375           break;
9376
9377         case EXEC_ASSIGN:
9378           if (t == FAILURE)
9379             break;
9380
9381           if (gfc_check_vardef_context (code->expr1, false, false,
9382                                         _("assignment")) == FAILURE)
9383             break;
9384
9385           if (resolve_ordinary_assign (code, ns))
9386             {
9387               if (code->op == EXEC_COMPCALL)
9388                 goto compcall;
9389               else
9390                 goto call;
9391             }
9392           break;
9393
9394         case EXEC_LABEL_ASSIGN:
9395           if (code->label1->defined == ST_LABEL_UNKNOWN)
9396             gfc_error ("Label %d referenced at %L is never defined",
9397                        code->label1->value, &code->label1->where);
9398           if (t == SUCCESS
9399               && (code->expr1->expr_type != EXPR_VARIABLE
9400                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
9401                   || code->expr1->symtree->n.sym->ts.kind
9402                      != gfc_default_integer_kind
9403                   || code->expr1->symtree->n.sym->as != NULL))
9404             gfc_error ("ASSIGN statement at %L requires a scalar "
9405                        "default INTEGER variable", &code->expr1->where);
9406           break;
9407
9408         case EXEC_POINTER_ASSIGN:
9409           {
9410             gfc_expr* e;
9411
9412             if (t == FAILURE)
9413               break;
9414
9415             /* This is both a variable definition and pointer assignment
9416                context, so check both of them.  For rank remapping, a final
9417                array ref may be present on the LHS and fool gfc_expr_attr
9418                used in gfc_check_vardef_context.  Remove it.  */
9419             e = remove_last_array_ref (code->expr1);
9420             t = gfc_check_vardef_context (e, true, false,
9421                                           _("pointer assignment"));
9422             if (t == SUCCESS)
9423               t = gfc_check_vardef_context (e, false, false,
9424                                             _("pointer assignment"));
9425             gfc_free_expr (e);
9426             if (t == FAILURE)
9427               break;
9428
9429             gfc_check_pointer_assign (code->expr1, code->expr2);
9430             break;
9431           }
9432
9433         case EXEC_ARITHMETIC_IF:
9434           if (t == SUCCESS
9435               && code->expr1->ts.type != BT_INTEGER
9436               && code->expr1->ts.type != BT_REAL)
9437             gfc_error ("Arithmetic IF statement at %L requires a numeric "
9438                        "expression", &code->expr1->where);
9439
9440           resolve_branch (code->label1, code);
9441           resolve_branch (code->label2, code);
9442           resolve_branch (code->label3, code);
9443           break;
9444
9445         case EXEC_IF:
9446           if (t == SUCCESS && code->expr1 != NULL
9447               && (code->expr1->ts.type != BT_LOGICAL
9448                   || code->expr1->rank != 0))
9449             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9450                        &code->expr1->where);
9451           break;
9452
9453         case EXEC_CALL:
9454         call:
9455           resolve_call (code);
9456           break;
9457
9458         case EXEC_COMPCALL:
9459         compcall:
9460           resolve_typebound_subroutine (code);
9461           break;
9462
9463         case EXEC_CALL_PPC:
9464           resolve_ppc_call (code);
9465           break;
9466
9467         case EXEC_SELECT:
9468           /* Select is complicated. Also, a SELECT construct could be
9469              a transformed computed GOTO.  */
9470           resolve_select (code);
9471           break;
9472
9473         case EXEC_SELECT_TYPE:
9474           resolve_select_type (code, ns);
9475           break;
9476
9477         case EXEC_BLOCK:
9478           resolve_block_construct (code);
9479           break;
9480
9481         case EXEC_DO:
9482           if (code->ext.iterator != NULL)
9483             {
9484               gfc_iterator *iter = code->ext.iterator;
9485               if (gfc_resolve_iterator (iter, true) != FAILURE)
9486                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
9487             }
9488           break;
9489
9490         case EXEC_DO_WHILE:
9491           if (code->expr1 == NULL)
9492             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
9493           if (t == SUCCESS
9494               && (code->expr1->rank != 0
9495                   || code->expr1->ts.type != BT_LOGICAL))
9496             gfc_error ("Exit condition of DO WHILE loop at %L must be "
9497                        "a scalar LOGICAL expression", &code->expr1->where);
9498           break;
9499
9500         case EXEC_ALLOCATE:
9501           if (t == SUCCESS)
9502             resolve_allocate_deallocate (code, "ALLOCATE");
9503
9504           break;
9505
9506         case EXEC_DEALLOCATE:
9507           if (t == SUCCESS)
9508             resolve_allocate_deallocate (code, "DEALLOCATE");
9509
9510           break;
9511
9512         case EXEC_OPEN:
9513           if (gfc_resolve_open (code->ext.open) == FAILURE)
9514             break;
9515
9516           resolve_branch (code->ext.open->err, code);
9517           break;
9518
9519         case EXEC_CLOSE:
9520           if (gfc_resolve_close (code->ext.close) == FAILURE)
9521             break;
9522
9523           resolve_branch (code->ext.close->err, code);
9524           break;
9525
9526         case EXEC_BACKSPACE:
9527         case EXEC_ENDFILE:
9528         case EXEC_REWIND:
9529         case EXEC_FLUSH:
9530           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
9531             break;
9532
9533           resolve_branch (code->ext.filepos->err, code);
9534           break;
9535
9536         case EXEC_INQUIRE:
9537           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9538               break;
9539
9540           resolve_branch (code->ext.inquire->err, code);
9541           break;
9542
9543         case EXEC_IOLENGTH:
9544           gcc_assert (code->ext.inquire != NULL);
9545           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9546             break;
9547
9548           resolve_branch (code->ext.inquire->err, code);
9549           break;
9550
9551         case EXEC_WAIT:
9552           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
9553             break;
9554
9555           resolve_branch (code->ext.wait->err, code);
9556           resolve_branch (code->ext.wait->end, code);
9557           resolve_branch (code->ext.wait->eor, code);
9558           break;
9559
9560         case EXEC_READ:
9561         case EXEC_WRITE:
9562           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
9563             break;
9564
9565           resolve_branch (code->ext.dt->err, code);
9566           resolve_branch (code->ext.dt->end, code);
9567           resolve_branch (code->ext.dt->eor, code);
9568           break;
9569
9570         case EXEC_TRANSFER:
9571           resolve_transfer (code);
9572           break;
9573
9574         case EXEC_DO_CONCURRENT:
9575         case EXEC_FORALL:
9576           resolve_forall_iterators (code->ext.forall_iterator);
9577
9578           if (code->expr1 != NULL
9579               && (code->expr1->ts.type != BT_LOGICAL || code->expr1->rank))
9580             gfc_error ("FORALL mask clause at %L requires a scalar LOGICAL "
9581                        "expression", &code->expr1->where);
9582           break;
9583
9584         case EXEC_OMP_ATOMIC:
9585         case EXEC_OMP_BARRIER:
9586         case EXEC_OMP_CRITICAL:
9587         case EXEC_OMP_FLUSH:
9588         case EXEC_OMP_DO:
9589         case EXEC_OMP_MASTER:
9590         case EXEC_OMP_ORDERED:
9591         case EXEC_OMP_SECTIONS:
9592         case EXEC_OMP_SINGLE:
9593         case EXEC_OMP_TASKWAIT:
9594         case EXEC_OMP_TASKYIELD:
9595         case EXEC_OMP_WORKSHARE:
9596           gfc_resolve_omp_directive (code, ns);
9597           break;
9598
9599         case EXEC_OMP_PARALLEL:
9600         case EXEC_OMP_PARALLEL_DO:
9601         case EXEC_OMP_PARALLEL_SECTIONS:
9602         case EXEC_OMP_PARALLEL_WORKSHARE:
9603         case EXEC_OMP_TASK:
9604           omp_workshare_save = omp_workshare_flag;
9605           omp_workshare_flag = 0;
9606           gfc_resolve_omp_directive (code, ns);
9607           omp_workshare_flag = omp_workshare_save;
9608           break;
9609
9610         default:
9611           gfc_internal_error ("resolve_code(): Bad statement code");
9612         }
9613     }
9614
9615   cs_base = frame.prev;
9616 }
9617
9618
9619 /* Resolve initial values and make sure they are compatible with
9620    the variable.  */
9621
9622 static void
9623 resolve_values (gfc_symbol *sym)
9624 {
9625   gfc_try t;
9626
9627   if (sym->value == NULL || sym->attr.use_assoc)
9628     return;
9629
9630   if (sym->value->expr_type == EXPR_STRUCTURE)
9631     t= resolve_structure_cons (sym->value, 1);
9632   else 
9633     t = gfc_resolve_expr (sym->value);
9634
9635   if (t == FAILURE)
9636     return;
9637
9638   gfc_check_assign_symbol (sym, sym->value);
9639 }
9640
9641
9642 /* Verify the binding labels for common blocks that are BIND(C).  The label
9643    for a BIND(C) common block must be identical in all scoping units in which
9644    the common block is declared.  Further, the binding label can not collide
9645    with any other global entity in the program.  */
9646
9647 static void
9648 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
9649 {
9650   if (comm_block_tree->n.common->is_bind_c == 1)
9651     {
9652       gfc_gsymbol *binding_label_gsym;
9653       gfc_gsymbol *comm_name_gsym;
9654
9655       /* See if a global symbol exists by the common block's name.  It may
9656          be NULL if the common block is use-associated.  */
9657       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
9658                                          comm_block_tree->n.common->name);
9659       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
9660         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
9661                    "with the global entity '%s' at %L",
9662                    comm_block_tree->n.common->binding_label,
9663                    comm_block_tree->n.common->name,
9664                    &(comm_block_tree->n.common->where),
9665                    comm_name_gsym->name, &(comm_name_gsym->where));
9666       else if (comm_name_gsym != NULL
9667                && strcmp (comm_name_gsym->name,
9668                           comm_block_tree->n.common->name) == 0)
9669         {
9670           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
9671              as expected.  */
9672           if (comm_name_gsym->binding_label == NULL)
9673             /* No binding label for common block stored yet; save this one.  */
9674             comm_name_gsym->binding_label =
9675               comm_block_tree->n.common->binding_label;
9676           else
9677             if (strcmp (comm_name_gsym->binding_label,
9678                         comm_block_tree->n.common->binding_label) != 0)
9679               {
9680                 /* Common block names match but binding labels do not.  */
9681                 gfc_error ("Binding label '%s' for common block '%s' at %L "
9682                            "does not match the binding label '%s' for common "
9683                            "block '%s' at %L",
9684                            comm_block_tree->n.common->binding_label,
9685                            comm_block_tree->n.common->name,
9686                            &(comm_block_tree->n.common->where),
9687                            comm_name_gsym->binding_label,
9688                            comm_name_gsym->name,
9689                            &(comm_name_gsym->where));
9690                 return;
9691               }
9692         }
9693
9694       /* There is no binding label (NAME="") so we have nothing further to
9695          check and nothing to add as a global symbol for the label.  */
9696       if (comm_block_tree->n.common->binding_label[0] == '\0' )
9697         return;
9698       
9699       binding_label_gsym =
9700         gfc_find_gsymbol (gfc_gsym_root,
9701                           comm_block_tree->n.common->binding_label);
9702       if (binding_label_gsym == NULL)
9703         {
9704           /* Need to make a global symbol for the binding label to prevent
9705              it from colliding with another.  */
9706           binding_label_gsym =
9707             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
9708           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
9709           binding_label_gsym->type = GSYM_COMMON;
9710         }
9711       else
9712         {
9713           /* If comm_name_gsym is NULL, the name common block is use
9714              associated and the name could be colliding.  */
9715           if (binding_label_gsym->type != GSYM_COMMON)
9716             gfc_error ("Binding label '%s' for common block '%s' at %L "
9717                        "collides with the global entity '%s' at %L",
9718                        comm_block_tree->n.common->binding_label,
9719                        comm_block_tree->n.common->name,
9720                        &(comm_block_tree->n.common->where),
9721                        binding_label_gsym->name,
9722                        &(binding_label_gsym->where));
9723           else if (comm_name_gsym != NULL
9724                    && (strcmp (binding_label_gsym->name,
9725                                comm_name_gsym->binding_label) != 0)
9726                    && (strcmp (binding_label_gsym->sym_name,
9727                                comm_name_gsym->name) != 0))
9728             gfc_error ("Binding label '%s' for common block '%s' at %L "
9729                        "collides with global entity '%s' at %L",
9730                        binding_label_gsym->name, binding_label_gsym->sym_name,
9731                        &(comm_block_tree->n.common->where),
9732                        comm_name_gsym->name, &(comm_name_gsym->where));
9733         }
9734     }
9735   
9736   return;
9737 }
9738
9739
9740 /* Verify any BIND(C) derived types in the namespace so we can report errors
9741    for them once, rather than for each variable declared of that type.  */
9742
9743 static void
9744 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
9745 {
9746   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
9747       && derived_sym->attr.is_bind_c == 1)
9748     verify_bind_c_derived_type (derived_sym);
9749   
9750   return;
9751 }
9752
9753
9754 /* Verify that any binding labels used in a given namespace do not collide 
9755    with the names or binding labels of any global symbols.  */
9756
9757 static void
9758 gfc_verify_binding_labels (gfc_symbol *sym)
9759 {
9760   int has_error = 0;
9761   
9762   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
9763       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
9764     {
9765       gfc_gsymbol *bind_c_sym;
9766
9767       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
9768       if (bind_c_sym != NULL 
9769           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
9770         {
9771           if (sym->attr.if_source == IFSRC_DECL 
9772               && (bind_c_sym->type != GSYM_SUBROUTINE 
9773                   && bind_c_sym->type != GSYM_FUNCTION) 
9774               && ((sym->attr.contained == 1 
9775                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
9776                   || (sym->attr.use_assoc == 1 
9777                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
9778             {
9779               /* Make sure global procedures don't collide with anything.  */
9780               gfc_error ("Binding label '%s' at %L collides with the global "
9781                          "entity '%s' at %L", sym->binding_label,
9782                          &(sym->declared_at), bind_c_sym->name,
9783                          &(bind_c_sym->where));
9784               has_error = 1;
9785             }
9786           else if (sym->attr.contained == 0 
9787                    && (sym->attr.if_source == IFSRC_IFBODY 
9788                        && sym->attr.flavor == FL_PROCEDURE) 
9789                    && (bind_c_sym->sym_name != NULL 
9790                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
9791             {
9792               /* Make sure procedures in interface bodies don't collide.  */
9793               gfc_error ("Binding label '%s' in interface body at %L collides "
9794                          "with the global entity '%s' at %L",
9795                          sym->binding_label,
9796                          &(sym->declared_at), bind_c_sym->name,
9797                          &(bind_c_sym->where));
9798               has_error = 1;
9799             }
9800           else if (sym->attr.contained == 0 
9801                    && sym->attr.if_source == IFSRC_UNKNOWN)
9802             if ((sym->attr.use_assoc && bind_c_sym->mod_name
9803                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
9804                 || sym->attr.use_assoc == 0)
9805               {
9806                 gfc_error ("Binding label '%s' at %L collides with global "
9807                            "entity '%s' at %L", sym->binding_label,
9808                            &(sym->declared_at), bind_c_sym->name,
9809                            &(bind_c_sym->where));
9810                 has_error = 1;
9811               }
9812
9813           if (has_error != 0)
9814             /* Clear the binding label to prevent checking multiple times.  */
9815             sym->binding_label[0] = '\0';
9816         }
9817       else if (bind_c_sym == NULL)
9818         {
9819           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
9820           bind_c_sym->where = sym->declared_at;
9821           bind_c_sym->sym_name = sym->name;
9822
9823           if (sym->attr.use_assoc == 1)
9824             bind_c_sym->mod_name = sym->module;
9825           else
9826             if (sym->ns->proc_name != NULL)
9827               bind_c_sym->mod_name = sym->ns->proc_name->name;
9828
9829           if (sym->attr.contained == 0)
9830             {
9831               if (sym->attr.subroutine)
9832                 bind_c_sym->type = GSYM_SUBROUTINE;
9833               else if (sym->attr.function)
9834                 bind_c_sym->type = GSYM_FUNCTION;
9835             }
9836         }
9837     }
9838   return;
9839 }
9840
9841
9842 /* Resolve an index expression.  */
9843
9844 static gfc_try
9845 resolve_index_expr (gfc_expr *e)
9846 {
9847   if (gfc_resolve_expr (e) == FAILURE)
9848     return FAILURE;
9849
9850   if (gfc_simplify_expr (e, 0) == FAILURE)
9851     return FAILURE;
9852
9853   if (gfc_specification_expr (e) == FAILURE)
9854     return FAILURE;
9855
9856   return SUCCESS;
9857 }
9858
9859
9860 /* Resolve a charlen structure.  */
9861
9862 static gfc_try
9863 resolve_charlen (gfc_charlen *cl)
9864 {
9865   int i, k;
9866
9867   if (cl->resolved)
9868     return SUCCESS;
9869
9870   cl->resolved = 1;
9871
9872   specification_expr = 1;
9873
9874   if (resolve_index_expr (cl->length) == FAILURE)
9875     {
9876       specification_expr = 0;
9877       return FAILURE;
9878     }
9879
9880   /* "If the character length parameter value evaluates to a negative
9881      value, the length of character entities declared is zero."  */
9882   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
9883     {
9884       if (gfc_option.warn_surprising)
9885         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
9886                          " the length has been set to zero",
9887                          &cl->length->where, i);
9888       gfc_replace_expr (cl->length,
9889                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
9890     }
9891
9892   /* Check that the character length is not too large.  */
9893   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
9894   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
9895       && cl->length->ts.type == BT_INTEGER
9896       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
9897     {
9898       gfc_error ("String length at %L is too large", &cl->length->where);
9899       return FAILURE;
9900     }
9901
9902   return SUCCESS;
9903 }
9904
9905
9906 /* Test for non-constant shape arrays.  */
9907
9908 static bool
9909 is_non_constant_shape_array (gfc_symbol *sym)
9910 {
9911   gfc_expr *e;
9912   int i;
9913   bool not_constant;
9914
9915   not_constant = false;
9916   if (sym->as != NULL)
9917     {
9918       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
9919          has not been simplified; parameter array references.  Do the
9920          simplification now.  */
9921       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
9922         {
9923           e = sym->as->lower[i];
9924           if (e && (resolve_index_expr (e) == FAILURE
9925                     || !gfc_is_constant_expr (e)))
9926             not_constant = true;
9927           e = sym->as->upper[i];
9928           if (e && (resolve_index_expr (e) == FAILURE
9929                     || !gfc_is_constant_expr (e)))
9930             not_constant = true;
9931         }
9932     }
9933   return not_constant;
9934 }
9935
9936 /* Given a symbol and an initialization expression, add code to initialize
9937    the symbol to the function entry.  */
9938 static void
9939 build_init_assign (gfc_symbol *sym, gfc_expr *init)
9940 {
9941   gfc_expr *lval;
9942   gfc_code *init_st;
9943   gfc_namespace *ns = sym->ns;
9944
9945   /* Search for the function namespace if this is a contained
9946      function without an explicit result.  */
9947   if (sym->attr.function && sym == sym->result
9948       && sym->name != sym->ns->proc_name->name)
9949     {
9950       ns = ns->contained;
9951       for (;ns; ns = ns->sibling)
9952         if (strcmp (ns->proc_name->name, sym->name) == 0)
9953           break;
9954     }
9955
9956   if (ns == NULL)
9957     {
9958       gfc_free_expr (init);
9959       return;
9960     }
9961
9962   /* Build an l-value expression for the result.  */
9963   lval = gfc_lval_expr_from_sym (sym);
9964
9965   /* Add the code at scope entry.  */
9966   init_st = gfc_get_code ();
9967   init_st->next = ns->code;
9968   ns->code = init_st;
9969
9970   /* Assign the default initializer to the l-value.  */
9971   init_st->loc = sym->declared_at;
9972   init_st->op = EXEC_INIT_ASSIGN;
9973   init_st->expr1 = lval;
9974   init_st->expr2 = init;
9975 }
9976
9977 /* Assign the default initializer to a derived type variable or result.  */
9978
9979 static void
9980 apply_default_init (gfc_symbol *sym)
9981 {
9982   gfc_expr *init = NULL;
9983
9984   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9985     return;
9986
9987   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
9988     init = gfc_default_initializer (&sym->ts);
9989
9990   if (init == NULL && sym->ts.type != BT_CLASS)
9991     return;
9992
9993   build_init_assign (sym, init);
9994   sym->attr.referenced = 1;
9995 }
9996
9997 /* Build an initializer for a local integer, real, complex, logical, or
9998    character variable, based on the command line flags finit-local-zero,
9999    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
10000    null if the symbol should not have a default initialization.  */
10001 static gfc_expr *
10002 build_default_init_expr (gfc_symbol *sym)
10003 {
10004   int char_len;
10005   gfc_expr *init_expr;
10006   int i;
10007
10008   /* These symbols should never have a default initialization.  */
10009   if (sym->attr.allocatable
10010       || sym->attr.external
10011       || sym->attr.dummy
10012       || sym->attr.pointer
10013       || sym->attr.in_equivalence
10014       || sym->attr.in_common
10015       || sym->attr.data
10016       || sym->module
10017       || sym->attr.cray_pointee
10018       || sym->attr.cray_pointer)
10019     return NULL;
10020
10021   /* Now we'll try to build an initializer expression.  */
10022   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
10023                                      &sym->declared_at);
10024
10025   /* We will only initialize integers, reals, complex, logicals, and
10026      characters, and only if the corresponding command-line flags
10027      were set.  Otherwise, we free init_expr and return null.  */
10028   switch (sym->ts.type)
10029     {    
10030     case BT_INTEGER:
10031       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
10032         mpz_set_si (init_expr->value.integer, 
10033                          gfc_option.flag_init_integer_value);
10034       else
10035         {
10036           gfc_free_expr (init_expr);
10037           init_expr = NULL;
10038         }
10039       break;
10040
10041     case BT_REAL:
10042       switch (gfc_option.flag_init_real)
10043         {
10044         case GFC_INIT_REAL_SNAN:
10045           init_expr->is_snan = 1;
10046           /* Fall through.  */
10047         case GFC_INIT_REAL_NAN:
10048           mpfr_set_nan (init_expr->value.real);
10049           break;
10050
10051         case GFC_INIT_REAL_INF:
10052           mpfr_set_inf (init_expr->value.real, 1);
10053           break;
10054
10055         case GFC_INIT_REAL_NEG_INF:
10056           mpfr_set_inf (init_expr->value.real, -1);
10057           break;
10058
10059         case GFC_INIT_REAL_ZERO:
10060           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
10061           break;
10062
10063         default:
10064           gfc_free_expr (init_expr);
10065           init_expr = NULL;
10066           break;
10067         }
10068       break;
10069           
10070     case BT_COMPLEX:
10071       switch (gfc_option.flag_init_real)
10072         {
10073         case GFC_INIT_REAL_SNAN:
10074           init_expr->is_snan = 1;
10075           /* Fall through.  */
10076         case GFC_INIT_REAL_NAN:
10077           mpfr_set_nan (mpc_realref (init_expr->value.complex));
10078           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
10079           break;
10080
10081         case GFC_INIT_REAL_INF:
10082           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
10083           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
10084           break;
10085
10086         case GFC_INIT_REAL_NEG_INF:
10087           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
10088           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
10089           break;
10090
10091         case GFC_INIT_REAL_ZERO:
10092           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
10093           break;
10094
10095         default:
10096           gfc_free_expr (init_expr);
10097           init_expr = NULL;
10098           break;
10099         }
10100       break;
10101           
10102     case BT_LOGICAL:
10103       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
10104         init_expr->value.logical = 0;
10105       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
10106         init_expr->value.logical = 1;
10107       else
10108         {
10109           gfc_free_expr (init_expr);
10110           init_expr = NULL;
10111         }
10112       break;
10113           
10114     case BT_CHARACTER:
10115       /* For characters, the length must be constant in order to 
10116          create a default initializer.  */
10117       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
10118           && sym->ts.u.cl->length
10119           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
10120         {
10121           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
10122           init_expr->value.character.length = char_len;
10123           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
10124           for (i = 0; i < char_len; i++)
10125             init_expr->value.character.string[i]
10126               = (unsigned char) gfc_option.flag_init_character_value;
10127         }
10128       else
10129         {
10130           gfc_free_expr (init_expr);
10131           init_expr = NULL;
10132         }
10133       break;
10134           
10135     default:
10136      gfc_free_expr (init_expr);
10137      init_expr = NULL;
10138     }
10139   return init_expr;
10140 }
10141
10142 /* Add an initialization expression to a local variable.  */
10143 static void
10144 apply_default_init_local (gfc_symbol *sym)
10145 {
10146   gfc_expr *init = NULL;
10147
10148   /* The symbol should be a variable or a function return value.  */
10149   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
10150       || (sym->attr.function && sym->result != sym))
10151     return;
10152
10153   /* Try to build the initializer expression.  If we can't initialize
10154      this symbol, then init will be NULL.  */
10155   init = build_default_init_expr (sym);
10156   if (init == NULL)
10157     return;
10158
10159   /* For saved variables, we don't want to add an initializer at 
10160      function entry, so we just add a static initializer.  */
10161   if (sym->attr.save || sym->ns->save_all 
10162       || gfc_option.flag_max_stack_var_size == 0)
10163     {
10164       /* Don't clobber an existing initializer!  */
10165       gcc_assert (sym->value == NULL);
10166       sym->value = init;
10167       return;
10168     }
10169
10170   build_init_assign (sym, init);
10171 }
10172
10173
10174 /* Resolution of common features of flavors variable and procedure.  */
10175
10176 static gfc_try
10177 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
10178 {
10179   gfc_array_spec *as;
10180
10181   /* Avoid double diagnostics for function result symbols.  */
10182   if ((sym->result || sym->attr.result) && !sym->attr.dummy
10183       && (sym->ns != gfc_current_ns))
10184     return SUCCESS;
10185
10186   if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
10187     as = CLASS_DATA (sym)->as;
10188   else
10189     as = sym->as;
10190
10191   /* Constraints on deferred shape variable.  */
10192   if (as == NULL || as->type != AS_DEFERRED)
10193     {
10194       bool pointer, allocatable, dimension;
10195
10196       if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
10197         {
10198           pointer = CLASS_DATA (sym)->attr.class_pointer;
10199           allocatable = CLASS_DATA (sym)->attr.allocatable;
10200           dimension = CLASS_DATA (sym)->attr.dimension;
10201         }
10202       else
10203         {
10204           pointer = sym->attr.pointer;
10205           allocatable = sym->attr.allocatable;
10206           dimension = sym->attr.dimension;
10207         }
10208
10209       if (allocatable)
10210         {
10211           if (dimension)
10212             {
10213               gfc_error ("Allocatable array '%s' at %L must have "
10214                          "a deferred shape", sym->name, &sym->declared_at);
10215               return FAILURE;
10216             }
10217           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
10218                                    "may not be ALLOCATABLE", sym->name,
10219                                    &sym->declared_at) == FAILURE)
10220             return FAILURE;
10221         }
10222
10223       if (pointer && dimension)
10224         {
10225           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
10226                      sym->name, &sym->declared_at);
10227           return FAILURE;
10228         }
10229     }
10230   else
10231     {
10232       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
10233           && sym->ts.type != BT_CLASS && !sym->assoc)
10234         {
10235           gfc_error ("Array '%s' at %L cannot have a deferred shape",
10236                      sym->name, &sym->declared_at);
10237           return FAILURE;
10238          }
10239     }
10240
10241   /* Constraints on polymorphic variables.  */
10242   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
10243     {
10244       /* F03:C502.  */
10245       if (sym->attr.class_ok
10246           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
10247         {
10248           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
10249                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
10250                      &sym->declared_at);
10251           return FAILURE;
10252         }
10253
10254       /* F03:C509.  */
10255       /* Assume that use associated symbols were checked in the module ns.
10256          Class-variables that are associate-names are also something special
10257          and excepted from the test.  */
10258       if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
10259         {
10260           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
10261                      "or pointer", sym->name, &sym->declared_at);
10262           return FAILURE;
10263         }
10264     }
10265     
10266   return SUCCESS;
10267 }
10268
10269
10270 /* Additional checks for symbols with flavor variable and derived
10271    type.  To be called from resolve_fl_variable.  */
10272
10273 static gfc_try
10274 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
10275 {
10276   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
10277
10278   /* Check to see if a derived type is blocked from being host
10279      associated by the presence of another class I symbol in the same
10280      namespace.  14.6.1.3 of the standard and the discussion on
10281      comp.lang.fortran.  */
10282   if (sym->ns != sym->ts.u.derived->ns
10283       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
10284     {
10285       gfc_symbol *s;
10286       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
10287       if (s && s->attr.generic)
10288         s = gfc_find_dt_in_generic (s);
10289       if (s && s->attr.flavor != FL_DERIVED)
10290         {
10291           gfc_error ("The type '%s' cannot be host associated at %L "
10292                      "because it is blocked by an incompatible object "
10293                      "of the same name declared at %L",
10294                      sym->ts.u.derived->name, &sym->declared_at,
10295                      &s->declared_at);
10296           return FAILURE;
10297         }
10298     }
10299
10300   /* 4th constraint in section 11.3: "If an object of a type for which
10301      component-initialization is specified (R429) appears in the
10302      specification-part of a module and does not have the ALLOCATABLE
10303      or POINTER attribute, the object shall have the SAVE attribute."
10304
10305      The check for initializers is performed with
10306      gfc_has_default_initializer because gfc_default_initializer generates
10307      a hidden default for allocatable components.  */
10308   if (!(sym->value || no_init_flag) && sym->ns->proc_name
10309       && sym->ns->proc_name->attr.flavor == FL_MODULE
10310       && !sym->ns->save_all && !sym->attr.save
10311       && !sym->attr.pointer && !sym->attr.allocatable
10312       && gfc_has_default_initializer (sym->ts.u.derived)
10313       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
10314                          "module variable '%s' at %L, needed due to "
10315                          "the default initialization", sym->name,
10316                          &sym->declared_at) == FAILURE)
10317     return FAILURE;
10318
10319   /* Assign default initializer.  */
10320   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
10321       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
10322     {
10323       sym->value = gfc_default_initializer (&sym->ts);
10324     }
10325
10326   return SUCCESS;
10327 }
10328
10329
10330 /* Resolve symbols with flavor variable.  */
10331
10332 static gfc_try
10333 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
10334 {
10335   int no_init_flag, automatic_flag;
10336   gfc_expr *e;
10337   const char *auto_save_msg;
10338
10339   auto_save_msg = "Automatic object '%s' at %L cannot have the "
10340                   "SAVE attribute";
10341
10342   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10343     return FAILURE;
10344
10345   /* Set this flag to check that variables are parameters of all entries.
10346      This check is effected by the call to gfc_resolve_expr through
10347      is_non_constant_shape_array.  */
10348   specification_expr = 1;
10349
10350   if (sym->ns->proc_name
10351       && (sym->ns->proc_name->attr.flavor == FL_MODULE
10352           || sym->ns->proc_name->attr.is_main_program)
10353       && !sym->attr.use_assoc
10354       && !sym->attr.allocatable
10355       && !sym->attr.pointer
10356       && is_non_constant_shape_array (sym))
10357     {
10358       /* The shape of a main program or module array needs to be
10359          constant.  */
10360       gfc_error ("The module or main program array '%s' at %L must "
10361                  "have constant shape", sym->name, &sym->declared_at);
10362       specification_expr = 0;
10363       return FAILURE;
10364     }
10365
10366   /* Constraints on deferred type parameter.  */
10367   if (sym->ts.deferred && !(sym->attr.pointer || sym->attr.allocatable))
10368     {
10369       gfc_error ("Entity '%s' at %L has a deferred type parameter and "
10370                  "requires either the pointer or allocatable attribute",
10371                      sym->name, &sym->declared_at);
10372       return FAILURE;
10373     }
10374
10375   if (sym->ts.type == BT_CHARACTER)
10376     {
10377       /* Make sure that character string variables with assumed length are
10378          dummy arguments.  */
10379       e = sym->ts.u.cl->length;
10380       if (e == NULL && !sym->attr.dummy && !sym->attr.result
10381           && !sym->ts.deferred)
10382         {
10383           gfc_error ("Entity with assumed character length at %L must be a "
10384                      "dummy argument or a PARAMETER", &sym->declared_at);
10385           return FAILURE;
10386         }
10387
10388       if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
10389         {
10390           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10391           return FAILURE;
10392         }
10393
10394       if (!gfc_is_constant_expr (e)
10395           && !(e->expr_type == EXPR_VARIABLE
10396                && e->symtree->n.sym->attr.flavor == FL_PARAMETER))
10397         {
10398           if (!sym->attr.use_assoc && sym->ns->proc_name
10399               && (sym->ns->proc_name->attr.flavor == FL_MODULE
10400                   || sym->ns->proc_name->attr.is_main_program))
10401             {
10402               gfc_error ("'%s' at %L must have constant character length "
10403                         "in this context", sym->name, &sym->declared_at);
10404               return FAILURE;
10405             }
10406           if (sym->attr.in_common)
10407             {
10408               gfc_error ("COMMON variable '%s' at %L must have constant "
10409                          "character length", sym->name, &sym->declared_at);
10410               return FAILURE;
10411             }
10412         }
10413     }
10414
10415   if (sym->value == NULL && sym->attr.referenced)
10416     apply_default_init_local (sym); /* Try to apply a default initialization.  */
10417
10418   /* Determine if the symbol may not have an initializer.  */
10419   no_init_flag = automatic_flag = 0;
10420   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
10421       || sym->attr.intrinsic || sym->attr.result)
10422     no_init_flag = 1;
10423   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
10424            && is_non_constant_shape_array (sym))
10425     {
10426       no_init_flag = automatic_flag = 1;
10427
10428       /* Also, they must not have the SAVE attribute.
10429          SAVE_IMPLICIT is checked below.  */
10430       if (sym->as && sym->attr.codimension)
10431         {
10432           int corank = sym->as->corank;
10433           sym->as->corank = 0;
10434           no_init_flag = automatic_flag = is_non_constant_shape_array (sym);
10435           sym->as->corank = corank;
10436         }
10437       if (automatic_flag && sym->attr.save == SAVE_EXPLICIT)
10438         {
10439           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10440           return FAILURE;
10441         }
10442     }
10443
10444   /* Ensure that any initializer is simplified.  */
10445   if (sym->value)
10446     gfc_simplify_expr (sym->value, 1);
10447
10448   /* Reject illegal initializers.  */
10449   if (!sym->mark && sym->value)
10450     {
10451       if (sym->attr.allocatable || (sym->ts.type == BT_CLASS
10452                                     && CLASS_DATA (sym)->attr.allocatable))
10453         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
10454                    sym->name, &sym->declared_at);
10455       else if (sym->attr.external)
10456         gfc_error ("External '%s' at %L cannot have an initializer",
10457                    sym->name, &sym->declared_at);
10458       else if (sym->attr.dummy
10459         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
10460         gfc_error ("Dummy '%s' at %L cannot have an initializer",
10461                    sym->name, &sym->declared_at);
10462       else if (sym->attr.intrinsic)
10463         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
10464                    sym->name, &sym->declared_at);
10465       else if (sym->attr.result)
10466         gfc_error ("Function result '%s' at %L cannot have an initializer",
10467                    sym->name, &sym->declared_at);
10468       else if (automatic_flag)
10469         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
10470                    sym->name, &sym->declared_at);
10471       else
10472         goto no_init_error;
10473       return FAILURE;
10474     }
10475
10476 no_init_error:
10477   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
10478     return resolve_fl_variable_derived (sym, no_init_flag);
10479
10480   return SUCCESS;
10481 }
10482
10483
10484 /* Resolve a procedure.  */
10485
10486 static gfc_try
10487 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
10488 {
10489   gfc_formal_arglist *arg;
10490
10491   if (sym->attr.function
10492       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10493     return FAILURE;
10494
10495   if (sym->ts.type == BT_CHARACTER)
10496     {
10497       gfc_charlen *cl = sym->ts.u.cl;
10498
10499       if (cl && cl->length && gfc_is_constant_expr (cl->length)
10500              && resolve_charlen (cl) == FAILURE)
10501         return FAILURE;
10502
10503       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
10504           && sym->attr.proc == PROC_ST_FUNCTION)
10505         {
10506           gfc_error ("Character-valued statement function '%s' at %L must "
10507                      "have constant length", sym->name, &sym->declared_at);
10508           return FAILURE;
10509         }
10510     }
10511
10512   /* Ensure that derived type for are not of a private type.  Internal
10513      module procedures are excluded by 2.2.3.3 - i.e., they are not
10514      externally accessible and can access all the objects accessible in
10515      the host.  */
10516   if (!(sym->ns->parent
10517         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
10518       && gfc_check_symbol_access (sym))
10519     {
10520       gfc_interface *iface;
10521
10522       for (arg = sym->formal; arg; arg = arg->next)
10523         {
10524           if (arg->sym
10525               && arg->sym->ts.type == BT_DERIVED
10526               && !arg->sym->ts.u.derived->attr.use_assoc
10527               && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10528               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
10529                                  "PRIVATE type and cannot be a dummy argument"
10530                                  " of '%s', which is PUBLIC at %L",
10531                                  arg->sym->name, sym->name, &sym->declared_at)
10532                  == FAILURE)
10533             {
10534               /* Stop this message from recurring.  */
10535               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10536               return FAILURE;
10537             }
10538         }
10539
10540       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10541          PRIVATE to the containing module.  */
10542       for (iface = sym->generic; iface; iface = iface->next)
10543         {
10544           for (arg = iface->sym->formal; arg; arg = arg->next)
10545             {
10546               if (arg->sym
10547                   && arg->sym->ts.type == BT_DERIVED
10548                   && !arg->sym->ts.u.derived->attr.use_assoc
10549                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10550                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10551                                      "'%s' in PUBLIC interface '%s' at %L "
10552                                      "takes dummy arguments of '%s' which is "
10553                                      "PRIVATE", iface->sym->name, sym->name,
10554                                      &iface->sym->declared_at,
10555                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10556                 {
10557                   /* Stop this message from recurring.  */
10558                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10559                   return FAILURE;
10560                 }
10561              }
10562         }
10563
10564       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10565          PRIVATE to the containing module.  */
10566       for (iface = sym->generic; iface; iface = iface->next)
10567         {
10568           for (arg = iface->sym->formal; arg; arg = arg->next)
10569             {
10570               if (arg->sym
10571                   && arg->sym->ts.type == BT_DERIVED
10572                   && !arg->sym->ts.u.derived->attr.use_assoc
10573                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10574                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10575                                      "'%s' in PUBLIC interface '%s' at %L "
10576                                      "takes dummy arguments of '%s' which is "
10577                                      "PRIVATE", iface->sym->name, sym->name,
10578                                      &iface->sym->declared_at,
10579                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10580                 {
10581                   /* Stop this message from recurring.  */
10582                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10583                   return FAILURE;
10584                 }
10585              }
10586         }
10587     }
10588
10589   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
10590       && !sym->attr.proc_pointer)
10591     {
10592       gfc_error ("Function '%s' at %L cannot have an initializer",
10593                  sym->name, &sym->declared_at);
10594       return FAILURE;
10595     }
10596
10597   /* An external symbol may not have an initializer because it is taken to be
10598      a procedure. Exception: Procedure Pointers.  */
10599   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
10600     {
10601       gfc_error ("External object '%s' at %L may not have an initializer",
10602                  sym->name, &sym->declared_at);
10603       return FAILURE;
10604     }
10605
10606   /* An elemental function is required to return a scalar 12.7.1  */
10607   if (sym->attr.elemental && sym->attr.function && sym->as)
10608     {
10609       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
10610                  "result", sym->name, &sym->declared_at);
10611       /* Reset so that the error only occurs once.  */
10612       sym->attr.elemental = 0;
10613       return FAILURE;
10614     }
10615
10616   if (sym->attr.proc == PROC_ST_FUNCTION
10617       && (sym->attr.allocatable || sym->attr.pointer))
10618     {
10619       gfc_error ("Statement function '%s' at %L may not have pointer or "
10620                  "allocatable attribute", sym->name, &sym->declared_at);
10621       return FAILURE;
10622     }
10623
10624   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
10625      char-len-param shall not be array-valued, pointer-valued, recursive
10626      or pure.  ....snip... A character value of * may only be used in the
10627      following ways: (i) Dummy arg of procedure - dummy associates with
10628      actual length; (ii) To declare a named constant; or (iii) External
10629      function - but length must be declared in calling scoping unit.  */
10630   if (sym->attr.function
10631       && sym->ts.type == BT_CHARACTER
10632       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
10633     {
10634       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
10635           || (sym->attr.recursive) || (sym->attr.pure))
10636         {
10637           if (sym->as && sym->as->rank)
10638             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10639                        "array-valued", sym->name, &sym->declared_at);
10640
10641           if (sym->attr.pointer)
10642             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10643                        "pointer-valued", sym->name, &sym->declared_at);
10644
10645           if (sym->attr.pure)
10646             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10647                        "pure", sym->name, &sym->declared_at);
10648
10649           if (sym->attr.recursive)
10650             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10651                        "recursive", sym->name, &sym->declared_at);
10652
10653           return FAILURE;
10654         }
10655
10656       /* Appendix B.2 of the standard.  Contained functions give an
10657          error anyway.  Fixed-form is likely to be F77/legacy. Deferred
10658          character length is an F2003 feature.  */
10659       if (!sym->attr.contained
10660             && gfc_current_form != FORM_FIXED
10661             && !sym->ts.deferred)
10662         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
10663                         "CHARACTER(*) function '%s' at %L",
10664                         sym->name, &sym->declared_at);
10665     }
10666
10667   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
10668     {
10669       gfc_formal_arglist *curr_arg;
10670       int has_non_interop_arg = 0;
10671
10672       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10673                              sym->common_block) == FAILURE)
10674         {
10675           /* Clear these to prevent looking at them again if there was an
10676              error.  */
10677           sym->attr.is_bind_c = 0;
10678           sym->attr.is_c_interop = 0;
10679           sym->ts.is_c_interop = 0;
10680         }
10681       else
10682         {
10683           /* So far, no errors have been found.  */
10684           sym->attr.is_c_interop = 1;
10685           sym->ts.is_c_interop = 1;
10686         }
10687       
10688       curr_arg = sym->formal;
10689       while (curr_arg != NULL)
10690         {
10691           /* Skip implicitly typed dummy args here.  */
10692           if (curr_arg->sym->attr.implicit_type == 0)
10693             if (gfc_verify_c_interop_param (curr_arg->sym) == FAILURE)
10694               /* If something is found to fail, record the fact so we
10695                  can mark the symbol for the procedure as not being
10696                  BIND(C) to try and prevent multiple errors being
10697                  reported.  */
10698               has_non_interop_arg = 1;
10699           
10700           curr_arg = curr_arg->next;
10701         }
10702
10703       /* See if any of the arguments were not interoperable and if so, clear
10704          the procedure symbol to prevent duplicate error messages.  */
10705       if (has_non_interop_arg != 0)
10706         {
10707           sym->attr.is_c_interop = 0;
10708           sym->ts.is_c_interop = 0;
10709           sym->attr.is_bind_c = 0;
10710         }
10711     }
10712   
10713   if (!sym->attr.proc_pointer)
10714     {
10715       if (sym->attr.save == SAVE_EXPLICIT)
10716         {
10717           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
10718                      "in '%s' at %L", sym->name, &sym->declared_at);
10719           return FAILURE;
10720         }
10721       if (sym->attr.intent)
10722         {
10723           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
10724                      "in '%s' at %L", sym->name, &sym->declared_at);
10725           return FAILURE;
10726         }
10727       if (sym->attr.subroutine && sym->attr.result)
10728         {
10729           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
10730                      "in '%s' at %L", sym->name, &sym->declared_at);
10731           return FAILURE;
10732         }
10733       if (sym->attr.external && sym->attr.function
10734           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
10735               || sym->attr.contained))
10736         {
10737           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
10738                      "in '%s' at %L", sym->name, &sym->declared_at);
10739           return FAILURE;
10740         }
10741       if (strcmp ("ppr@", sym->name) == 0)
10742         {
10743           gfc_error ("Procedure pointer result '%s' at %L "
10744                      "is missing the pointer attribute",
10745                      sym->ns->proc_name->name, &sym->declared_at);
10746           return FAILURE;
10747         }
10748     }
10749
10750   return SUCCESS;
10751 }
10752
10753
10754 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
10755    been defined and we now know their defined arguments, check that they fulfill
10756    the requirements of the standard for procedures used as finalizers.  */
10757
10758 static gfc_try
10759 gfc_resolve_finalizers (gfc_symbol* derived)
10760 {
10761   gfc_finalizer* list;
10762   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
10763   gfc_try result = SUCCESS;
10764   bool seen_scalar = false;
10765
10766   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
10767     return SUCCESS;
10768
10769   /* Walk over the list of finalizer-procedures, check them, and if any one
10770      does not fit in with the standard's definition, print an error and remove
10771      it from the list.  */
10772   prev_link = &derived->f2k_derived->finalizers;
10773   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
10774     {
10775       gfc_symbol* arg;
10776       gfc_finalizer* i;
10777       int my_rank;
10778
10779       /* Skip this finalizer if we already resolved it.  */
10780       if (list->proc_tree)
10781         {
10782           prev_link = &(list->next);
10783           continue;
10784         }
10785
10786       /* Check this exists and is a SUBROUTINE.  */
10787       if (!list->proc_sym->attr.subroutine)
10788         {
10789           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
10790                      list->proc_sym->name, &list->where);
10791           goto error;
10792         }
10793
10794       /* We should have exactly one argument.  */
10795       if (!list->proc_sym->formal || list->proc_sym->formal->next)
10796         {
10797           gfc_error ("FINAL procedure at %L must have exactly one argument",
10798                      &list->where);
10799           goto error;
10800         }
10801       arg = list->proc_sym->formal->sym;
10802
10803       /* This argument must be of our type.  */
10804       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
10805         {
10806           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
10807                      &arg->declared_at, derived->name);
10808           goto error;
10809         }
10810
10811       /* It must neither be a pointer nor allocatable nor optional.  */
10812       if (arg->attr.pointer)
10813         {
10814           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
10815                      &arg->declared_at);
10816           goto error;
10817         }
10818       if (arg->attr.allocatable)
10819         {
10820           gfc_error ("Argument of FINAL procedure at %L must not be"
10821                      " ALLOCATABLE", &arg->declared_at);
10822           goto error;
10823         }
10824       if (arg->attr.optional)
10825         {
10826           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
10827                      &arg->declared_at);
10828           goto error;
10829         }
10830
10831       /* It must not be INTENT(OUT).  */
10832       if (arg->attr.intent == INTENT_OUT)
10833         {
10834           gfc_error ("Argument of FINAL procedure at %L must not be"
10835                      " INTENT(OUT)", &arg->declared_at);
10836           goto error;
10837         }
10838
10839       /* Warn if the procedure is non-scalar and not assumed shape.  */
10840       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
10841           && arg->as->type != AS_ASSUMED_SHAPE)
10842         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
10843                      " shape argument", &arg->declared_at);
10844
10845       /* Check that it does not match in kind and rank with a FINAL procedure
10846          defined earlier.  To really loop over the *earlier* declarations,
10847          we need to walk the tail of the list as new ones were pushed at the
10848          front.  */
10849       /* TODO: Handle kind parameters once they are implemented.  */
10850       my_rank = (arg->as ? arg->as->rank : 0);
10851       for (i = list->next; i; i = i->next)
10852         {
10853           /* Argument list might be empty; that is an error signalled earlier,
10854              but we nevertheless continued resolving.  */
10855           if (i->proc_sym->formal)
10856             {
10857               gfc_symbol* i_arg = i->proc_sym->formal->sym;
10858               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
10859               if (i_rank == my_rank)
10860                 {
10861                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
10862                              " rank (%d) as '%s'",
10863                              list->proc_sym->name, &list->where, my_rank, 
10864                              i->proc_sym->name);
10865                   goto error;
10866                 }
10867             }
10868         }
10869
10870         /* Is this the/a scalar finalizer procedure?  */
10871         if (!arg->as || arg->as->rank == 0)
10872           seen_scalar = true;
10873
10874         /* Find the symtree for this procedure.  */
10875         gcc_assert (!list->proc_tree);
10876         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
10877
10878         prev_link = &list->next;
10879         continue;
10880
10881         /* Remove wrong nodes immediately from the list so we don't risk any
10882            troubles in the future when they might fail later expectations.  */
10883 error:
10884         result = FAILURE;
10885         i = list;
10886         *prev_link = list->next;
10887         gfc_free_finalizer (i);
10888     }
10889
10890   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
10891      were nodes in the list, must have been for arrays.  It is surely a good
10892      idea to have a scalar version there if there's something to finalize.  */
10893   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
10894     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
10895                  " defined at %L, suggest also scalar one",
10896                  derived->name, &derived->declared_at);
10897
10898   /* TODO:  Remove this error when finalization is finished.  */
10899   gfc_error ("Finalization at %L is not yet implemented",
10900              &derived->declared_at);
10901
10902   return result;
10903 }
10904
10905
10906 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10907
10908 static gfc_try
10909 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10910                              const char* generic_name, locus where)
10911 {
10912   gfc_symbol* sym1;
10913   gfc_symbol* sym2;
10914
10915   gcc_assert (t1->specific && t2->specific);
10916   gcc_assert (!t1->specific->is_generic);
10917   gcc_assert (!t2->specific->is_generic);
10918
10919   sym1 = t1->specific->u.specific->n.sym;
10920   sym2 = t2->specific->u.specific->n.sym;
10921
10922   if (sym1 == sym2)
10923     return SUCCESS;
10924
10925   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10926   if (sym1->attr.subroutine != sym2->attr.subroutine
10927       || sym1->attr.function != sym2->attr.function)
10928     {
10929       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10930                  " GENERIC '%s' at %L",
10931                  sym1->name, sym2->name, generic_name, &where);
10932       return FAILURE;
10933     }
10934
10935   /* Compare the interfaces.  */
10936   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10937     {
10938       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10939                  sym1->name, sym2->name, generic_name, &where);
10940       return FAILURE;
10941     }
10942
10943   return SUCCESS;
10944 }
10945
10946
10947 /* Worker function for resolving a generic procedure binding; this is used to
10948    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10949
10950    The difference between those cases is finding possible inherited bindings
10951    that are overridden, as one has to look for them in tb_sym_root,
10952    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10953    the super-type and set p->overridden correctly.  */
10954
10955 static gfc_try
10956 resolve_tb_generic_targets (gfc_symbol* super_type,
10957                             gfc_typebound_proc* p, const char* name)
10958 {
10959   gfc_tbp_generic* target;
10960   gfc_symtree* first_target;
10961   gfc_symtree* inherited;
10962
10963   gcc_assert (p && p->is_generic);
10964
10965   /* Try to find the specific bindings for the symtrees in our target-list.  */
10966   gcc_assert (p->u.generic);
10967   for (target = p->u.generic; target; target = target->next)
10968     if (!target->specific)
10969       {
10970         gfc_typebound_proc* overridden_tbp;
10971         gfc_tbp_generic* g;
10972         const char* target_name;
10973
10974         target_name = target->specific_st->name;
10975
10976         /* Defined for this type directly.  */
10977         if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
10978           {
10979             target->specific = target->specific_st->n.tb;
10980             goto specific_found;
10981           }
10982
10983         /* Look for an inherited specific binding.  */
10984         if (super_type)
10985           {
10986             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10987                                                  true, NULL);
10988
10989             if (inherited)
10990               {
10991                 gcc_assert (inherited->n.tb);
10992                 target->specific = inherited->n.tb;
10993                 goto specific_found;
10994               }
10995           }
10996
10997         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10998                    " at %L", target_name, name, &p->where);
10999         return FAILURE;
11000
11001         /* Once we've found the specific binding, check it is not ambiguous with
11002            other specifics already found or inherited for the same GENERIC.  */
11003 specific_found:
11004         gcc_assert (target->specific);
11005
11006         /* This must really be a specific binding!  */
11007         if (target->specific->is_generic)
11008           {
11009             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
11010                        " '%s' is GENERIC, too", name, &p->where, target_name);
11011             return FAILURE;
11012           }
11013
11014         /* Check those already resolved on this type directly.  */
11015         for (g = p->u.generic; g; g = g->next)
11016           if (g != target && g->specific
11017               && check_generic_tbp_ambiguity (target, g, name, p->where)
11018                   == FAILURE)
11019             return FAILURE;
11020
11021         /* Check for ambiguity with inherited specific targets.  */
11022         for (overridden_tbp = p->overridden; overridden_tbp;
11023              overridden_tbp = overridden_tbp->overridden)
11024           if (overridden_tbp->is_generic)
11025             {
11026               for (g = overridden_tbp->u.generic; g; g = g->next)
11027                 {
11028                   gcc_assert (g->specific);
11029                   if (check_generic_tbp_ambiguity (target, g,
11030                                                    name, p->where) == FAILURE)
11031                     return FAILURE;
11032                 }
11033             }
11034       }
11035
11036   /* If we attempt to "overwrite" a specific binding, this is an error.  */
11037   if (p->overridden && !p->overridden->is_generic)
11038     {
11039       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
11040                  " the same name", name, &p->where);
11041       return FAILURE;
11042     }
11043
11044   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
11045      all must have the same attributes here.  */
11046   first_target = p->u.generic->specific->u.specific;
11047   gcc_assert (first_target);
11048   p->subroutine = first_target->n.sym->attr.subroutine;
11049   p->function = first_target->n.sym->attr.function;
11050
11051   return SUCCESS;
11052 }
11053
11054
11055 /* Resolve a GENERIC procedure binding for a derived type.  */
11056
11057 static gfc_try
11058 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
11059 {
11060   gfc_symbol* super_type;
11061
11062   /* Find the overridden binding if any.  */
11063   st->n.tb->overridden = NULL;
11064   super_type = gfc_get_derived_super_type (derived);
11065   if (super_type)
11066     {
11067       gfc_symtree* overridden;
11068       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
11069                                             true, NULL);
11070
11071       if (overridden && overridden->n.tb)
11072         st->n.tb->overridden = overridden->n.tb;
11073     }
11074
11075   /* Resolve using worker function.  */
11076   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
11077 }
11078
11079
11080 /* Retrieve the target-procedure of an operator binding and do some checks in
11081    common for intrinsic and user-defined type-bound operators.  */
11082
11083 static gfc_symbol*
11084 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
11085 {
11086   gfc_symbol* target_proc;
11087
11088   gcc_assert (target->specific && !target->specific->is_generic);
11089   target_proc = target->specific->u.specific->n.sym;
11090   gcc_assert (target_proc);
11091
11092   /* All operator bindings must have a passed-object dummy argument.  */
11093   if (target->specific->nopass)
11094     {
11095       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
11096       return NULL;
11097     }
11098
11099   return target_proc;
11100 }
11101
11102
11103 /* Resolve a type-bound intrinsic operator.  */
11104
11105 static gfc_try
11106 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
11107                                 gfc_typebound_proc* p)
11108 {
11109   gfc_symbol* super_type;
11110   gfc_tbp_generic* target;
11111   
11112   /* If there's already an error here, do nothing (but don't fail again).  */
11113   if (p->error)
11114     return SUCCESS;
11115
11116   /* Operators should always be GENERIC bindings.  */
11117   gcc_assert (p->is_generic);
11118
11119   /* Look for an overridden binding.  */
11120   super_type = gfc_get_derived_super_type (derived);
11121   if (super_type && super_type->f2k_derived)
11122     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
11123                                                      op, true, NULL);
11124   else
11125     p->overridden = NULL;
11126
11127   /* Resolve general GENERIC properties using worker function.  */
11128   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
11129     goto error;
11130
11131   /* Check the targets to be procedures of correct interface.  */
11132   for (target = p->u.generic; target; target = target->next)
11133     {
11134       gfc_symbol* target_proc;
11135
11136       target_proc = get_checked_tb_operator_target (target, p->where);
11137       if (!target_proc)
11138         goto error;
11139
11140       if (!gfc_check_operator_interface (target_proc, op, p->where))
11141         goto error;
11142     }
11143
11144   return SUCCESS;
11145
11146 error:
11147   p->error = 1;
11148   return FAILURE;
11149 }
11150
11151
11152 /* Resolve a type-bound user operator (tree-walker callback).  */
11153
11154 static gfc_symbol* resolve_bindings_derived;
11155 static gfc_try resolve_bindings_result;
11156
11157 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
11158
11159 static void
11160 resolve_typebound_user_op (gfc_symtree* stree)
11161 {
11162   gfc_symbol* super_type;
11163   gfc_tbp_generic* target;
11164
11165   gcc_assert (stree && stree->n.tb);
11166
11167   if (stree->n.tb->error)
11168     return;
11169
11170   /* Operators should always be GENERIC bindings.  */
11171   gcc_assert (stree->n.tb->is_generic);
11172
11173   /* Find overridden procedure, if any.  */
11174   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11175   if (super_type && super_type->f2k_derived)
11176     {
11177       gfc_symtree* overridden;
11178       overridden = gfc_find_typebound_user_op (super_type, NULL,
11179                                                stree->name, true, NULL);
11180
11181       if (overridden && overridden->n.tb)
11182         stree->n.tb->overridden = overridden->n.tb;
11183     }
11184   else
11185     stree->n.tb->overridden = NULL;
11186
11187   /* Resolve basically using worker function.  */
11188   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
11189         == FAILURE)
11190     goto error;
11191
11192   /* Check the targets to be functions of correct interface.  */
11193   for (target = stree->n.tb->u.generic; target; target = target->next)
11194     {
11195       gfc_symbol* target_proc;
11196
11197       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
11198       if (!target_proc)
11199         goto error;
11200
11201       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
11202         goto error;
11203     }
11204
11205   return;
11206
11207 error:
11208   resolve_bindings_result = FAILURE;
11209   stree->n.tb->error = 1;
11210 }
11211
11212
11213 /* Resolve the type-bound procedures for a derived type.  */
11214
11215 static void
11216 resolve_typebound_procedure (gfc_symtree* stree)
11217 {
11218   gfc_symbol* proc;
11219   locus where;
11220   gfc_symbol* me_arg;
11221   gfc_symbol* super_type;
11222   gfc_component* comp;
11223
11224   gcc_assert (stree);
11225
11226   /* Undefined specific symbol from GENERIC target definition.  */
11227   if (!stree->n.tb)
11228     return;
11229
11230   if (stree->n.tb->error)
11231     return;
11232
11233   /* If this is a GENERIC binding, use that routine.  */
11234   if (stree->n.tb->is_generic)
11235     {
11236       if (resolve_typebound_generic (resolve_bindings_derived, stree)
11237             == FAILURE)
11238         goto error;
11239       return;
11240     }
11241
11242   /* Get the target-procedure to check it.  */
11243   gcc_assert (!stree->n.tb->is_generic);
11244   gcc_assert (stree->n.tb->u.specific);
11245   proc = stree->n.tb->u.specific->n.sym;
11246   where = stree->n.tb->where;
11247
11248   /* Default access should already be resolved from the parser.  */
11249   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
11250
11251   /* It should be a module procedure or an external procedure with explicit
11252      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
11253   if ((!proc->attr.subroutine && !proc->attr.function)
11254       || (proc->attr.proc != PROC_MODULE
11255           && proc->attr.if_source != IFSRC_IFBODY)
11256       || (proc->attr.abstract && !stree->n.tb->deferred))
11257     {
11258       gfc_error ("'%s' must be a module procedure or an external procedure with"
11259                  " an explicit interface at %L", proc->name, &where);
11260       goto error;
11261     }
11262   stree->n.tb->subroutine = proc->attr.subroutine;
11263   stree->n.tb->function = proc->attr.function;
11264
11265   /* Find the super-type of the current derived type.  We could do this once and
11266      store in a global if speed is needed, but as long as not I believe this is
11267      more readable and clearer.  */
11268   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11269
11270   /* If PASS, resolve and check arguments if not already resolved / loaded
11271      from a .mod file.  */
11272   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
11273     {
11274       if (stree->n.tb->pass_arg)
11275         {
11276           gfc_formal_arglist* i;
11277
11278           /* If an explicit passing argument name is given, walk the arg-list
11279              and look for it.  */
11280
11281           me_arg = NULL;
11282           stree->n.tb->pass_arg_num = 1;
11283           for (i = proc->formal; i; i = i->next)
11284             {
11285               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
11286                 {
11287                   me_arg = i->sym;
11288                   break;
11289                 }
11290               ++stree->n.tb->pass_arg_num;
11291             }
11292
11293           if (!me_arg)
11294             {
11295               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
11296                          " argument '%s'",
11297                          proc->name, stree->n.tb->pass_arg, &where,
11298                          stree->n.tb->pass_arg);
11299               goto error;
11300             }
11301         }
11302       else
11303         {
11304           /* Otherwise, take the first one; there should in fact be at least
11305              one.  */
11306           stree->n.tb->pass_arg_num = 1;
11307           if (!proc->formal)
11308             {
11309               gfc_error ("Procedure '%s' with PASS at %L must have at"
11310                          " least one argument", proc->name, &where);
11311               goto error;
11312             }
11313           me_arg = proc->formal->sym;
11314         }
11315
11316       /* Now check that the argument-type matches and the passed-object
11317          dummy argument is generally fine.  */
11318
11319       gcc_assert (me_arg);
11320
11321       if (me_arg->ts.type != BT_CLASS)
11322         {
11323           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11324                      " at %L", proc->name, &where);
11325           goto error;
11326         }
11327
11328       if (CLASS_DATA (me_arg)->ts.u.derived
11329           != resolve_bindings_derived)
11330         {
11331           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11332                      " the derived-type '%s'", me_arg->name, proc->name,
11333                      me_arg->name, &where, resolve_bindings_derived->name);
11334           goto error;
11335         }
11336   
11337       gcc_assert (me_arg->ts.type == BT_CLASS);
11338       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
11339         {
11340           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
11341                      " scalar", proc->name, &where);
11342           goto error;
11343         }
11344       if (CLASS_DATA (me_arg)->attr.allocatable)
11345         {
11346           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11347                      " be ALLOCATABLE", proc->name, &where);
11348           goto error;
11349         }
11350       if (CLASS_DATA (me_arg)->attr.class_pointer)
11351         {
11352           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11353                      " be POINTER", proc->name, &where);
11354           goto error;
11355         }
11356     }
11357
11358   /* If we are extending some type, check that we don't override a procedure
11359      flagged NON_OVERRIDABLE.  */
11360   stree->n.tb->overridden = NULL;
11361   if (super_type)
11362     {
11363       gfc_symtree* overridden;
11364       overridden = gfc_find_typebound_proc (super_type, NULL,
11365                                             stree->name, true, NULL);
11366
11367       if (overridden)
11368         {
11369           if (overridden->n.tb)
11370             stree->n.tb->overridden = overridden->n.tb;
11371
11372           if (gfc_check_typebound_override (stree, overridden) == FAILURE)
11373             goto error;
11374         }
11375     }
11376
11377   /* See if there's a name collision with a component directly in this type.  */
11378   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
11379     if (!strcmp (comp->name, stree->name))
11380       {
11381         gfc_error ("Procedure '%s' at %L has the same name as a component of"
11382                    " '%s'",
11383                    stree->name, &where, resolve_bindings_derived->name);
11384         goto error;
11385       }
11386
11387   /* Try to find a name collision with an inherited component.  */
11388   if (super_type && gfc_find_component (super_type, stree->name, true, true))
11389     {
11390       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
11391                  " component of '%s'",
11392                  stree->name, &where, resolve_bindings_derived->name);
11393       goto error;
11394     }
11395
11396   stree->n.tb->error = 0;
11397   return;
11398
11399 error:
11400   resolve_bindings_result = FAILURE;
11401   stree->n.tb->error = 1;
11402 }
11403
11404
11405 static gfc_try
11406 resolve_typebound_procedures (gfc_symbol* derived)
11407 {
11408   int op;
11409   gfc_symbol* super_type;
11410
11411   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
11412     return SUCCESS;
11413   
11414   super_type = gfc_get_derived_super_type (derived);
11415   if (super_type)
11416     resolve_typebound_procedures (super_type);
11417
11418   resolve_bindings_derived = derived;
11419   resolve_bindings_result = SUCCESS;
11420
11421   /* Make sure the vtab has been generated.  */
11422   gfc_find_derived_vtab (derived);
11423
11424   if (derived->f2k_derived->tb_sym_root)
11425     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
11426                           &resolve_typebound_procedure);
11427
11428   if (derived->f2k_derived->tb_uop_root)
11429     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
11430                           &resolve_typebound_user_op);
11431
11432   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
11433     {
11434       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
11435       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
11436                                                p) == FAILURE)
11437         resolve_bindings_result = FAILURE;
11438     }
11439
11440   return resolve_bindings_result;
11441 }
11442
11443
11444 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
11445    to give all identical derived types the same backend_decl.  */
11446 static void
11447 add_dt_to_dt_list (gfc_symbol *derived)
11448 {
11449   gfc_dt_list *dt_list;
11450
11451   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
11452     if (derived == dt_list->derived)
11453       return;
11454
11455   dt_list = gfc_get_dt_list ();
11456   dt_list->next = gfc_derived_types;
11457   dt_list->derived = derived;
11458   gfc_derived_types = dt_list;
11459 }
11460
11461
11462 /* Ensure that a derived-type is really not abstract, meaning that every
11463    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
11464
11465 static gfc_try
11466 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
11467 {
11468   if (!st)
11469     return SUCCESS;
11470
11471   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
11472     return FAILURE;
11473   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
11474     return FAILURE;
11475
11476   if (st->n.tb && st->n.tb->deferred)
11477     {
11478       gfc_symtree* overriding;
11479       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
11480       if (!overriding)
11481         return FAILURE;
11482       gcc_assert (overriding->n.tb);
11483       if (overriding->n.tb->deferred)
11484         {
11485           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
11486                      " '%s' is DEFERRED and not overridden",
11487                      sub->name, &sub->declared_at, st->name);
11488           return FAILURE;
11489         }
11490     }
11491
11492   return SUCCESS;
11493 }
11494
11495 static gfc_try
11496 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
11497 {
11498   /* The algorithm used here is to recursively travel up the ancestry of sub
11499      and for each ancestor-type, check all bindings.  If any of them is
11500      DEFERRED, look it up starting from sub and see if the found (overriding)
11501      binding is not DEFERRED.
11502      This is not the most efficient way to do this, but it should be ok and is
11503      clearer than something sophisticated.  */
11504
11505   gcc_assert (ancestor && !sub->attr.abstract);
11506   
11507   if (!ancestor->attr.abstract)
11508     return SUCCESS;
11509
11510   /* Walk bindings of this ancestor.  */
11511   if (ancestor->f2k_derived)
11512     {
11513       gfc_try t;
11514       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
11515       if (t == FAILURE)
11516         return FAILURE;
11517     }
11518
11519   /* Find next ancestor type and recurse on it.  */
11520   ancestor = gfc_get_derived_super_type (ancestor);
11521   if (ancestor)
11522     return ensure_not_abstract (sub, ancestor);
11523
11524   return SUCCESS;
11525 }
11526
11527
11528 /* Resolve the components of a derived type. This does not have to wait until
11529    resolution stage, but can be done as soon as the dt declaration has been
11530    parsed.  */
11531
11532 static gfc_try
11533 resolve_fl_derived0 (gfc_symbol *sym)
11534 {
11535   gfc_symbol* super_type;
11536   gfc_component *c;
11537
11538   super_type = gfc_get_derived_super_type (sym);
11539
11540   /* F2008, C432. */
11541   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
11542     {
11543       gfc_error ("As extending type '%s' at %L has a coarray component, "
11544                  "parent type '%s' shall also have one", sym->name,
11545                  &sym->declared_at, super_type->name);
11546       return FAILURE;
11547     }
11548
11549   /* Ensure the extended type gets resolved before we do.  */
11550   if (super_type && resolve_fl_derived0 (super_type) == FAILURE)
11551     return FAILURE;
11552
11553   /* An ABSTRACT type must be extensible.  */
11554   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
11555     {
11556       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
11557                  sym->name, &sym->declared_at);
11558       return FAILURE;
11559     }
11560
11561   c = (sym->attr.is_class) ? sym->components->ts.u.derived->components
11562                            : sym->components;
11563
11564   for ( ; c != NULL; c = c->next)
11565     {
11566       /* See PRs 51550, 47545, 48654, 49050, 51075 - and 45170.  */
11567       if (c->ts.type == BT_CHARACTER && c->ts.deferred)
11568         {
11569           gfc_error ("Deferred-length character component '%s' at %L is not "
11570                      "yet supported", c->name, &c->loc);
11571           return FAILURE;
11572         }
11573
11574       /* F2008, C442.  */
11575       if ((!sym->attr.is_class || c != sym->components)
11576           && c->attr.codimension
11577           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
11578         {
11579           gfc_error ("Coarray component '%s' at %L must be allocatable with "
11580                      "deferred shape", c->name, &c->loc);
11581           return FAILURE;
11582         }
11583
11584       /* F2008, C443.  */
11585       if (c->attr.codimension && c->ts.type == BT_DERIVED
11586           && c->ts.u.derived->ts.is_iso_c)
11587         {
11588           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11589                      "shall not be a coarray", c->name, &c->loc);
11590           return FAILURE;
11591         }
11592
11593       /* F2008, C444.  */
11594       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
11595           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
11596               || c->attr.allocatable))
11597         {
11598           gfc_error ("Component '%s' at %L with coarray component "
11599                      "shall be a nonpointer, nonallocatable scalar",
11600                      c->name, &c->loc);
11601           return FAILURE;
11602         }
11603
11604       /* F2008, C448.  */
11605       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
11606         {
11607           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
11608                      "is not an array pointer", c->name, &c->loc);
11609           return FAILURE;
11610         }
11611
11612       if (c->attr.proc_pointer && c->ts.interface)
11613         {
11614           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
11615             gfc_error ("Interface '%s', used by procedure pointer component "
11616                        "'%s' at %L, is declared in a later PROCEDURE statement",
11617                        c->ts.interface->name, c->name, &c->loc);
11618
11619           /* Get the attributes from the interface (now resolved).  */
11620           if (c->ts.interface->attr.if_source
11621               || c->ts.interface->attr.intrinsic)
11622             {
11623               gfc_symbol *ifc = c->ts.interface;
11624
11625               if (ifc->formal && !ifc->formal_ns)
11626                 resolve_symbol (ifc);
11627
11628               if (ifc->attr.intrinsic)
11629                 resolve_intrinsic (ifc, &ifc->declared_at);
11630
11631               if (ifc->result)
11632                 {
11633                   c->ts = ifc->result->ts;
11634                   c->attr.allocatable = ifc->result->attr.allocatable;
11635                   c->attr.pointer = ifc->result->attr.pointer;
11636                   c->attr.dimension = ifc->result->attr.dimension;
11637                   c->as = gfc_copy_array_spec (ifc->result->as);
11638                 }
11639               else
11640                 {   
11641                   c->ts = ifc->ts;
11642                   c->attr.allocatable = ifc->attr.allocatable;
11643                   c->attr.pointer = ifc->attr.pointer;
11644                   c->attr.dimension = ifc->attr.dimension;
11645                   c->as = gfc_copy_array_spec (ifc->as);
11646                 }
11647               c->ts.interface = ifc;
11648               c->attr.function = ifc->attr.function;
11649               c->attr.subroutine = ifc->attr.subroutine;
11650               gfc_copy_formal_args_ppc (c, ifc);
11651
11652               c->attr.pure = ifc->attr.pure;
11653               c->attr.elemental = ifc->attr.elemental;
11654               c->attr.recursive = ifc->attr.recursive;
11655               c->attr.always_explicit = ifc->attr.always_explicit;
11656               c->attr.ext_attr |= ifc->attr.ext_attr;
11657               /* Replace symbols in array spec.  */
11658               if (c->as)
11659                 {
11660                   int i;
11661                   for (i = 0; i < c->as->rank; i++)
11662                     {
11663                       gfc_expr_replace_comp (c->as->lower[i], c);
11664                       gfc_expr_replace_comp (c->as->upper[i], c);
11665                     }
11666                 }
11667               /* Copy char length.  */
11668               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11669                 {
11670                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11671                   gfc_expr_replace_comp (cl->length, c);
11672                   if (cl->length && !cl->resolved
11673                         && gfc_resolve_expr (cl->length) == FAILURE)
11674                     return FAILURE;
11675                   c->ts.u.cl = cl;
11676                 }
11677             }
11678           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
11679             {
11680               gfc_error ("Interface '%s' of procedure pointer component "
11681                          "'%s' at %L must be explicit", c->ts.interface->name,
11682                          c->name, &c->loc);
11683               return FAILURE;
11684             }
11685         }
11686       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
11687         {
11688           /* Since PPCs are not implicitly typed, a PPC without an explicit
11689              interface must be a subroutine.  */
11690           gfc_add_subroutine (&c->attr, c->name, &c->loc);
11691         }
11692
11693       /* Procedure pointer components: Check PASS arg.  */
11694       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
11695           && !sym->attr.vtype)
11696         {
11697           gfc_symbol* me_arg;
11698
11699           if (c->tb->pass_arg)
11700             {
11701               gfc_formal_arglist* i;
11702
11703               /* If an explicit passing argument name is given, walk the arg-list
11704                 and look for it.  */
11705
11706               me_arg = NULL;
11707               c->tb->pass_arg_num = 1;
11708               for (i = c->formal; i; i = i->next)
11709                 {
11710                   if (!strcmp (i->sym->name, c->tb->pass_arg))
11711                     {
11712                       me_arg = i->sym;
11713                       break;
11714                     }
11715                   c->tb->pass_arg_num++;
11716                 }
11717
11718               if (!me_arg)
11719                 {
11720                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
11721                              "at %L has no argument '%s'", c->name,
11722                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
11723                   c->tb->error = 1;
11724                   return FAILURE;
11725                 }
11726             }
11727           else
11728             {
11729               /* Otherwise, take the first one; there should in fact be at least
11730                 one.  */
11731               c->tb->pass_arg_num = 1;
11732               if (!c->formal)
11733                 {
11734                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
11735                              "must have at least one argument",
11736                              c->name, &c->loc);
11737                   c->tb->error = 1;
11738                   return FAILURE;
11739                 }
11740               me_arg = c->formal->sym;
11741             }
11742
11743           /* Now check that the argument-type matches.  */
11744           gcc_assert (me_arg);
11745           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
11746               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
11747               || (me_arg->ts.type == BT_CLASS
11748                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
11749             {
11750               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11751                          " the derived type '%s'", me_arg->name, c->name,
11752                          me_arg->name, &c->loc, sym->name);
11753               c->tb->error = 1;
11754               return FAILURE;
11755             }
11756
11757           /* Check for C453.  */
11758           if (me_arg->attr.dimension)
11759             {
11760               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11761                          "must be scalar", me_arg->name, c->name, me_arg->name,
11762                          &c->loc);
11763               c->tb->error = 1;
11764               return FAILURE;
11765             }
11766
11767           if (me_arg->attr.pointer)
11768             {
11769               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11770                          "may not have the POINTER attribute", me_arg->name,
11771                          c->name, me_arg->name, &c->loc);
11772               c->tb->error = 1;
11773               return FAILURE;
11774             }
11775
11776           if (me_arg->attr.allocatable)
11777             {
11778               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11779                          "may not be ALLOCATABLE", me_arg->name, c->name,
11780                          me_arg->name, &c->loc);
11781               c->tb->error = 1;
11782               return FAILURE;
11783             }
11784
11785           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11786             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11787                        " at %L", c->name, &c->loc);
11788
11789         }
11790
11791       /* Check type-spec if this is not the parent-type component.  */
11792       if (((sym->attr.is_class
11793             && (!sym->components->ts.u.derived->attr.extension
11794                 || c != sym->components->ts.u.derived->components))
11795            || (!sym->attr.is_class
11796                && (!sym->attr.extension || c != sym->components)))
11797           && !sym->attr.vtype
11798           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11799         return FAILURE;
11800
11801       /* If this type is an extension, set the accessibility of the parent
11802          component.  */
11803       if (super_type
11804           && ((sym->attr.is_class
11805                && c == sym->components->ts.u.derived->components)
11806               || (!sym->attr.is_class && c == sym->components))
11807           && strcmp (super_type->name, c->name) == 0)
11808         c->attr.access = super_type->attr.access;
11809       
11810       /* If this type is an extension, see if this component has the same name
11811          as an inherited type-bound procedure.  */
11812       if (super_type && !sym->attr.is_class
11813           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11814         {
11815           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11816                      " inherited type-bound procedure",
11817                      c->name, sym->name, &c->loc);
11818           return FAILURE;
11819         }
11820
11821       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer
11822             && !c->ts.deferred)
11823         {
11824          if (c->ts.u.cl->length == NULL
11825              || (resolve_charlen (c->ts.u.cl) == FAILURE)
11826              || !gfc_is_constant_expr (c->ts.u.cl->length))
11827            {
11828              gfc_error ("Character length of component '%s' needs to "
11829                         "be a constant specification expression at %L",
11830                         c->name,
11831                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
11832              return FAILURE;
11833            }
11834         }
11835
11836       if (c->ts.type == BT_CHARACTER && c->ts.deferred
11837           && !c->attr.pointer && !c->attr.allocatable)
11838         {
11839           gfc_error ("Character component '%s' of '%s' at %L with deferred "
11840                      "length must be a POINTER or ALLOCATABLE",
11841                      c->name, sym->name, &c->loc);
11842           return FAILURE;
11843         }
11844
11845       if (c->ts.type == BT_DERIVED
11846           && sym->component_access != ACCESS_PRIVATE
11847           && gfc_check_symbol_access (sym)
11848           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11849           && !c->ts.u.derived->attr.use_assoc
11850           && !gfc_check_symbol_access (c->ts.u.derived)
11851           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11852                              "is a PRIVATE type and cannot be a component of "
11853                              "'%s', which is PUBLIC at %L", c->name,
11854                              sym->name, &sym->declared_at) == FAILURE)
11855         return FAILURE;
11856
11857       if ((sym->attr.sequence || sym->attr.is_bind_c) && c->ts.type == BT_CLASS)
11858         {
11859           gfc_error ("Polymorphic component %s at %L in SEQUENCE or BIND(C) "
11860                      "type %s", c->name, &c->loc, sym->name);
11861           return FAILURE;
11862         }
11863
11864       if (sym->attr.sequence)
11865         {
11866           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
11867             {
11868               gfc_error ("Component %s of SEQUENCE type declared at %L does "
11869                          "not have the SEQUENCE attribute",
11870                          c->ts.u.derived->name, &sym->declared_at);
11871               return FAILURE;
11872             }
11873         }
11874
11875       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.generic)
11876         c->ts.u.derived = gfc_find_dt_in_generic (c->ts.u.derived);
11877       else if (c->ts.type == BT_CLASS && c->attr.class_ok
11878                && CLASS_DATA (c)->ts.u.derived->attr.generic)
11879         CLASS_DATA (c)->ts.u.derived
11880                         = gfc_find_dt_in_generic (CLASS_DATA (c)->ts.u.derived);
11881
11882       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && !sym->attr.vtype
11883           && c->attr.pointer && c->ts.u.derived->components == NULL
11884           && !c->ts.u.derived->attr.zero_comp)
11885         {
11886           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11887                      "that has not been declared", c->name, sym->name,
11888                      &c->loc);
11889           return FAILURE;
11890         }
11891
11892       if (c->ts.type == BT_CLASS && c->attr.class_ok
11893           && CLASS_DATA (c)->attr.class_pointer
11894           && CLASS_DATA (c)->ts.u.derived->components == NULL
11895           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
11896         {
11897           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11898                      "that has not been declared", c->name, sym->name,
11899                      &c->loc);
11900           return FAILURE;
11901         }
11902
11903       /* C437.  */
11904       if (c->ts.type == BT_CLASS && c->attr.flavor != FL_PROCEDURE
11905           && (!c->attr.class_ok
11906               || !(CLASS_DATA (c)->attr.class_pointer
11907                    || CLASS_DATA (c)->attr.allocatable)))
11908         {
11909           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
11910                      "or pointer", c->name, &c->loc);
11911           return FAILURE;
11912         }
11913
11914       /* Ensure that all the derived type components are put on the
11915          derived type list; even in formal namespaces, where derived type
11916          pointer components might not have been declared.  */
11917       if (c->ts.type == BT_DERIVED
11918             && c->ts.u.derived
11919             && c->ts.u.derived->components
11920             && c->attr.pointer
11921             && sym != c->ts.u.derived)
11922         add_dt_to_dt_list (c->ts.u.derived);
11923
11924       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
11925                                            || c->attr.proc_pointer
11926                                            || c->attr.allocatable)) == FAILURE)
11927         return FAILURE;
11928     }
11929
11930   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11931      all DEFERRED bindings are overridden.  */
11932   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11933       && !sym->attr.is_class
11934       && ensure_not_abstract (sym, super_type) == FAILURE)
11935     return FAILURE;
11936
11937   /* Add derived type to the derived type list.  */
11938   add_dt_to_dt_list (sym);
11939
11940   return SUCCESS;
11941 }
11942
11943
11944 /* The following procedure does the full resolution of a derived type,
11945    including resolution of all type-bound procedures (if present). In contrast
11946    to 'resolve_fl_derived0' this can only be done after the module has been
11947    parsed completely.  */
11948
11949 static gfc_try
11950 resolve_fl_derived (gfc_symbol *sym)
11951 {
11952   gfc_symbol *gen_dt = NULL;
11953
11954   if (!sym->attr.is_class)
11955     gfc_find_symbol (sym->name, sym->ns, 0, &gen_dt);
11956   if (gen_dt && gen_dt->generic && gen_dt->generic->next
11957       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Generic name '%s' of "
11958                          "function '%s' at %L being the same name as derived "
11959                          "type at %L", sym->name,
11960                          gen_dt->generic->sym == sym
11961                            ? gen_dt->generic->next->sym->name
11962                            : gen_dt->generic->sym->name,
11963                          gen_dt->generic->sym == sym
11964                            ? &gen_dt->generic->next->sym->declared_at
11965                            : &gen_dt->generic->sym->declared_at,
11966                          &sym->declared_at) == FAILURE)
11967     return FAILURE;
11968
11969   if (sym->attr.is_class && sym->ts.u.derived == NULL)
11970     {
11971       /* Fix up incomplete CLASS symbols.  */
11972       gfc_component *data = gfc_find_component (sym, "_data", true, true);
11973       gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true);
11974       if (vptr->ts.u.derived == NULL)
11975         {
11976           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
11977           gcc_assert (vtab);
11978           vptr->ts.u.derived = vtab->ts.u.derived;
11979         }
11980     }
11981   
11982   if (resolve_fl_derived0 (sym) == FAILURE)
11983     return FAILURE;
11984   
11985   /* Resolve the type-bound procedures.  */
11986   if (resolve_typebound_procedures (sym) == FAILURE)
11987     return FAILURE;
11988
11989   /* Resolve the finalizer procedures.  */
11990   if (gfc_resolve_finalizers (sym) == FAILURE)
11991     return FAILURE;
11992   
11993   return SUCCESS;
11994 }
11995
11996
11997 static gfc_try
11998 resolve_fl_namelist (gfc_symbol *sym)
11999 {
12000   gfc_namelist *nl;
12001   gfc_symbol *nlsym;
12002
12003   for (nl = sym->namelist; nl; nl = nl->next)
12004     {
12005       /* Check again, the check in match only works if NAMELIST comes
12006          after the decl.  */
12007       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SIZE)
12008         {
12009           gfc_error ("Assumed size array '%s' in namelist '%s' at %L is not "
12010                      "allowed", nl->sym->name, sym->name, &sym->declared_at);
12011           return FAILURE;
12012         }
12013
12014       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
12015           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: NAMELIST array "
12016                              "object '%s' with assumed shape in namelist "
12017                              "'%s' at %L", nl->sym->name, sym->name,
12018                              &sym->declared_at) == FAILURE)
12019         return FAILURE;
12020
12021       if (is_non_constant_shape_array (nl->sym)
12022           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST array "
12023                              "object '%s' with nonconstant shape in namelist "
12024                              "'%s' at %L", nl->sym->name, sym->name,
12025                              &sym->declared_at) == FAILURE)
12026         return FAILURE;
12027
12028       if (nl->sym->ts.type == BT_CHARACTER
12029           && (nl->sym->ts.u.cl->length == NULL
12030               || !gfc_is_constant_expr (nl->sym->ts.u.cl->length))
12031           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
12032                              "'%s' with nonconstant character length in "
12033                              "namelist '%s' at %L", nl->sym->name, sym->name,
12034                              &sym->declared_at) == FAILURE)
12035         return FAILURE;
12036
12037       /* FIXME: Once UDDTIO is implemented, the following can be
12038          removed.  */
12039       if (nl->sym->ts.type == BT_CLASS)
12040         {
12041           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L is "
12042                      "polymorphic and requires a defined input/output "
12043                      "procedure", nl->sym->name, sym->name, &sym->declared_at);
12044           return FAILURE;
12045         }
12046
12047       if (nl->sym->ts.type == BT_DERIVED
12048           && (nl->sym->ts.u.derived->attr.alloc_comp
12049               || nl->sym->ts.u.derived->attr.pointer_comp))
12050         {
12051           if (gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
12052                               "'%s' in namelist '%s' at %L with ALLOCATABLE "
12053                               "or POINTER components", nl->sym->name,
12054                               sym->name, &sym->declared_at) == FAILURE)
12055             return FAILURE;
12056
12057          /* FIXME: Once UDDTIO is implemented, the following can be
12058             removed.  */
12059           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L has "
12060                      "ALLOCATABLE or POINTER components and thus requires "
12061                      "a defined input/output procedure", nl->sym->name,
12062                      sym->name, &sym->declared_at);
12063           return FAILURE;
12064         }
12065     }
12066
12067   /* Reject PRIVATE objects in a PUBLIC namelist.  */
12068   if (gfc_check_symbol_access (sym))
12069     {
12070       for (nl = sym->namelist; nl; nl = nl->next)
12071         {
12072           if (!nl->sym->attr.use_assoc
12073               && !is_sym_host_assoc (nl->sym, sym->ns)
12074               && !gfc_check_symbol_access (nl->sym))
12075             {
12076               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
12077                          "cannot be member of PUBLIC namelist '%s' at %L",
12078                          nl->sym->name, sym->name, &sym->declared_at);
12079               return FAILURE;
12080             }
12081
12082           /* Types with private components that came here by USE-association.  */
12083           if (nl->sym->ts.type == BT_DERIVED
12084               && derived_inaccessible (nl->sym->ts.u.derived))
12085             {
12086               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
12087                          "components and cannot be member of namelist '%s' at %L",
12088                          nl->sym->name, sym->name, &sym->declared_at);
12089               return FAILURE;
12090             }
12091
12092           /* Types with private components that are defined in the same module.  */
12093           if (nl->sym->ts.type == BT_DERIVED
12094               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
12095               && nl->sym->ts.u.derived->attr.private_comp)
12096             {
12097               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
12098                          "cannot be a member of PUBLIC namelist '%s' at %L",
12099                          nl->sym->name, sym->name, &sym->declared_at);
12100               return FAILURE;
12101             }
12102         }
12103     }
12104
12105
12106   /* 14.1.2 A module or internal procedure represent local entities
12107      of the same type as a namelist member and so are not allowed.  */
12108   for (nl = sym->namelist; nl; nl = nl->next)
12109     {
12110       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
12111         continue;
12112
12113       if (nl->sym->attr.function && nl->sym == nl->sym->result)
12114         if ((nl->sym == sym->ns->proc_name)
12115                ||
12116             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
12117           continue;
12118
12119       nlsym = NULL;
12120       if (nl->sym && nl->sym->name)
12121         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
12122       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
12123         {
12124           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
12125                      "attribute in '%s' at %L", nlsym->name,
12126                      &sym->declared_at);
12127           return FAILURE;
12128         }
12129     }
12130
12131   return SUCCESS;
12132 }
12133
12134
12135 static gfc_try
12136 resolve_fl_parameter (gfc_symbol *sym)
12137 {
12138   /* A parameter array's shape needs to be constant.  */
12139   if (sym->as != NULL 
12140       && (sym->as->type == AS_DEFERRED
12141           || is_non_constant_shape_array (sym)))
12142     {
12143       gfc_error ("Parameter array '%s' at %L cannot be automatic "
12144                  "or of deferred shape", sym->name, &sym->declared_at);
12145       return FAILURE;
12146     }
12147
12148   /* Make sure a parameter that has been implicitly typed still
12149      matches the implicit type, since PARAMETER statements can precede
12150      IMPLICIT statements.  */
12151   if (sym->attr.implicit_type
12152       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
12153                                                              sym->ns)))
12154     {
12155       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
12156                  "later IMPLICIT type", sym->name, &sym->declared_at);
12157       return FAILURE;
12158     }
12159
12160   /* Make sure the types of derived parameters are consistent.  This
12161      type checking is deferred until resolution because the type may
12162      refer to a derived type from the host.  */
12163   if (sym->ts.type == BT_DERIVED && sym->value
12164       && !gfc_compare_types (&sym->ts, &sym->value->ts))
12165     {
12166       gfc_error ("Incompatible derived type in PARAMETER at %L",
12167                  &sym->value->where);
12168       return FAILURE;
12169     }
12170   return SUCCESS;
12171 }
12172
12173
12174 /* Do anything necessary to resolve a symbol.  Right now, we just
12175    assume that an otherwise unknown symbol is a variable.  This sort
12176    of thing commonly happens for symbols in module.  */
12177
12178 static void
12179 resolve_symbol (gfc_symbol *sym)
12180 {
12181   int check_constant, mp_flag;
12182   gfc_symtree *symtree;
12183   gfc_symtree *this_symtree;
12184   gfc_namespace *ns;
12185   gfc_component *c;
12186   symbol_attribute class_attr;
12187   gfc_array_spec *as;
12188
12189   if (sym->attr.flavor == FL_UNKNOWN)
12190     {
12191
12192     /* If we find that a flavorless symbol is an interface in one of the
12193        parent namespaces, find its symtree in this namespace, free the
12194        symbol and set the symtree to point to the interface symbol.  */
12195       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
12196         {
12197           symtree = gfc_find_symtree (ns->sym_root, sym->name);
12198           if (symtree && (symtree->n.sym->generic ||
12199                           (symtree->n.sym->attr.flavor == FL_PROCEDURE
12200                            && sym->ns->construct_entities)))
12201             {
12202               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
12203                                                sym->name);
12204               gfc_release_symbol (sym);
12205               symtree->n.sym->refs++;
12206               this_symtree->n.sym = symtree->n.sym;
12207               return;
12208             }
12209         }
12210
12211       /* Otherwise give it a flavor according to such attributes as
12212          it has.  */
12213       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
12214         sym->attr.flavor = FL_VARIABLE;
12215       else
12216         {
12217           sym->attr.flavor = FL_PROCEDURE;
12218           if (sym->attr.dimension)
12219             sym->attr.function = 1;
12220         }
12221     }
12222
12223   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
12224     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
12225
12226   if (sym->attr.procedure && sym->ts.interface
12227       && sym->attr.if_source != IFSRC_DECL
12228       && resolve_procedure_interface (sym) == FAILURE)
12229     return;
12230
12231   if (sym->attr.is_protected && !sym->attr.proc_pointer
12232       && (sym->attr.procedure || sym->attr.external))
12233     {
12234       if (sym->attr.external)
12235         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
12236                    "at %L", &sym->declared_at);
12237       else
12238         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
12239                    "at %L", &sym->declared_at);
12240
12241       return;
12242     }
12243
12244   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
12245     return;
12246
12247   /* Symbols that are module procedures with results (functions) have
12248      the types and array specification copied for type checking in
12249      procedures that call them, as well as for saving to a module
12250      file.  These symbols can't stand the scrutiny that their results
12251      can.  */
12252   mp_flag = (sym->result != NULL && sym->result != sym);
12253
12254   /* Make sure that the intrinsic is consistent with its internal 
12255      representation. This needs to be done before assigning a default 
12256      type to avoid spurious warnings.  */
12257   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
12258       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
12259     return;
12260
12261   /* Resolve associate names.  */
12262   if (sym->assoc)
12263     resolve_assoc_var (sym, true);
12264
12265   /* Assign default type to symbols that need one and don't have one.  */
12266   if (sym->ts.type == BT_UNKNOWN)
12267     {
12268       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
12269         {
12270           gfc_set_default_type (sym, 1, NULL);
12271         }
12272
12273       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
12274           && !sym->attr.function && !sym->attr.subroutine
12275           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
12276         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
12277
12278       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12279         {
12280           /* The specific case of an external procedure should emit an error
12281              in the case that there is no implicit type.  */
12282           if (!mp_flag)
12283             gfc_set_default_type (sym, sym->attr.external, NULL);
12284           else
12285             {
12286               /* Result may be in another namespace.  */
12287               resolve_symbol (sym->result);
12288
12289               if (!sym->result->attr.proc_pointer)
12290                 {
12291                   sym->ts = sym->result->ts;
12292                   sym->as = gfc_copy_array_spec (sym->result->as);
12293                   sym->attr.dimension = sym->result->attr.dimension;
12294                   sym->attr.pointer = sym->result->attr.pointer;
12295                   sym->attr.allocatable = sym->result->attr.allocatable;
12296                   sym->attr.contiguous = sym->result->attr.contiguous;
12297                 }
12298             }
12299         }
12300     }
12301   else if (mp_flag && sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12302     gfc_resolve_array_spec (sym->result->as, false);
12303
12304   if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
12305     {
12306       as = CLASS_DATA (sym)->as;
12307       class_attr = CLASS_DATA (sym)->attr;
12308       class_attr.pointer = class_attr.class_pointer;
12309     }
12310   else
12311     {
12312       class_attr = sym->attr;
12313       as = sym->as;
12314     }
12315
12316   /* F2008, C530. */
12317   if (sym->attr.contiguous
12318       && (!class_attr.dimension
12319           || (as->type != AS_ASSUMED_SHAPE && !class_attr.pointer)))
12320     {
12321       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
12322                   "array pointer or an assumed-shape array", sym->name,
12323                   &sym->declared_at);
12324       return;
12325     }
12326
12327   /* Assumed size arrays and assumed shape arrays must be dummy
12328      arguments.  Array-spec's of implied-shape should have been resolved to
12329      AS_EXPLICIT already.  */
12330
12331   if (as)
12332     {
12333       gcc_assert (as->type != AS_IMPLIED_SHAPE);
12334       if (((as->type == AS_ASSUMED_SIZE && !as->cp_was_assumed)
12335            || as->type == AS_ASSUMED_SHAPE)
12336           && sym->attr.dummy == 0)
12337         {
12338           if (as->type == AS_ASSUMED_SIZE)
12339             gfc_error ("Assumed size array at %L must be a dummy argument",
12340                        &sym->declared_at);
12341           else
12342             gfc_error ("Assumed shape array at %L must be a dummy argument",
12343                        &sym->declared_at);
12344           return;
12345         }
12346     }
12347
12348   /* Make sure symbols with known intent or optional are really dummy
12349      variable.  Because of ENTRY statement, this has to be deferred
12350      until resolution time.  */
12351
12352   if (!sym->attr.dummy
12353       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
12354     {
12355       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
12356       return;
12357     }
12358
12359   if (sym->attr.value && !sym->attr.dummy)
12360     {
12361       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
12362                  "it is not a dummy argument", sym->name, &sym->declared_at);
12363       return;
12364     }
12365
12366   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
12367     {
12368       gfc_charlen *cl = sym->ts.u.cl;
12369       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
12370         {
12371           gfc_error ("Character dummy variable '%s' at %L with VALUE "
12372                      "attribute must have constant length",
12373                      sym->name, &sym->declared_at);
12374           return;
12375         }
12376
12377       if (sym->ts.is_c_interop
12378           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
12379         {
12380           gfc_error ("C interoperable character dummy variable '%s' at %L "
12381                      "with VALUE attribute must have length one",
12382                      sym->name, &sym->declared_at);
12383           return;
12384         }
12385     }
12386
12387   if (sym->ts.type == BT_DERIVED && !sym->attr.is_iso_c
12388       && sym->ts.u.derived->attr.generic)
12389     {
12390       sym->ts.u.derived = gfc_find_dt_in_generic (sym->ts.u.derived);
12391       if (!sym->ts.u.derived)
12392         {
12393           gfc_error ("The derived type '%s' at %L is of type '%s', "
12394                      "which has not been defined", sym->name,
12395                      &sym->declared_at, sym->ts.u.derived->name);
12396           sym->ts.type = BT_UNKNOWN;
12397           return;
12398         }
12399     }
12400
12401   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
12402      do this for something that was implicitly typed because that is handled
12403      in gfc_set_default_type.  Handle dummy arguments and procedure
12404      definitions separately.  Also, anything that is use associated is not
12405      handled here but instead is handled in the module it is declared in.
12406      Finally, derived type definitions are allowed to be BIND(C) since that
12407      only implies that they're interoperable, and they are checked fully for
12408      interoperability when a variable is declared of that type.  */
12409   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
12410       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
12411       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
12412     {
12413       gfc_try t = SUCCESS;
12414       
12415       /* First, make sure the variable is declared at the
12416          module-level scope (J3/04-007, Section 15.3).  */
12417       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
12418           sym->attr.in_common == 0)
12419         {
12420           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
12421                      "is neither a COMMON block nor declared at the "
12422                      "module level scope", sym->name, &(sym->declared_at));
12423           t = FAILURE;
12424         }
12425       else if (sym->common_head != NULL)
12426         {
12427           t = verify_com_block_vars_c_interop (sym->common_head);
12428         }
12429       else
12430         {
12431           /* If type() declaration, we need to verify that the components
12432              of the given type are all C interoperable, etc.  */
12433           if (sym->ts.type == BT_DERIVED &&
12434               sym->ts.u.derived->attr.is_c_interop != 1)
12435             {
12436               /* Make sure the user marked the derived type as BIND(C).  If
12437                  not, call the verify routine.  This could print an error
12438                  for the derived type more than once if multiple variables
12439                  of that type are declared.  */
12440               if (sym->ts.u.derived->attr.is_bind_c != 1)
12441                 verify_bind_c_derived_type (sym->ts.u.derived);
12442               t = FAILURE;
12443             }
12444           
12445           /* Verify the variable itself as C interoperable if it
12446              is BIND(C).  It is not possible for this to succeed if
12447              the verify_bind_c_derived_type failed, so don't have to handle
12448              any error returned by verify_bind_c_derived_type.  */
12449           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
12450                                  sym->common_block);
12451         }
12452
12453       if (t == FAILURE)
12454         {
12455           /* clear the is_bind_c flag to prevent reporting errors more than
12456              once if something failed.  */
12457           sym->attr.is_bind_c = 0;
12458           return;
12459         }
12460     }
12461
12462   /* If a derived type symbol has reached this point, without its
12463      type being declared, we have an error.  Notice that most
12464      conditions that produce undefined derived types have already
12465      been dealt with.  However, the likes of:
12466      implicit type(t) (t) ..... call foo (t) will get us here if
12467      the type is not declared in the scope of the implicit
12468      statement. Change the type to BT_UNKNOWN, both because it is so
12469      and to prevent an ICE.  */
12470   if (sym->ts.type == BT_DERIVED && !sym->attr.is_iso_c
12471       && sym->ts.u.derived->components == NULL
12472       && !sym->ts.u.derived->attr.zero_comp)
12473     {
12474       gfc_error ("The derived type '%s' at %L is of type '%s', "
12475                  "which has not been defined", sym->name,
12476                   &sym->declared_at, sym->ts.u.derived->name);
12477       sym->ts.type = BT_UNKNOWN;
12478       return;
12479     }
12480
12481   /* Make sure that the derived type has been resolved and that the
12482      derived type is visible in the symbol's namespace, if it is a
12483      module function and is not PRIVATE.  */
12484   if (sym->ts.type == BT_DERIVED
12485         && sym->ts.u.derived->attr.use_assoc
12486         && sym->ns->proc_name
12487         && sym->ns->proc_name->attr.flavor == FL_MODULE
12488         && resolve_fl_derived (sym->ts.u.derived) == FAILURE)
12489     return;
12490
12491   /* Unless the derived-type declaration is use associated, Fortran 95
12492      does not allow public entries of private derived types.
12493      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
12494      161 in 95-006r3.  */
12495   if (sym->ts.type == BT_DERIVED
12496       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
12497       && !sym->ts.u.derived->attr.use_assoc
12498       && gfc_check_symbol_access (sym)
12499       && !gfc_check_symbol_access (sym->ts.u.derived)
12500       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
12501                          "of PRIVATE derived type '%s'",
12502                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
12503                          : "variable", sym->name, &sym->declared_at,
12504                          sym->ts.u.derived->name) == FAILURE)
12505     return;
12506
12507   /* F2008, C1302.  */
12508   if (sym->ts.type == BT_DERIVED
12509       && ((sym->ts.u.derived->from_intmod == INTMOD_ISO_FORTRAN_ENV
12510            && sym->ts.u.derived->intmod_sym_id == ISOFORTRAN_LOCK_TYPE)
12511           || sym->ts.u.derived->attr.lock_comp)
12512       && !sym->attr.codimension && !sym->ts.u.derived->attr.coarray_comp)
12513     {
12514       gfc_error ("Variable %s at %L of type LOCK_TYPE or with subcomponent of "
12515                  "type LOCK_TYPE must be a coarray", sym->name,
12516                  &sym->declared_at);
12517       return;
12518     }
12519
12520   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
12521      default initialization is defined (5.1.2.4.4).  */
12522   if (sym->ts.type == BT_DERIVED
12523       && sym->attr.dummy
12524       && sym->attr.intent == INTENT_OUT
12525       && sym->as
12526       && sym->as->type == AS_ASSUMED_SIZE)
12527     {
12528       for (c = sym->ts.u.derived->components; c; c = c->next)
12529         {
12530           if (c->initializer)
12531             {
12532               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
12533                          "ASSUMED SIZE and so cannot have a default initializer",
12534                          sym->name, &sym->declared_at);
12535               return;
12536             }
12537         }
12538     }
12539
12540   /* F2008, C542.  */
12541   if (sym->ts.type == BT_DERIVED && sym->attr.dummy
12542       && sym->attr.intent == INTENT_OUT && sym->attr.lock_comp)
12543     {
12544       gfc_error ("Dummy argument '%s' at %L of LOCK_TYPE shall not be "
12545                  "INTENT(OUT)", sym->name, &sym->declared_at);
12546       return;
12547     }
12548
12549   /* F2008, C525.  */
12550   if ((((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12551          || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12552              && CLASS_DATA (sym)->attr.coarray_comp))
12553        || class_attr.codimension)
12554       && (sym->attr.result || sym->result == sym))
12555     {
12556       gfc_error ("Function result '%s' at %L shall not be a coarray or have "
12557                  "a coarray component", sym->name, &sym->declared_at);
12558       return;
12559     }
12560
12561   /* F2008, C524.  */
12562   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
12563       && sym->ts.u.derived->ts.is_iso_c)
12564     {
12565       gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12566                  "shall not be a coarray", sym->name, &sym->declared_at);
12567       return;
12568     }
12569
12570   /* F2008, C525.  */
12571   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12572         || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12573             && CLASS_DATA (sym)->attr.coarray_comp))
12574       && (class_attr.codimension || class_attr.pointer || class_attr.dimension
12575           || class_attr.allocatable))
12576     {
12577       gfc_error ("Variable '%s' at %L with coarray component "
12578                  "shall be a nonpointer, nonallocatable scalar",
12579                  sym->name, &sym->declared_at);
12580       return;
12581     }
12582
12583   /* F2008, C526.  The function-result case was handled above.  */
12584   if (class_attr.codimension
12585       && !(class_attr.allocatable || sym->attr.dummy || sym->attr.save
12586            || sym->attr.select_type_temporary
12587            || sym->ns->save_all
12588            || sym->ns->proc_name->attr.flavor == FL_MODULE
12589            || sym->ns->proc_name->attr.is_main_program
12590            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
12591     {
12592       gfc_error ("Variable '%s' at %L is a coarray and is not ALLOCATABLE, SAVE "
12593                  "nor a dummy argument", sym->name, &sym->declared_at);
12594       return;
12595     }
12596   /* F2008, C528.  */
12597   else if (class_attr.codimension && !sym->attr.select_type_temporary
12598            && !class_attr.allocatable && as && as->cotype == AS_DEFERRED)
12599     {
12600       gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
12601                  "deferred shape", sym->name, &sym->declared_at);
12602       return;
12603     }
12604   else if (class_attr.codimension && class_attr.allocatable && as
12605            && (as->cotype != AS_DEFERRED || as->type != AS_DEFERRED))
12606     {
12607       gfc_error ("Allocatable coarray variable '%s' at %L must have "
12608                  "deferred shape", sym->name, &sym->declared_at);
12609       return;
12610     }
12611
12612   /* F2008, C541.  */
12613   if ((((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12614         || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12615             && CLASS_DATA (sym)->attr.coarray_comp))
12616        || (class_attr.codimension && class_attr.allocatable))
12617       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
12618     {
12619       gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
12620                  "allocatable coarray or have coarray components",
12621                  sym->name, &sym->declared_at);
12622       return;
12623     }
12624
12625   if (class_attr.codimension && sym->attr.dummy
12626       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
12627     {
12628       gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
12629                  "procedure '%s'", sym->name, &sym->declared_at,
12630                  sym->ns->proc_name->name);
12631       return;
12632     }
12633
12634   switch (sym->attr.flavor)
12635     {
12636     case FL_VARIABLE:
12637       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
12638         return;
12639       break;
12640
12641     case FL_PROCEDURE:
12642       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
12643         return;
12644       break;
12645
12646     case FL_NAMELIST:
12647       if (resolve_fl_namelist (sym) == FAILURE)
12648         return;
12649       break;
12650
12651     case FL_PARAMETER:
12652       if (resolve_fl_parameter (sym) == FAILURE)
12653         return;
12654       break;
12655
12656     default:
12657       break;
12658     }
12659
12660   /* Resolve array specifier. Check as well some constraints
12661      on COMMON blocks.  */
12662
12663   check_constant = sym->attr.in_common && !sym->attr.pointer;
12664
12665   /* Set the formal_arg_flag so that check_conflict will not throw
12666      an error for host associated variables in the specification
12667      expression for an array_valued function.  */
12668   if (sym->attr.function && sym->as)
12669     formal_arg_flag = 1;
12670
12671   gfc_resolve_array_spec (sym->as, check_constant);
12672
12673   formal_arg_flag = 0;
12674
12675   /* Resolve formal namespaces.  */
12676   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
12677       && !sym->attr.contained && !sym->attr.intrinsic)
12678     gfc_resolve (sym->formal_ns);
12679
12680   /* Make sure the formal namespace is present.  */
12681   if (sym->formal && !sym->formal_ns)
12682     {
12683       gfc_formal_arglist *formal = sym->formal;
12684       while (formal && !formal->sym)
12685         formal = formal->next;
12686
12687       if (formal)
12688         {
12689           sym->formal_ns = formal->sym->ns;
12690           sym->formal_ns->refs++;
12691         }
12692     }
12693
12694   /* Check threadprivate restrictions.  */
12695   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
12696       && (!sym->attr.in_common
12697           && sym->module == NULL
12698           && (sym->ns->proc_name == NULL
12699               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
12700     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
12701
12702   /* If we have come this far we can apply default-initializers, as
12703      described in 14.7.5, to those variables that have not already
12704      been assigned one.  */
12705   if (sym->ts.type == BT_DERIVED
12706       && sym->ns == gfc_current_ns
12707       && !sym->value
12708       && !sym->attr.allocatable
12709       && !sym->attr.alloc_comp)
12710     {
12711       symbol_attribute *a = &sym->attr;
12712
12713       if ((!a->save && !a->dummy && !a->pointer
12714            && !a->in_common && !a->use_assoc
12715            && (a->referenced || a->result)
12716            && !(a->function && sym != sym->result))
12717           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
12718         apply_default_init (sym);
12719     }
12720
12721   if (sym->ts.type == BT_CLASS && sym->ns == gfc_current_ns
12722       && sym->attr.dummy && sym->attr.intent == INTENT_OUT
12723       && !CLASS_DATA (sym)->attr.class_pointer
12724       && !CLASS_DATA (sym)->attr.allocatable)
12725     apply_default_init (sym);
12726
12727   /* If this symbol has a type-spec, check it.  */
12728   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
12729       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
12730     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
12731           == FAILURE)
12732       return;
12733 }
12734
12735
12736 /************* Resolve DATA statements *************/
12737
12738 static struct
12739 {
12740   gfc_data_value *vnode;
12741   mpz_t left;
12742 }
12743 values;
12744
12745
12746 /* Advance the values structure to point to the next value in the data list.  */
12747
12748 static gfc_try
12749 next_data_value (void)
12750 {
12751   while (mpz_cmp_ui (values.left, 0) == 0)
12752     {
12753
12754       if (values.vnode->next == NULL)
12755         return FAILURE;
12756
12757       values.vnode = values.vnode->next;
12758       mpz_set (values.left, values.vnode->repeat);
12759     }
12760
12761   return SUCCESS;
12762 }
12763
12764
12765 static gfc_try
12766 check_data_variable (gfc_data_variable *var, locus *where)
12767 {
12768   gfc_expr *e;
12769   mpz_t size;
12770   mpz_t offset;
12771   gfc_try t;
12772   ar_type mark = AR_UNKNOWN;
12773   int i;
12774   mpz_t section_index[GFC_MAX_DIMENSIONS];
12775   gfc_ref *ref;
12776   gfc_array_ref *ar;
12777   gfc_symbol *sym;
12778   int has_pointer;
12779
12780   if (gfc_resolve_expr (var->expr) == FAILURE)
12781     return FAILURE;
12782
12783   ar = NULL;
12784   mpz_init_set_si (offset, 0);
12785   e = var->expr;
12786
12787   if (e->expr_type != EXPR_VARIABLE)
12788     gfc_internal_error ("check_data_variable(): Bad expression");
12789
12790   sym = e->symtree->n.sym;
12791
12792   if (sym->ns->is_block_data && !sym->attr.in_common)
12793     {
12794       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
12795                  sym->name, &sym->declared_at);
12796     }
12797
12798   if (e->ref == NULL && sym->as)
12799     {
12800       gfc_error ("DATA array '%s' at %L must be specified in a previous"
12801                  " declaration", sym->name, where);
12802       return FAILURE;
12803     }
12804
12805   has_pointer = sym->attr.pointer;
12806
12807   if (gfc_is_coindexed (e))
12808     {
12809       gfc_error ("DATA element '%s' at %L cannot have a coindex", sym->name,
12810                  where);
12811       return FAILURE;
12812     }
12813
12814   for (ref = e->ref; ref; ref = ref->next)
12815     {
12816       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
12817         has_pointer = 1;
12818
12819       if (has_pointer
12820             && ref->type == REF_ARRAY
12821             && ref->u.ar.type != AR_FULL)
12822           {
12823             gfc_error ("DATA element '%s' at %L is a pointer and so must "
12824                         "be a full array", sym->name, where);
12825             return FAILURE;
12826           }
12827     }
12828
12829   if (e->rank == 0 || has_pointer)
12830     {
12831       mpz_init_set_ui (size, 1);
12832       ref = NULL;
12833     }
12834   else
12835     {
12836       ref = e->ref;
12837
12838       /* Find the array section reference.  */
12839       for (ref = e->ref; ref; ref = ref->next)
12840         {
12841           if (ref->type != REF_ARRAY)
12842             continue;
12843           if (ref->u.ar.type == AR_ELEMENT)
12844             continue;
12845           break;
12846         }
12847       gcc_assert (ref);
12848
12849       /* Set marks according to the reference pattern.  */
12850       switch (ref->u.ar.type)
12851         {
12852         case AR_FULL:
12853           mark = AR_FULL;
12854           break;
12855
12856         case AR_SECTION:
12857           ar = &ref->u.ar;
12858           /* Get the start position of array section.  */
12859           gfc_get_section_index (ar, section_index, &offset);
12860           mark = AR_SECTION;
12861           break;
12862
12863         default:
12864           gcc_unreachable ();
12865         }
12866
12867       if (gfc_array_size (e, &size) == FAILURE)
12868         {
12869           gfc_error ("Nonconstant array section at %L in DATA statement",
12870                      &e->where);
12871           mpz_clear (offset);
12872           return FAILURE;
12873         }
12874     }
12875
12876   t = SUCCESS;
12877
12878   while (mpz_cmp_ui (size, 0) > 0)
12879     {
12880       if (next_data_value () == FAILURE)
12881         {
12882           gfc_error ("DATA statement at %L has more variables than values",
12883                      where);
12884           t = FAILURE;
12885           break;
12886         }
12887
12888       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
12889       if (t == FAILURE)
12890         break;
12891
12892       /* If we have more than one element left in the repeat count,
12893          and we have more than one element left in the target variable,
12894          then create a range assignment.  */
12895       /* FIXME: Only done for full arrays for now, since array sections
12896          seem tricky.  */
12897       if (mark == AR_FULL && ref && ref->next == NULL
12898           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
12899         {
12900           mpz_t range;
12901
12902           if (mpz_cmp (size, values.left) >= 0)
12903             {
12904               mpz_init_set (range, values.left);
12905               mpz_sub (size, size, values.left);
12906               mpz_set_ui (values.left, 0);
12907             }
12908           else
12909             {
12910               mpz_init_set (range, size);
12911               mpz_sub (values.left, values.left, size);
12912               mpz_set_ui (size, 0);
12913             }
12914
12915           t = gfc_assign_data_value (var->expr, values.vnode->expr,
12916                                      offset, &range);
12917
12918           mpz_add (offset, offset, range);
12919           mpz_clear (range);
12920
12921           if (t == FAILURE)
12922             break;
12923         }
12924
12925       /* Assign initial value to symbol.  */
12926       else
12927         {
12928           mpz_sub_ui (values.left, values.left, 1);
12929           mpz_sub_ui (size, size, 1);
12930
12931           t = gfc_assign_data_value (var->expr, values.vnode->expr,
12932                                      offset, NULL);
12933           if (t == FAILURE)
12934             break;
12935
12936           if (mark == AR_FULL)
12937             mpz_add_ui (offset, offset, 1);
12938
12939           /* Modify the array section indexes and recalculate the offset
12940              for next element.  */
12941           else if (mark == AR_SECTION)
12942             gfc_advance_section (section_index, ar, &offset);
12943         }
12944     }
12945
12946   if (mark == AR_SECTION)
12947     {
12948       for (i = 0; i < ar->dimen; i++)
12949         mpz_clear (section_index[i]);
12950     }
12951
12952   mpz_clear (size);
12953   mpz_clear (offset);
12954
12955   return t;
12956 }
12957
12958
12959 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
12960
12961 /* Iterate over a list of elements in a DATA statement.  */
12962
12963 static gfc_try
12964 traverse_data_list (gfc_data_variable *var, locus *where)
12965 {
12966   mpz_t trip;
12967   iterator_stack frame;
12968   gfc_expr *e, *start, *end, *step;
12969   gfc_try retval = SUCCESS;
12970
12971   mpz_init (frame.value);
12972   mpz_init (trip);
12973
12974   start = gfc_copy_expr (var->iter.start);
12975   end = gfc_copy_expr (var->iter.end);
12976   step = gfc_copy_expr (var->iter.step);
12977
12978   if (gfc_simplify_expr (start, 1) == FAILURE
12979       || start->expr_type != EXPR_CONSTANT)
12980     {
12981       gfc_error ("start of implied-do loop at %L could not be "
12982                  "simplified to a constant value", &start->where);
12983       retval = FAILURE;
12984       goto cleanup;
12985     }
12986   if (gfc_simplify_expr (end, 1) == FAILURE
12987       || end->expr_type != EXPR_CONSTANT)
12988     {
12989       gfc_error ("end of implied-do loop at %L could not be "
12990                  "simplified to a constant value", &start->where);
12991       retval = FAILURE;
12992       goto cleanup;
12993     }
12994   if (gfc_simplify_expr (step, 1) == FAILURE
12995       || step->expr_type != EXPR_CONSTANT)
12996     {
12997       gfc_error ("step of implied-do loop at %L could not be "
12998                  "simplified to a constant value", &start->where);
12999       retval = FAILURE;
13000       goto cleanup;
13001     }
13002
13003   mpz_set (trip, end->value.integer);
13004   mpz_sub (trip, trip, start->value.integer);
13005   mpz_add (trip, trip, step->value.integer);
13006
13007   mpz_div (trip, trip, step->value.integer);
13008
13009   mpz_set (frame.value, start->value.integer);
13010
13011   frame.prev = iter_stack;
13012   frame.variable = var->iter.var->symtree;
13013   iter_stack = &frame;
13014
13015   while (mpz_cmp_ui (trip, 0) > 0)
13016     {
13017       if (traverse_data_var (var->list, where) == FAILURE)
13018         {
13019           retval = FAILURE;
13020           goto cleanup;
13021         }
13022
13023       e = gfc_copy_expr (var->expr);
13024       if (gfc_simplify_expr (e, 1) == FAILURE)
13025         {
13026           gfc_free_expr (e);
13027           retval = FAILURE;
13028           goto cleanup;
13029         }
13030
13031       mpz_add (frame.value, frame.value, step->value.integer);
13032
13033       mpz_sub_ui (trip, trip, 1);
13034     }
13035
13036 cleanup:
13037   mpz_clear (frame.value);
13038   mpz_clear (trip);
13039
13040   gfc_free_expr (start);
13041   gfc_free_expr (end);
13042   gfc_free_expr (step);
13043
13044   iter_stack = frame.prev;
13045   return retval;
13046 }
13047
13048
13049 /* Type resolve variables in the variable list of a DATA statement.  */
13050
13051 static gfc_try
13052 traverse_data_var (gfc_data_variable *var, locus *where)
13053 {
13054   gfc_try t;
13055
13056   for (; var; var = var->next)
13057     {
13058       if (var->expr == NULL)
13059         t = traverse_data_list (var, where);
13060       else
13061         t = check_data_variable (var, where);
13062
13063       if (t == FAILURE)
13064         return FAILURE;
13065     }
13066
13067   return SUCCESS;
13068 }
13069
13070
13071 /* Resolve the expressions and iterators associated with a data statement.
13072    This is separate from the assignment checking because data lists should
13073    only be resolved once.  */
13074
13075 static gfc_try
13076 resolve_data_variables (gfc_data_variable *d)
13077 {
13078   for (; d; d = d->next)
13079     {
13080       if (d->list == NULL)
13081         {
13082           if (gfc_resolve_expr (d->expr) == FAILURE)
13083             return FAILURE;
13084         }
13085       else
13086         {
13087           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
13088             return FAILURE;
13089
13090           if (resolve_data_variables (d->list) == FAILURE)
13091             return FAILURE;
13092         }
13093     }
13094
13095   return SUCCESS;
13096 }
13097
13098
13099 /* Resolve a single DATA statement.  We implement this by storing a pointer to
13100    the value list into static variables, and then recursively traversing the
13101    variables list, expanding iterators and such.  */
13102
13103 static void
13104 resolve_data (gfc_data *d)
13105 {
13106
13107   if (resolve_data_variables (d->var) == FAILURE)
13108     return;
13109
13110   values.vnode = d->value;
13111   if (d->value == NULL)
13112     mpz_set_ui (values.left, 0);
13113   else
13114     mpz_set (values.left, d->value->repeat);
13115
13116   if (traverse_data_var (d->var, &d->where) == FAILURE)
13117     return;
13118
13119   /* At this point, we better not have any values left.  */
13120
13121   if (next_data_value () == SUCCESS)
13122     gfc_error ("DATA statement at %L has more values than variables",
13123                &d->where);
13124 }
13125
13126
13127 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
13128    accessed by host or use association, is a dummy argument to a pure function,
13129    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
13130    is storage associated with any such variable, shall not be used in the
13131    following contexts: (clients of this function).  */
13132
13133 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
13134    procedure.  Returns zero if assignment is OK, nonzero if there is a
13135    problem.  */
13136 int
13137 gfc_impure_variable (gfc_symbol *sym)
13138 {
13139   gfc_symbol *proc;
13140   gfc_namespace *ns;
13141
13142   if (sym->attr.use_assoc || sym->attr.in_common)
13143     return 1;
13144
13145   /* Check if the symbol's ns is inside the pure procedure.  */
13146   for (ns = gfc_current_ns; ns; ns = ns->parent)
13147     {
13148       if (ns == sym->ns)
13149         break;
13150       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
13151         return 1;
13152     }
13153
13154   proc = sym->ns->proc_name;
13155   if (sym->attr.dummy && gfc_pure (proc)
13156         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
13157                 ||
13158              proc->attr.function))
13159     return 1;
13160
13161   /* TODO: Sort out what can be storage associated, if anything, and include
13162      it here.  In principle equivalences should be scanned but it does not
13163      seem to be possible to storage associate an impure variable this way.  */
13164   return 0;
13165 }
13166
13167
13168 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
13169    current namespace is inside a pure procedure.  */
13170
13171 int
13172 gfc_pure (gfc_symbol *sym)
13173 {
13174   symbol_attribute attr;
13175   gfc_namespace *ns;
13176
13177   if (sym == NULL)
13178     {
13179       /* Check if the current namespace or one of its parents
13180         belongs to a pure procedure.  */
13181       for (ns = gfc_current_ns; ns; ns = ns->parent)
13182         {
13183           sym = ns->proc_name;
13184           if (sym == NULL)
13185             return 0;
13186           attr = sym->attr;
13187           if (attr.flavor == FL_PROCEDURE && attr.pure)
13188             return 1;
13189         }
13190       return 0;
13191     }
13192
13193   attr = sym->attr;
13194
13195   return attr.flavor == FL_PROCEDURE && attr.pure;
13196 }
13197
13198
13199 /* Test whether a symbol is implicitly pure or not.  For a NULL pointer,
13200    checks if the current namespace is implicitly pure.  Note that this
13201    function returns false for a PURE procedure.  */
13202
13203 int
13204 gfc_implicit_pure (gfc_symbol *sym)
13205 {
13206   gfc_namespace *ns;
13207
13208   if (sym == NULL)
13209     {
13210       /* Check if the current procedure is implicit_pure.  Walk up
13211          the procedure list until we find a procedure.  */
13212       for (ns = gfc_current_ns; ns; ns = ns->parent)
13213         {
13214           sym = ns->proc_name;
13215           if (sym == NULL)
13216             return 0;
13217           
13218           if (sym->attr.flavor == FL_PROCEDURE)
13219             break;
13220         }
13221     }
13222   
13223   return sym->attr.flavor == FL_PROCEDURE && sym->attr.implicit_pure
13224     && !sym->attr.pure;
13225 }
13226
13227
13228 /* Test whether the current procedure is elemental or not.  */
13229
13230 int
13231 gfc_elemental (gfc_symbol *sym)
13232 {
13233   symbol_attribute attr;
13234
13235   if (sym == NULL)
13236     sym = gfc_current_ns->proc_name;
13237   if (sym == NULL)
13238     return 0;
13239   attr = sym->attr;
13240
13241   return attr.flavor == FL_PROCEDURE && attr.elemental;
13242 }
13243
13244
13245 /* Warn about unused labels.  */
13246
13247 static void
13248 warn_unused_fortran_label (gfc_st_label *label)
13249 {
13250   if (label == NULL)
13251     return;
13252
13253   warn_unused_fortran_label (label->left);
13254
13255   if (label->defined == ST_LABEL_UNKNOWN)
13256     return;
13257
13258   switch (label->referenced)
13259     {
13260     case ST_LABEL_UNKNOWN:
13261       gfc_warning ("Label %d at %L defined but not used", label->value,
13262                    &label->where);
13263       break;
13264
13265     case ST_LABEL_BAD_TARGET:
13266       gfc_warning ("Label %d at %L defined but cannot be used",
13267                    label->value, &label->where);
13268       break;
13269
13270     default:
13271       break;
13272     }
13273
13274   warn_unused_fortran_label (label->right);
13275 }
13276
13277
13278 /* Returns the sequence type of a symbol or sequence.  */
13279
13280 static seq_type
13281 sequence_type (gfc_typespec ts)
13282 {
13283   seq_type result;
13284   gfc_component *c;
13285
13286   switch (ts.type)
13287   {
13288     case BT_DERIVED:
13289
13290       if (ts.u.derived->components == NULL)
13291         return SEQ_NONDEFAULT;
13292
13293       result = sequence_type (ts.u.derived->components->ts);
13294       for (c = ts.u.derived->components->next; c; c = c->next)
13295         if (sequence_type (c->ts) != result)
13296           return SEQ_MIXED;
13297
13298       return result;
13299
13300     case BT_CHARACTER:
13301       if (ts.kind != gfc_default_character_kind)
13302           return SEQ_NONDEFAULT;
13303
13304       return SEQ_CHARACTER;
13305
13306     case BT_INTEGER:
13307       if (ts.kind != gfc_default_integer_kind)
13308           return SEQ_NONDEFAULT;
13309
13310       return SEQ_NUMERIC;
13311
13312     case BT_REAL:
13313       if (!(ts.kind == gfc_default_real_kind
13314             || ts.kind == gfc_default_double_kind))
13315           return SEQ_NONDEFAULT;
13316
13317       return SEQ_NUMERIC;
13318
13319     case BT_COMPLEX:
13320       if (ts.kind != gfc_default_complex_kind)
13321           return SEQ_NONDEFAULT;
13322
13323       return SEQ_NUMERIC;
13324
13325     case BT_LOGICAL:
13326       if (ts.kind != gfc_default_logical_kind)
13327           return SEQ_NONDEFAULT;
13328
13329       return SEQ_NUMERIC;
13330
13331     default:
13332       return SEQ_NONDEFAULT;
13333   }
13334 }
13335
13336
13337 /* Resolve derived type EQUIVALENCE object.  */
13338
13339 static gfc_try
13340 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
13341 {
13342   gfc_component *c = derived->components;
13343
13344   if (!derived)
13345     return SUCCESS;
13346
13347   /* Shall not be an object of nonsequence derived type.  */
13348   if (!derived->attr.sequence)
13349     {
13350       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
13351                  "attribute to be an EQUIVALENCE object", sym->name,
13352                  &e->where);
13353       return FAILURE;
13354     }
13355
13356   /* Shall not have allocatable components.  */
13357   if (derived->attr.alloc_comp)
13358     {
13359       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
13360                  "components to be an EQUIVALENCE object",sym->name,
13361                  &e->where);
13362       return FAILURE;
13363     }
13364
13365   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
13366     {
13367       gfc_error ("Derived type variable '%s' at %L with default "
13368                  "initialization cannot be in EQUIVALENCE with a variable "
13369                  "in COMMON", sym->name, &e->where);
13370       return FAILURE;
13371     }
13372
13373   for (; c ; c = c->next)
13374     {
13375       if (c->ts.type == BT_DERIVED
13376           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
13377         return FAILURE;
13378
13379       /* Shall not be an object of sequence derived type containing a pointer
13380          in the structure.  */
13381       if (c->attr.pointer)
13382         {
13383           gfc_error ("Derived type variable '%s' at %L with pointer "
13384                      "component(s) cannot be an EQUIVALENCE object",
13385                      sym->name, &e->where);
13386           return FAILURE;
13387         }
13388     }
13389   return SUCCESS;
13390 }
13391
13392
13393 /* Resolve equivalence object. 
13394    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
13395    an allocatable array, an object of nonsequence derived type, an object of
13396    sequence derived type containing a pointer at any level of component
13397    selection, an automatic object, a function name, an entry name, a result
13398    name, a named constant, a structure component, or a subobject of any of
13399    the preceding objects.  A substring shall not have length zero.  A
13400    derived type shall not have components with default initialization nor
13401    shall two objects of an equivalence group be initialized.
13402    Either all or none of the objects shall have an protected attribute.
13403    The simple constraints are done in symbol.c(check_conflict) and the rest
13404    are implemented here.  */
13405
13406 static void
13407 resolve_equivalence (gfc_equiv *eq)
13408 {
13409   gfc_symbol *sym;
13410   gfc_symbol *first_sym;
13411   gfc_expr *e;
13412   gfc_ref *r;
13413   locus *last_where = NULL;
13414   seq_type eq_type, last_eq_type;
13415   gfc_typespec *last_ts;
13416   int object, cnt_protected;
13417   const char *msg;
13418
13419   last_ts = &eq->expr->symtree->n.sym->ts;
13420
13421   first_sym = eq->expr->symtree->n.sym;
13422
13423   cnt_protected = 0;
13424
13425   for (object = 1; eq; eq = eq->eq, object++)
13426     {
13427       e = eq->expr;
13428
13429       e->ts = e->symtree->n.sym->ts;
13430       /* match_varspec might not know yet if it is seeing
13431          array reference or substring reference, as it doesn't
13432          know the types.  */
13433       if (e->ref && e->ref->type == REF_ARRAY)
13434         {
13435           gfc_ref *ref = e->ref;
13436           sym = e->symtree->n.sym;
13437
13438           if (sym->attr.dimension)
13439             {
13440               ref->u.ar.as = sym->as;
13441               ref = ref->next;
13442             }
13443
13444           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
13445           if (e->ts.type == BT_CHARACTER
13446               && ref
13447               && ref->type == REF_ARRAY
13448               && ref->u.ar.dimen == 1
13449               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
13450               && ref->u.ar.stride[0] == NULL)
13451             {
13452               gfc_expr *start = ref->u.ar.start[0];
13453               gfc_expr *end = ref->u.ar.end[0];
13454               void *mem = NULL;
13455
13456               /* Optimize away the (:) reference.  */
13457               if (start == NULL && end == NULL)
13458                 {
13459                   if (e->ref == ref)
13460                     e->ref = ref->next;
13461                   else
13462                     e->ref->next = ref->next;
13463                   mem = ref;
13464                 }
13465               else
13466                 {
13467                   ref->type = REF_SUBSTRING;
13468                   if (start == NULL)
13469                     start = gfc_get_int_expr (gfc_default_integer_kind,
13470                                               NULL, 1);
13471                   ref->u.ss.start = start;
13472                   if (end == NULL && e->ts.u.cl)
13473                     end = gfc_copy_expr (e->ts.u.cl->length);
13474                   ref->u.ss.end = end;
13475                   ref->u.ss.length = e->ts.u.cl;
13476                   e->ts.u.cl = NULL;
13477                 }
13478               ref = ref->next;
13479               free (mem);
13480             }
13481
13482           /* Any further ref is an error.  */
13483           if (ref)
13484             {
13485               gcc_assert (ref->type == REF_ARRAY);
13486               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
13487                          &ref->u.ar.where);
13488               continue;
13489             }
13490         }
13491
13492       if (gfc_resolve_expr (e) == FAILURE)
13493         continue;
13494
13495       sym = e->symtree->n.sym;
13496
13497       if (sym->attr.is_protected)
13498         cnt_protected++;
13499       if (cnt_protected > 0 && cnt_protected != object)
13500         {
13501               gfc_error ("Either all or none of the objects in the "
13502                          "EQUIVALENCE set at %L shall have the "
13503                          "PROTECTED attribute",
13504                          &e->where);
13505               break;
13506         }
13507
13508       /* Shall not equivalence common block variables in a PURE procedure.  */
13509       if (sym->ns->proc_name
13510           && sym->ns->proc_name->attr.pure
13511           && sym->attr.in_common)
13512         {
13513           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
13514                      "object in the pure procedure '%s'",
13515                      sym->name, &e->where, sym->ns->proc_name->name);
13516           break;
13517         }
13518
13519       /* Shall not be a named constant.  */
13520       if (e->expr_type == EXPR_CONSTANT)
13521         {
13522           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
13523                      "object", sym->name, &e->where);
13524           continue;
13525         }
13526
13527       if (e->ts.type == BT_DERIVED
13528           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
13529         continue;
13530
13531       /* Check that the types correspond correctly:
13532          Note 5.28:
13533          A numeric sequence structure may be equivalenced to another sequence
13534          structure, an object of default integer type, default real type, double
13535          precision real type, default logical type such that components of the
13536          structure ultimately only become associated to objects of the same
13537          kind. A character sequence structure may be equivalenced to an object
13538          of default character kind or another character sequence structure.
13539          Other objects may be equivalenced only to objects of the same type and
13540          kind parameters.  */
13541
13542       /* Identical types are unconditionally OK.  */
13543       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
13544         goto identical_types;
13545
13546       last_eq_type = sequence_type (*last_ts);
13547       eq_type = sequence_type (sym->ts);
13548
13549       /* Since the pair of objects is not of the same type, mixed or
13550          non-default sequences can be rejected.  */
13551
13552       msg = "Sequence %s with mixed components in EQUIVALENCE "
13553             "statement at %L with different type objects";
13554       if ((object ==2
13555            && last_eq_type == SEQ_MIXED
13556            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
13557               == FAILURE)
13558           || (eq_type == SEQ_MIXED
13559               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13560                                  &e->where) == FAILURE))
13561         continue;
13562
13563       msg = "Non-default type object or sequence %s in EQUIVALENCE "
13564             "statement at %L with objects of different type";
13565       if ((object ==2
13566            && last_eq_type == SEQ_NONDEFAULT
13567            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
13568                               last_where) == FAILURE)
13569           || (eq_type == SEQ_NONDEFAULT
13570               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13571                                  &e->where) == FAILURE))
13572         continue;
13573
13574       msg ="Non-CHARACTER object '%s' in default CHARACTER "
13575            "EQUIVALENCE statement at %L";
13576       if (last_eq_type == SEQ_CHARACTER
13577           && eq_type != SEQ_CHARACTER
13578           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13579                              &e->where) == FAILURE)
13580                 continue;
13581
13582       msg ="Non-NUMERIC object '%s' in default NUMERIC "
13583            "EQUIVALENCE statement at %L";
13584       if (last_eq_type == SEQ_NUMERIC
13585           && eq_type != SEQ_NUMERIC
13586           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13587                              &e->where) == FAILURE)
13588                 continue;
13589
13590   identical_types:
13591       last_ts =&sym->ts;
13592       last_where = &e->where;
13593
13594       if (!e->ref)
13595         continue;
13596
13597       /* Shall not be an automatic array.  */
13598       if (e->ref->type == REF_ARRAY
13599           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
13600         {
13601           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
13602                      "an EQUIVALENCE object", sym->name, &e->where);
13603           continue;
13604         }
13605
13606       r = e->ref;
13607       while (r)
13608         {
13609           /* Shall not be a structure component.  */
13610           if (r->type == REF_COMPONENT)
13611             {
13612               gfc_error ("Structure component '%s' at %L cannot be an "
13613                          "EQUIVALENCE object",
13614                          r->u.c.component->name, &e->where);
13615               break;
13616             }
13617
13618           /* A substring shall not have length zero.  */
13619           if (r->type == REF_SUBSTRING)
13620             {
13621               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
13622                 {
13623                   gfc_error ("Substring at %L has length zero",
13624                              &r->u.ss.start->where);
13625                   break;
13626                 }
13627             }
13628           r = r->next;
13629         }
13630     }
13631 }
13632
13633
13634 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
13635
13636 static void
13637 resolve_fntype (gfc_namespace *ns)
13638 {
13639   gfc_entry_list *el;
13640   gfc_symbol *sym;
13641
13642   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
13643     return;
13644
13645   /* If there are any entries, ns->proc_name is the entry master
13646      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
13647   if (ns->entries)
13648     sym = ns->entries->sym;
13649   else
13650     sym = ns->proc_name;
13651   if (sym->result == sym
13652       && sym->ts.type == BT_UNKNOWN
13653       && gfc_set_default_type (sym, 0, NULL) == FAILURE
13654       && !sym->attr.untyped)
13655     {
13656       gfc_error ("Function '%s' at %L has no IMPLICIT type",
13657                  sym->name, &sym->declared_at);
13658       sym->attr.untyped = 1;
13659     }
13660
13661   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
13662       && !sym->attr.contained
13663       && !gfc_check_symbol_access (sym->ts.u.derived)
13664       && gfc_check_symbol_access (sym))
13665     {
13666       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
13667                       "%L of PRIVATE type '%s'", sym->name,
13668                       &sym->declared_at, sym->ts.u.derived->name);
13669     }
13670
13671     if (ns->entries)
13672     for (el = ns->entries->next; el; el = el->next)
13673       {
13674         if (el->sym->result == el->sym
13675             && el->sym->ts.type == BT_UNKNOWN
13676             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
13677             && !el->sym->attr.untyped)
13678           {
13679             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
13680                        el->sym->name, &el->sym->declared_at);
13681             el->sym->attr.untyped = 1;
13682           }
13683       }
13684 }
13685
13686
13687 /* 12.3.2.1.1 Defined operators.  */
13688
13689 static gfc_try
13690 check_uop_procedure (gfc_symbol *sym, locus where)
13691 {
13692   gfc_formal_arglist *formal;
13693
13694   if (!sym->attr.function)
13695     {
13696       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
13697                  sym->name, &where);
13698       return FAILURE;
13699     }
13700
13701   if (sym->ts.type == BT_CHARACTER
13702       && !(sym->ts.u.cl && sym->ts.u.cl->length)
13703       && !(sym->result && sym->result->ts.u.cl
13704            && sym->result->ts.u.cl->length))
13705     {
13706       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
13707                  "character length", sym->name, &where);
13708       return FAILURE;
13709     }
13710
13711   formal = sym->formal;
13712   if (!formal || !formal->sym)
13713     {
13714       gfc_error ("User operator procedure '%s' at %L must have at least "
13715                  "one argument", sym->name, &where);
13716       return FAILURE;
13717     }
13718
13719   if (formal->sym->attr.intent != INTENT_IN)
13720     {
13721       gfc_error ("First argument of operator interface at %L must be "
13722                  "INTENT(IN)", &where);
13723       return FAILURE;
13724     }
13725
13726   if (formal->sym->attr.optional)
13727     {
13728       gfc_error ("First argument of operator interface at %L cannot be "
13729                  "optional", &where);
13730       return FAILURE;
13731     }
13732
13733   formal = formal->next;
13734   if (!formal || !formal->sym)
13735     return SUCCESS;
13736
13737   if (formal->sym->attr.intent != INTENT_IN)
13738     {
13739       gfc_error ("Second argument of operator interface at %L must be "
13740                  "INTENT(IN)", &where);
13741       return FAILURE;
13742     }
13743
13744   if (formal->sym->attr.optional)
13745     {
13746       gfc_error ("Second argument of operator interface at %L cannot be "
13747                  "optional", &where);
13748       return FAILURE;
13749     }
13750
13751   if (formal->next)
13752     {
13753       gfc_error ("Operator interface at %L must have, at most, two "
13754                  "arguments", &where);
13755       return FAILURE;
13756     }
13757
13758   return SUCCESS;
13759 }
13760
13761 static void
13762 gfc_resolve_uops (gfc_symtree *symtree)
13763 {
13764   gfc_interface *itr;
13765
13766   if (symtree == NULL)
13767     return;
13768
13769   gfc_resolve_uops (symtree->left);
13770   gfc_resolve_uops (symtree->right);
13771
13772   for (itr = symtree->n.uop->op; itr; itr = itr->next)
13773     check_uop_procedure (itr->sym, itr->sym->declared_at);
13774 }
13775
13776
13777 /* Examine all of the expressions associated with a program unit,
13778    assign types to all intermediate expressions, make sure that all
13779    assignments are to compatible types and figure out which names
13780    refer to which functions or subroutines.  It doesn't check code
13781    block, which is handled by resolve_code.  */
13782
13783 static void
13784 resolve_types (gfc_namespace *ns)
13785 {
13786   gfc_namespace *n;
13787   gfc_charlen *cl;
13788   gfc_data *d;
13789   gfc_equiv *eq;
13790   gfc_namespace* old_ns = gfc_current_ns;
13791
13792   /* Check that all IMPLICIT types are ok.  */
13793   if (!ns->seen_implicit_none)
13794     {
13795       unsigned letter;
13796       for (letter = 0; letter != GFC_LETTERS; ++letter)
13797         if (ns->set_flag[letter]
13798             && resolve_typespec_used (&ns->default_type[letter],
13799                                       &ns->implicit_loc[letter],
13800                                       NULL) == FAILURE)
13801           return;
13802     }
13803
13804   gfc_current_ns = ns;
13805
13806   resolve_entries (ns);
13807
13808   resolve_common_vars (ns->blank_common.head, false);
13809   resolve_common_blocks (ns->common_root);
13810
13811   resolve_contained_functions (ns);
13812
13813   if (ns->proc_name && ns->proc_name->attr.flavor == FL_PROCEDURE
13814       && ns->proc_name->attr.if_source == IFSRC_IFBODY)
13815     resolve_formal_arglist (ns->proc_name);
13816
13817   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
13818
13819   for (cl = ns->cl_list; cl; cl = cl->next)
13820     resolve_charlen (cl);
13821
13822   gfc_traverse_ns (ns, resolve_symbol);
13823
13824   resolve_fntype (ns);
13825
13826   for (n = ns->contained; n; n = n->sibling)
13827     {
13828       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
13829         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
13830                    "also be PURE", n->proc_name->name,
13831                    &n->proc_name->declared_at);
13832
13833       resolve_types (n);
13834     }
13835
13836   forall_flag = 0;
13837   do_concurrent_flag = 0;
13838   gfc_check_interfaces (ns);
13839
13840   gfc_traverse_ns (ns, resolve_values);
13841
13842   if (ns->save_all)
13843     gfc_save_all (ns);
13844
13845   iter_stack = NULL;
13846   for (d = ns->data; d; d = d->next)
13847     resolve_data (d);
13848
13849   iter_stack = NULL;
13850   gfc_traverse_ns (ns, gfc_formalize_init_value);
13851
13852   gfc_traverse_ns (ns, gfc_verify_binding_labels);
13853
13854   if (ns->common_root != NULL)
13855     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
13856
13857   for (eq = ns->equiv; eq; eq = eq->next)
13858     resolve_equivalence (eq);
13859
13860   /* Warn about unused labels.  */
13861   if (warn_unused_label)
13862     warn_unused_fortran_label (ns->st_labels);
13863
13864   gfc_resolve_uops (ns->uop_root);
13865
13866   gfc_current_ns = old_ns;
13867 }
13868
13869
13870 /* Call resolve_code recursively.  */
13871
13872 static void
13873 resolve_codes (gfc_namespace *ns)
13874 {
13875   gfc_namespace *n;
13876   bitmap_obstack old_obstack;
13877
13878   if (ns->resolved == 1)
13879     return;
13880
13881   for (n = ns->contained; n; n = n->sibling)
13882     resolve_codes (n);
13883
13884   gfc_current_ns = ns;
13885
13886   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
13887   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
13888     cs_base = NULL;
13889
13890   /* Set to an out of range value.  */
13891   current_entry_id = -1;
13892
13893   old_obstack = labels_obstack;
13894   bitmap_obstack_initialize (&labels_obstack);
13895
13896   resolve_code (ns->code, ns);
13897
13898   bitmap_obstack_release (&labels_obstack);
13899   labels_obstack = old_obstack;
13900 }
13901
13902
13903 /* This function is called after a complete program unit has been compiled.
13904    Its purpose is to examine all of the expressions associated with a program
13905    unit, assign types to all intermediate expressions, make sure that all
13906    assignments are to compatible types and figure out which names refer to
13907    which functions or subroutines.  */
13908
13909 void
13910 gfc_resolve (gfc_namespace *ns)
13911 {
13912   gfc_namespace *old_ns;
13913   code_stack *old_cs_base;
13914
13915   if (ns->resolved)
13916     return;
13917
13918   ns->resolved = -1;
13919   old_ns = gfc_current_ns;
13920   old_cs_base = cs_base;
13921
13922   resolve_types (ns);
13923   resolve_codes (ns);
13924
13925   gfc_current_ns = old_ns;
13926   cs_base = old_cs_base;
13927   ns->resolved = 1;
13928
13929   gfc_run_passes (ns);
13930 }