OSDN Git Service

2011-11-07 Janus Weil <janus@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009,
3    2010, 2011
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     return;
459
460   resolve_formal_arglist (sym);
461 }
462
463
464 /* Given a namespace, resolve all formal argument lists within the namespace.
465  */
466
467 static void
468 resolve_formal_arglists (gfc_namespace *ns)
469 {
470   if (ns == NULL)
471     return;
472
473   gfc_traverse_ns (ns, find_arglists);
474 }
475
476
477 static void
478 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
479 {
480   gfc_try t;
481
482   /* If this namespace is not a function or an entry master function,
483      ignore it.  */
484   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
485       || sym->attr.entry_master)
486     return;
487
488   /* Try to find out of what the return type is.  */
489   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
490     {
491       t = gfc_set_default_type (sym->result, 0, ns);
492
493       if (t == FAILURE && !sym->result->attr.untyped)
494         {
495           if (sym->result == sym)
496             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
497                        sym->name, &sym->declared_at);
498           else if (!sym->result->attr.proc_pointer)
499             gfc_error ("Result '%s' of contained function '%s' at %L has "
500                        "no IMPLICIT type", sym->result->name, sym->name,
501                        &sym->result->declared_at);
502           sym->result->attr.untyped = 1;
503         }
504     }
505
506   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
507      type, lists the only ways a character length value of * can be used:
508      dummy arguments of procedures, named constants, and function results
509      in external functions.  Internal function results and results of module
510      procedures are not on this list, ergo, not permitted.  */
511
512   if (sym->result->ts.type == BT_CHARACTER)
513     {
514       gfc_charlen *cl = sym->result->ts.u.cl;
515       if ((!cl || !cl->length) && !sym->result->ts.deferred)
516         {
517           /* See if this is a module-procedure and adapt error message
518              accordingly.  */
519           bool module_proc;
520           gcc_assert (ns->parent && ns->parent->proc_name);
521           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
522
523           gfc_error ("Character-valued %s '%s' at %L must not be"
524                      " assumed length",
525                      module_proc ? _("module procedure")
526                                  : _("internal function"),
527                      sym->name, &sym->declared_at);
528         }
529     }
530 }
531
532
533 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
534    introduce duplicates.  */
535
536 static void
537 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
538 {
539   gfc_formal_arglist *f, *new_arglist;
540   gfc_symbol *new_sym;
541
542   for (; new_args != NULL; new_args = new_args->next)
543     {
544       new_sym = new_args->sym;
545       /* See if this arg is already in the formal argument list.  */
546       for (f = proc->formal; f; f = f->next)
547         {
548           if (new_sym == f->sym)
549             break;
550         }
551
552       if (f)
553         continue;
554
555       /* Add a new argument.  Argument order is not important.  */
556       new_arglist = gfc_get_formal_arglist ();
557       new_arglist->sym = new_sym;
558       new_arglist->next = proc->formal;
559       proc->formal  = new_arglist;
560     }
561 }
562
563
564 /* Flag the arguments that are not present in all entries.  */
565
566 static void
567 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
568 {
569   gfc_formal_arglist *f, *head;
570   head = new_args;
571
572   for (f = proc->formal; f; f = f->next)
573     {
574       if (f->sym == NULL)
575         continue;
576
577       for (new_args = head; new_args; new_args = new_args->next)
578         {
579           if (new_args->sym == f->sym)
580             break;
581         }
582
583       if (new_args)
584         continue;
585
586       f->sym->attr.not_always_present = 1;
587     }
588 }
589
590
591 /* Resolve alternate entry points.  If a symbol has multiple entry points we
592    create a new master symbol for the main routine, and turn the existing
593    symbol into an entry point.  */
594
595 static void
596 resolve_entries (gfc_namespace *ns)
597 {
598   gfc_namespace *old_ns;
599   gfc_code *c;
600   gfc_symbol *proc;
601   gfc_entry_list *el;
602   char name[GFC_MAX_SYMBOL_LEN + 1];
603   static int master_count = 0;
604
605   if (ns->proc_name == NULL)
606     return;
607
608   /* No need to do anything if this procedure doesn't have alternate entry
609      points.  */
610   if (!ns->entries)
611     return;
612
613   /* We may already have resolved alternate entry points.  */
614   if (ns->proc_name->attr.entry_master)
615     return;
616
617   /* If this isn't a procedure something has gone horribly wrong.  */
618   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
619
620   /* Remember the current namespace.  */
621   old_ns = gfc_current_ns;
622
623   gfc_current_ns = ns;
624
625   /* Add the main entry point to the list of entry points.  */
626   el = gfc_get_entry_list ();
627   el->sym = ns->proc_name;
628   el->id = 0;
629   el->next = ns->entries;
630   ns->entries = el;
631   ns->proc_name->attr.entry = 1;
632
633   /* If it is a module function, it needs to be in the right namespace
634      so that gfc_get_fake_result_decl can gather up the results. The
635      need for this arose in get_proc_name, where these beasts were
636      left in their own namespace, to keep prior references linked to
637      the entry declaration.*/
638   if (ns->proc_name->attr.function
639       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
640     el->sym->ns = ns;
641
642   /* Do the same for entries where the master is not a module
643      procedure.  These are retained in the module namespace because
644      of the module procedure declaration.  */
645   for (el = el->next; el; el = el->next)
646     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
647           && el->sym->attr.mod_proc)
648       el->sym->ns = ns;
649   el = ns->entries;
650
651   /* Add an entry statement for it.  */
652   c = gfc_get_code ();
653   c->op = EXEC_ENTRY;
654   c->ext.entry = el;
655   c->next = ns->code;
656   ns->code = c;
657
658   /* Create a new symbol for the master function.  */
659   /* Give the internal function a unique name (within this file).
660      Also include the function name so the user has some hope of figuring
661      out what is going on.  */
662   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
663             master_count++, ns->proc_name->name);
664   gfc_get_ha_symbol (name, &proc);
665   gcc_assert (proc != NULL);
666
667   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
668   if (ns->proc_name->attr.subroutine)
669     gfc_add_subroutine (&proc->attr, proc->name, NULL);
670   else
671     {
672       gfc_symbol *sym;
673       gfc_typespec *ts, *fts;
674       gfc_array_spec *as, *fas;
675       gfc_add_function (&proc->attr, proc->name, NULL);
676       proc->result = proc;
677       fas = ns->entries->sym->as;
678       fas = fas ? fas : ns->entries->sym->result->as;
679       fts = &ns->entries->sym->result->ts;
680       if (fts->type == BT_UNKNOWN)
681         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
682       for (el = ns->entries->next; el; el = el->next)
683         {
684           ts = &el->sym->result->ts;
685           as = el->sym->as;
686           as = as ? as : el->sym->result->as;
687           if (ts->type == BT_UNKNOWN)
688             ts = gfc_get_default_type (el->sym->result->name, NULL);
689
690           if (! gfc_compare_types (ts, fts)
691               || (el->sym->result->attr.dimension
692                   != ns->entries->sym->result->attr.dimension)
693               || (el->sym->result->attr.pointer
694                   != ns->entries->sym->result->attr.pointer))
695             break;
696           else if (as && fas && ns->entries->sym->result != el->sym->result
697                       && gfc_compare_array_spec (as, fas) == 0)
698             gfc_error ("Function %s at %L has entries with mismatched "
699                        "array specifications", ns->entries->sym->name,
700                        &ns->entries->sym->declared_at);
701           /* The characteristics need to match and thus both need to have
702              the same string length, i.e. both len=*, or both len=4.
703              Having both len=<variable> is also possible, but difficult to
704              check at compile time.  */
705           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
706                    && (((ts->u.cl->length && !fts->u.cl->length)
707                         ||(!ts->u.cl->length && fts->u.cl->length))
708                        || (ts->u.cl->length
709                            && ts->u.cl->length->expr_type
710                               != fts->u.cl->length->expr_type)
711                        || (ts->u.cl->length
712                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
713                            && mpz_cmp (ts->u.cl->length->value.integer,
714                                        fts->u.cl->length->value.integer) != 0)))
715             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
716                             "entries returning variables of different "
717                             "string lengths", ns->entries->sym->name,
718                             &ns->entries->sym->declared_at);
719         }
720
721       if (el == NULL)
722         {
723           sym = ns->entries->sym->result;
724           /* All result types the same.  */
725           proc->ts = *fts;
726           if (sym->attr.dimension)
727             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
728           if (sym->attr.pointer)
729             gfc_add_pointer (&proc->attr, NULL);
730         }
731       else
732         {
733           /* Otherwise the result will be passed through a union by
734              reference.  */
735           proc->attr.mixed_entry_master = 1;
736           for (el = ns->entries; el; el = el->next)
737             {
738               sym = el->sym->result;
739               if (sym->attr.dimension)
740                 {
741                   if (el == ns->entries)
742                     gfc_error ("FUNCTION result %s can't be an array in "
743                                "FUNCTION %s at %L", sym->name,
744                                ns->entries->sym->name, &sym->declared_at);
745                   else
746                     gfc_error ("ENTRY result %s can't be an array in "
747                                "FUNCTION %s at %L", sym->name,
748                                ns->entries->sym->name, &sym->declared_at);
749                 }
750               else if (sym->attr.pointer)
751                 {
752                   if (el == ns->entries)
753                     gfc_error ("FUNCTION result %s can't be a POINTER in "
754                                "FUNCTION %s at %L", sym->name,
755                                ns->entries->sym->name, &sym->declared_at);
756                   else
757                     gfc_error ("ENTRY result %s can't be a POINTER in "
758                                "FUNCTION %s at %L", sym->name,
759                                ns->entries->sym->name, &sym->declared_at);
760                 }
761               else
762                 {
763                   ts = &sym->ts;
764                   if (ts->type == BT_UNKNOWN)
765                     ts = gfc_get_default_type (sym->name, NULL);
766                   switch (ts->type)
767                     {
768                     case BT_INTEGER:
769                       if (ts->kind == gfc_default_integer_kind)
770                         sym = NULL;
771                       break;
772                     case BT_REAL:
773                       if (ts->kind == gfc_default_real_kind
774                           || ts->kind == gfc_default_double_kind)
775                         sym = NULL;
776                       break;
777                     case BT_COMPLEX:
778                       if (ts->kind == gfc_default_complex_kind)
779                         sym = NULL;
780                       break;
781                     case BT_LOGICAL:
782                       if (ts->kind == gfc_default_logical_kind)
783                         sym = NULL;
784                       break;
785                     case BT_UNKNOWN:
786                       /* We will issue error elsewhere.  */
787                       sym = NULL;
788                       break;
789                     default:
790                       break;
791                     }
792                   if (sym)
793                     {
794                       if (el == ns->entries)
795                         gfc_error ("FUNCTION result %s can't be of type %s "
796                                    "in FUNCTION %s at %L", sym->name,
797                                    gfc_typename (ts), ns->entries->sym->name,
798                                    &sym->declared_at);
799                       else
800                         gfc_error ("ENTRY result %s can't be of type %s "
801                                    "in FUNCTION %s at %L", sym->name,
802                                    gfc_typename (ts), ns->entries->sym->name,
803                                    &sym->declared_at);
804                     }
805                 }
806             }
807         }
808     }
809   proc->attr.access = ACCESS_PRIVATE;
810   proc->attr.entry_master = 1;
811
812   /* Merge all the entry point arguments.  */
813   for (el = ns->entries; el; el = el->next)
814     merge_argument_lists (proc, el->sym->formal);
815
816   /* Check the master formal arguments for any that are not
817      present in all entry points.  */
818   for (el = ns->entries; el; el = el->next)
819     check_argument_lists (proc, el->sym->formal);
820
821   /* Use the master function for the function body.  */
822   ns->proc_name = proc;
823
824   /* Finalize the new symbols.  */
825   gfc_commit_symbols ();
826
827   /* Restore the original namespace.  */
828   gfc_current_ns = old_ns;
829 }
830
831
832 /* Resolve common variables.  */
833 static void
834 resolve_common_vars (gfc_symbol *sym, bool named_common)
835 {
836   gfc_symbol *csym = sym;
837
838   for (; csym; csym = csym->common_next)
839     {
840       if (csym->value || csym->attr.data)
841         {
842           if (!csym->ns->is_block_data)
843             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
844                             "but only in BLOCK DATA initialization is "
845                             "allowed", csym->name, &csym->declared_at);
846           else if (!named_common)
847             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
848                             "in a blank COMMON but initialization is only "
849                             "allowed in named common blocks", csym->name,
850                             &csym->declared_at);
851         }
852
853       if (csym->ts.type != BT_DERIVED)
854         continue;
855
856       if (!(csym->ts.u.derived->attr.sequence
857             || csym->ts.u.derived->attr.is_bind_c))
858         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
859                        "has neither the SEQUENCE nor the BIND(C) "
860                        "attribute", csym->name, &csym->declared_at);
861       if (csym->ts.u.derived->attr.alloc_comp)
862         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
863                        "has an ultimate component that is "
864                        "allocatable", csym->name, &csym->declared_at);
865       if (gfc_has_default_initializer (csym->ts.u.derived))
866         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
867                        "may not have default initializer", csym->name,
868                        &csym->declared_at);
869
870       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
871         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
872     }
873 }
874
875 /* Resolve common blocks.  */
876 static void
877 resolve_common_blocks (gfc_symtree *common_root)
878 {
879   gfc_symbol *sym;
880
881   if (common_root == NULL)
882     return;
883
884   if (common_root->left)
885     resolve_common_blocks (common_root->left);
886   if (common_root->right)
887     resolve_common_blocks (common_root->right);
888
889   resolve_common_vars (common_root->n.common->head, true);
890
891   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
892   if (sym == NULL)
893     return;
894
895   if (sym->attr.flavor == FL_PARAMETER)
896     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
897                sym->name, &common_root->n.common->where, &sym->declared_at);
898
899   if (sym->attr.external)
900     gfc_error ("COMMON block '%s' at %L can not have the EXTERNAL attribute",
901                sym->name, &common_root->n.common->where);
902
903   if (sym->attr.intrinsic)
904     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
905                sym->name, &common_root->n.common->where);
906   else if (sym->attr.result
907            || gfc_is_function_return_value (sym, gfc_current_ns))
908     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
909                     "that is also a function result", sym->name,
910                     &common_root->n.common->where);
911   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
912            && sym->attr.proc != PROC_ST_FUNCTION)
913     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
914                     "that is also a global procedure", sym->name,
915                     &common_root->n.common->where);
916 }
917
918
919 /* Resolve contained function types.  Because contained functions can call one
920    another, they have to be worked out before any of the contained procedures
921    can be resolved.
922
923    The good news is that if a function doesn't already have a type, the only
924    way it can get one is through an IMPLICIT type or a RESULT variable, because
925    by definition contained functions are contained namespace they're contained
926    in, not in a sibling or parent namespace.  */
927
928 static void
929 resolve_contained_functions (gfc_namespace *ns)
930 {
931   gfc_namespace *child;
932   gfc_entry_list *el;
933
934   resolve_formal_arglists (ns);
935
936   for (child = ns->contained; child; child = child->sibling)
937     {
938       /* Resolve alternate entry points first.  */
939       resolve_entries (child);
940
941       /* Then check function return types.  */
942       resolve_contained_fntype (child->proc_name, child);
943       for (el = child->entries; el; el = el->next)
944         resolve_contained_fntype (el->sym, child);
945     }
946 }
947
948
949 static gfc_try resolve_fl_derived0 (gfc_symbol *sym);
950
951
952 /* Resolve all of the elements of a structure constructor and make sure that
953    the types are correct. The 'init' flag indicates that the given
954    constructor is an initializer.  */
955
956 static gfc_try
957 resolve_structure_cons (gfc_expr *expr, int init)
958 {
959   gfc_constructor *cons;
960   gfc_component *comp;
961   gfc_try t;
962   symbol_attribute a;
963
964   t = SUCCESS;
965
966   if (expr->ts.type == BT_DERIVED)
967     resolve_fl_derived0 (expr->ts.u.derived);
968
969   cons = gfc_constructor_first (expr->value.constructor);
970   /* A constructor may have references if it is the result of substituting a
971      parameter variable.  In this case we just pull out the component we
972      want.  */
973   if (expr->ref)
974     comp = expr->ref->u.c.sym->components;
975   else
976     comp = expr->ts.u.derived->components;
977
978   /* See if the user is trying to invoke a structure constructor for one of
979      the iso_c_binding derived types.  */
980   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
981       && expr->ts.u.derived->ts.is_iso_c && cons
982       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
983     {
984       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
985                  expr->ts.u.derived->name, &(expr->where));
986       return FAILURE;
987     }
988
989   /* Return if structure constructor is c_null_(fun)prt.  */
990   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
991       && expr->ts.u.derived->ts.is_iso_c && cons
992       && cons->expr && cons->expr->expr_type == EXPR_NULL)
993     return SUCCESS;
994
995   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
996     {
997       int rank;
998
999       if (!cons->expr)
1000         continue;
1001
1002       if (gfc_resolve_expr (cons->expr) == FAILURE)
1003         {
1004           t = FAILURE;
1005           continue;
1006         }
1007
1008       rank = comp->as ? comp->as->rank : 0;
1009       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
1010           && (comp->attr.allocatable || cons->expr->rank))
1011         {
1012           gfc_error ("The rank of the element in the structure "
1013                      "constructor at %L does not match that of the "
1014                      "component (%d/%d)", &cons->expr->where,
1015                      cons->expr->rank, rank);
1016           t = FAILURE;
1017         }
1018
1019       /* If we don't have the right type, try to convert it.  */
1020
1021       if (!comp->attr.proc_pointer &&
1022           !gfc_compare_types (&cons->expr->ts, &comp->ts))
1023         {
1024           t = FAILURE;
1025           if (strcmp (comp->name, "_extends") == 0)
1026             {
1027               /* Can afford to be brutal with the _extends initializer.
1028                  The derived type can get lost because it is PRIVATE
1029                  but it is not usage constrained by the standard.  */
1030               cons->expr->ts = comp->ts;
1031               t = SUCCESS;
1032             }
1033           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
1034             gfc_error ("The element in the structure constructor at %L, "
1035                        "for pointer component '%s', is %s but should be %s",
1036                        &cons->expr->where, comp->name,
1037                        gfc_basic_typename (cons->expr->ts.type),
1038                        gfc_basic_typename (comp->ts.type));
1039           else
1040             t = gfc_convert_type (cons->expr, &comp->ts, 1);
1041         }
1042
1043       /* For strings, the length of the constructor should be the same as
1044          the one of the structure, ensure this if the lengths are known at
1045          compile time and when we are dealing with PARAMETER or structure
1046          constructors.  */
1047       if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1048           && comp->ts.u.cl->length
1049           && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1050           && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1051           && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1052           && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1053                       comp->ts.u.cl->length->value.integer) != 0)
1054         {
1055           if (cons->expr->expr_type == EXPR_VARIABLE
1056               && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1057             {
1058               /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1059                  to make use of the gfc_resolve_character_array_constructor
1060                  machinery.  The expression is later simplified away to
1061                  an array of string literals.  */
1062               gfc_expr *para = cons->expr;
1063               cons->expr = gfc_get_expr ();
1064               cons->expr->ts = para->ts;
1065               cons->expr->where = para->where;
1066               cons->expr->expr_type = EXPR_ARRAY;
1067               cons->expr->rank = para->rank;
1068               cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1069               gfc_constructor_append_expr (&cons->expr->value.constructor,
1070                                            para, &cons->expr->where);
1071             }
1072           if (cons->expr->expr_type == EXPR_ARRAY)
1073             {
1074               gfc_constructor *p;
1075               p = gfc_constructor_first (cons->expr->value.constructor);
1076               if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1077                 {
1078                   gfc_charlen *cl, *cl2;
1079
1080                   cl2 = NULL;
1081                   for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1082                     {
1083                       if (cl == cons->expr->ts.u.cl)
1084                         break;
1085                       cl2 = cl;
1086                     }
1087
1088                   gcc_assert (cl);
1089
1090                   if (cl2)
1091                     cl2->next = cl->next;
1092
1093                   gfc_free_expr (cl->length);
1094                   free (cl);
1095                 }
1096
1097               cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1098               cons->expr->ts.u.cl->length_from_typespec = true;
1099               cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1100               gfc_resolve_character_array_constructor (cons->expr);
1101             }
1102         }
1103
1104       if (cons->expr->expr_type == EXPR_NULL
1105           && !(comp->attr.pointer || comp->attr.allocatable
1106                || comp->attr.proc_pointer
1107                || (comp->ts.type == BT_CLASS
1108                    && (CLASS_DATA (comp)->attr.class_pointer
1109                        || CLASS_DATA (comp)->attr.allocatable))))
1110         {
1111           t = FAILURE;
1112           gfc_error ("The NULL in the structure constructor at %L is "
1113                      "being applied to component '%s', which is neither "
1114                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
1115                      comp->name);
1116         }
1117
1118       if (comp->attr.proc_pointer && comp->ts.interface)
1119         {
1120           /* Check procedure pointer interface.  */
1121           gfc_symbol *s2 = NULL;
1122           gfc_component *c2;
1123           const char *name;
1124           char err[200];
1125
1126           if (gfc_is_proc_ptr_comp (cons->expr, &c2))
1127             {
1128               s2 = c2->ts.interface;
1129               name = c2->name;
1130             }
1131           else if (cons->expr->expr_type == EXPR_FUNCTION)
1132             {
1133               s2 = cons->expr->symtree->n.sym->result;
1134               name = cons->expr->symtree->n.sym->result->name;
1135             }
1136           else if (cons->expr->expr_type != EXPR_NULL)
1137             {
1138               s2 = cons->expr->symtree->n.sym;
1139               name = cons->expr->symtree->n.sym->name;
1140             }
1141
1142           if (s2 && !gfc_compare_interfaces (comp->ts.interface, s2, name, 0, 1,
1143                                              err, sizeof (err)))
1144             {
1145               gfc_error ("Interface mismatch for procedure-pointer component "
1146                          "'%s' in structure constructor at %L: %s",
1147                          comp->name, &cons->expr->where, err);
1148               return FAILURE;
1149             }
1150         }
1151
1152       if (!comp->attr.pointer || comp->attr.proc_pointer
1153           || cons->expr->expr_type == EXPR_NULL)
1154         continue;
1155
1156       a = gfc_expr_attr (cons->expr);
1157
1158       if (!a.pointer && !a.target)
1159         {
1160           t = FAILURE;
1161           gfc_error ("The element in the structure constructor at %L, "
1162                      "for pointer component '%s' should be a POINTER or "
1163                      "a TARGET", &cons->expr->where, comp->name);
1164         }
1165
1166       if (init)
1167         {
1168           /* F08:C461. Additional checks for pointer initialization.  */
1169           if (a.allocatable)
1170             {
1171               t = FAILURE;
1172               gfc_error ("Pointer initialization target at %L "
1173                          "must not be ALLOCATABLE ", &cons->expr->where);
1174             }
1175           if (!a.save)
1176             {
1177               t = FAILURE;
1178               gfc_error ("Pointer initialization target at %L "
1179                          "must have the SAVE attribute", &cons->expr->where);
1180             }
1181         }
1182
1183       /* F2003, C1272 (3).  */
1184       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
1185           && (gfc_impure_variable (cons->expr->symtree->n.sym)
1186               || gfc_is_coindexed (cons->expr)))
1187         {
1188           t = FAILURE;
1189           gfc_error ("Invalid expression in the structure constructor for "
1190                      "pointer component '%s' at %L in PURE procedure",
1191                      comp->name, &cons->expr->where);
1192         }
1193
1194       if (gfc_implicit_pure (NULL)
1195             && cons->expr->expr_type == EXPR_VARIABLE
1196             && (gfc_impure_variable (cons->expr->symtree->n.sym)
1197                 || gfc_is_coindexed (cons->expr)))
1198         gfc_current_ns->proc_name->attr.implicit_pure = 0;
1199
1200     }
1201
1202   return t;
1203 }
1204
1205
1206 /****************** Expression name resolution ******************/
1207
1208 /* Returns 0 if a symbol was not declared with a type or
1209    attribute declaration statement, nonzero otherwise.  */
1210
1211 static int
1212 was_declared (gfc_symbol *sym)
1213 {
1214   symbol_attribute a;
1215
1216   a = sym->attr;
1217
1218   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1219     return 1;
1220
1221   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1222       || a.optional || a.pointer || a.save || a.target || a.volatile_
1223       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1224       || a.asynchronous || a.codimension)
1225     return 1;
1226
1227   return 0;
1228 }
1229
1230
1231 /* Determine if a symbol is generic or not.  */
1232
1233 static int
1234 generic_sym (gfc_symbol *sym)
1235 {
1236   gfc_symbol *s;
1237
1238   if (sym->attr.generic ||
1239       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1240     return 1;
1241
1242   if (was_declared (sym) || sym->ns->parent == NULL)
1243     return 0;
1244
1245   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1246   
1247   if (s != NULL)
1248     {
1249       if (s == sym)
1250         return 0;
1251       else
1252         return generic_sym (s);
1253     }
1254
1255   return 0;
1256 }
1257
1258
1259 /* Determine if a symbol is specific or not.  */
1260
1261 static int
1262 specific_sym (gfc_symbol *sym)
1263 {
1264   gfc_symbol *s;
1265
1266   if (sym->attr.if_source == IFSRC_IFBODY
1267       || sym->attr.proc == PROC_MODULE
1268       || sym->attr.proc == PROC_INTERNAL
1269       || sym->attr.proc == PROC_ST_FUNCTION
1270       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1271       || sym->attr.external)
1272     return 1;
1273
1274   if (was_declared (sym) || sym->ns->parent == NULL)
1275     return 0;
1276
1277   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1278
1279   return (s == NULL) ? 0 : specific_sym (s);
1280 }
1281
1282
1283 /* Figure out if the procedure is specific, generic or unknown.  */
1284
1285 typedef enum
1286 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1287 proc_type;
1288
1289 static proc_type
1290 procedure_kind (gfc_symbol *sym)
1291 {
1292   if (generic_sym (sym))
1293     return PTYPE_GENERIC;
1294
1295   if (specific_sym (sym))
1296     return PTYPE_SPECIFIC;
1297
1298   return PTYPE_UNKNOWN;
1299 }
1300
1301 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1302    is nonzero when matching actual arguments.  */
1303
1304 static int need_full_assumed_size = 0;
1305
1306 static bool
1307 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1308 {
1309   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1310       return false;
1311
1312   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1313      What should it be?  */
1314   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1315           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1316                && (e->ref->u.ar.type == AR_FULL))
1317     {
1318       gfc_error ("The upper bound in the last dimension must "
1319                  "appear in the reference to the assumed size "
1320                  "array '%s' at %L", sym->name, &e->where);
1321       return true;
1322     }
1323   return false;
1324 }
1325
1326
1327 /* Look for bad assumed size array references in argument expressions
1328   of elemental and array valued intrinsic procedures.  Since this is
1329   called from procedure resolution functions, it only recurses at
1330   operators.  */
1331
1332 static bool
1333 resolve_assumed_size_actual (gfc_expr *e)
1334 {
1335   if (e == NULL)
1336    return false;
1337
1338   switch (e->expr_type)
1339     {
1340     case EXPR_VARIABLE:
1341       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1342         return true;
1343       break;
1344
1345     case EXPR_OP:
1346       if (resolve_assumed_size_actual (e->value.op.op1)
1347           || resolve_assumed_size_actual (e->value.op.op2))
1348         return true;
1349       break;
1350
1351     default:
1352       break;
1353     }
1354   return false;
1355 }
1356
1357
1358 /* Check a generic procedure, passed as an actual argument, to see if
1359    there is a matching specific name.  If none, it is an error, and if
1360    more than one, the reference is ambiguous.  */
1361 static int
1362 count_specific_procs (gfc_expr *e)
1363 {
1364   int n;
1365   gfc_interface *p;
1366   gfc_symbol *sym;
1367         
1368   n = 0;
1369   sym = e->symtree->n.sym;
1370
1371   for (p = sym->generic; p; p = p->next)
1372     if (strcmp (sym->name, p->sym->name) == 0)
1373       {
1374         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1375                                        sym->name);
1376         n++;
1377       }
1378
1379   if (n > 1)
1380     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1381                &e->where);
1382
1383   if (n == 0)
1384     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1385                "argument at %L", sym->name, &e->where);
1386
1387   return n;
1388 }
1389
1390
1391 /* See if a call to sym could possibly be a not allowed RECURSION because of
1392    a missing RECURIVE declaration.  This means that either sym is the current
1393    context itself, or sym is the parent of a contained procedure calling its
1394    non-RECURSIVE containing procedure.
1395    This also works if sym is an ENTRY.  */
1396
1397 static bool
1398 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1399 {
1400   gfc_symbol* proc_sym;
1401   gfc_symbol* context_proc;
1402   gfc_namespace* real_context;
1403
1404   if (sym->attr.flavor == FL_PROGRAM)
1405     return false;
1406
1407   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1408
1409   /* If we've got an ENTRY, find real procedure.  */
1410   if (sym->attr.entry && sym->ns->entries)
1411     proc_sym = sym->ns->entries->sym;
1412   else
1413     proc_sym = sym;
1414
1415   /* If sym is RECURSIVE, all is well of course.  */
1416   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1417     return false;
1418
1419   /* Find the context procedure's "real" symbol if it has entries.
1420      We look for a procedure symbol, so recurse on the parents if we don't
1421      find one (like in case of a BLOCK construct).  */
1422   for (real_context = context; ; real_context = real_context->parent)
1423     {
1424       /* We should find something, eventually!  */
1425       gcc_assert (real_context);
1426
1427       context_proc = (real_context->entries ? real_context->entries->sym
1428                                             : real_context->proc_name);
1429
1430       /* In some special cases, there may not be a proc_name, like for this
1431          invalid code:
1432          real(bad_kind()) function foo () ...
1433          when checking the call to bad_kind ().
1434          In these cases, we simply return here and assume that the
1435          call is ok.  */
1436       if (!context_proc)
1437         return false;
1438
1439       if (context_proc->attr.flavor != FL_LABEL)
1440         break;
1441     }
1442
1443   /* A call from sym's body to itself is recursion, of course.  */
1444   if (context_proc == proc_sym)
1445     return true;
1446
1447   /* The same is true if context is a contained procedure and sym the
1448      containing one.  */
1449   if (context_proc->attr.contained)
1450     {
1451       gfc_symbol* parent_proc;
1452
1453       gcc_assert (context->parent);
1454       parent_proc = (context->parent->entries ? context->parent->entries->sym
1455                                               : context->parent->proc_name);
1456
1457       if (parent_proc == proc_sym)
1458         return true;
1459     }
1460
1461   return false;
1462 }
1463
1464
1465 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1466    its typespec and formal argument list.  */
1467
1468 static gfc_try
1469 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1470 {
1471   gfc_intrinsic_sym* isym = NULL;
1472   const char* symstd;
1473
1474   if (sym->formal)
1475     return SUCCESS;
1476
1477   /* Already resolved.  */
1478   if (sym->from_intmod && sym->ts.type != BT_UNKNOWN)
1479     return SUCCESS;
1480
1481   /* We already know this one is an intrinsic, so we don't call
1482      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1483      gfc_find_subroutine directly to check whether it is a function or
1484      subroutine.  */
1485
1486   if (sym->intmod_sym_id)
1487     isym = gfc_intrinsic_function_by_id ((gfc_isym_id) sym->intmod_sym_id);
1488   else
1489     isym = gfc_find_function (sym->name);
1490
1491   if (isym)
1492     {
1493       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1494           && !sym->attr.implicit_type)
1495         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1496                       " ignored", sym->name, &sym->declared_at);
1497
1498       if (!sym->attr.function &&
1499           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1500         return FAILURE;
1501
1502       sym->ts = isym->ts;
1503     }
1504   else if ((isym = gfc_find_subroutine (sym->name)))
1505     {
1506       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1507         {
1508           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1509                       " specifier", sym->name, &sym->declared_at);
1510           return FAILURE;
1511         }
1512
1513       if (!sym->attr.subroutine &&
1514           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1515         return FAILURE;
1516     }
1517   else
1518     {
1519       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1520                  &sym->declared_at);
1521       return FAILURE;
1522     }
1523
1524   gfc_copy_formal_args_intr (sym, isym);
1525
1526   /* Check it is actually available in the standard settings.  */
1527   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1528       == FAILURE)
1529     {
1530       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1531                  " available in the current standard settings but %s.  Use"
1532                  " an appropriate -std=* option or enable -fall-intrinsics"
1533                  " in order to use it.",
1534                  sym->name, &sym->declared_at, symstd);
1535       return FAILURE;
1536     }
1537
1538   return SUCCESS;
1539 }
1540
1541
1542 /* Resolve a procedure expression, like passing it to a called procedure or as
1543    RHS for a procedure pointer assignment.  */
1544
1545 static gfc_try
1546 resolve_procedure_expression (gfc_expr* expr)
1547 {
1548   gfc_symbol* sym;
1549
1550   if (expr->expr_type != EXPR_VARIABLE)
1551     return SUCCESS;
1552   gcc_assert (expr->symtree);
1553
1554   sym = expr->symtree->n.sym;
1555
1556   if (sym->attr.intrinsic)
1557     resolve_intrinsic (sym, &expr->where);
1558
1559   if (sym->attr.flavor != FL_PROCEDURE
1560       || (sym->attr.function && sym->result == sym))
1561     return SUCCESS;
1562
1563   /* A non-RECURSIVE procedure that is used as procedure expression within its
1564      own body is in danger of being called recursively.  */
1565   if (is_illegal_recursion (sym, gfc_current_ns))
1566     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1567                  " itself recursively.  Declare it RECURSIVE or use"
1568                  " -frecursive", sym->name, &expr->where);
1569   
1570   return SUCCESS;
1571 }
1572
1573
1574 /* Resolve an actual argument list.  Most of the time, this is just
1575    resolving the expressions in the list.
1576    The exception is that we sometimes have to decide whether arguments
1577    that look like procedure arguments are really simple variable
1578    references.  */
1579
1580 static gfc_try
1581 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1582                         bool no_formal_args)
1583 {
1584   gfc_symbol *sym;
1585   gfc_symtree *parent_st;
1586   gfc_expr *e;
1587   int save_need_full_assumed_size;
1588
1589   for (; arg; arg = arg->next)
1590     {
1591       e = arg->expr;
1592       if (e == NULL)
1593         {
1594           /* Check the label is a valid branching target.  */
1595           if (arg->label)
1596             {
1597               if (arg->label->defined == ST_LABEL_UNKNOWN)
1598                 {
1599                   gfc_error ("Label %d referenced at %L is never defined",
1600                              arg->label->value, &arg->label->where);
1601                   return FAILURE;
1602                 }
1603             }
1604           continue;
1605         }
1606
1607       if (e->expr_type == EXPR_VARIABLE
1608             && e->symtree->n.sym->attr.generic
1609             && no_formal_args
1610             && count_specific_procs (e) != 1)
1611         return FAILURE;
1612
1613       if (e->ts.type != BT_PROCEDURE)
1614         {
1615           save_need_full_assumed_size = need_full_assumed_size;
1616           if (e->expr_type != EXPR_VARIABLE)
1617             need_full_assumed_size = 0;
1618           if (gfc_resolve_expr (e) != SUCCESS)
1619             return FAILURE;
1620           need_full_assumed_size = save_need_full_assumed_size;
1621           goto argument_list;
1622         }
1623
1624       /* See if the expression node should really be a variable reference.  */
1625
1626       sym = e->symtree->n.sym;
1627
1628       if (sym->attr.flavor == FL_PROCEDURE
1629           || sym->attr.intrinsic
1630           || sym->attr.external)
1631         {
1632           int actual_ok;
1633
1634           /* If a procedure is not already determined to be something else
1635              check if it is intrinsic.  */
1636           if (!sym->attr.intrinsic
1637               && !(sym->attr.external || sym->attr.use_assoc
1638                    || sym->attr.if_source == IFSRC_IFBODY)
1639               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1640             sym->attr.intrinsic = 1;
1641
1642           if (sym->attr.proc == PROC_ST_FUNCTION)
1643             {
1644               gfc_error ("Statement function '%s' at %L is not allowed as an "
1645                          "actual argument", sym->name, &e->where);
1646             }
1647
1648           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1649                                                sym->attr.subroutine);
1650           if (sym->attr.intrinsic && actual_ok == 0)
1651             {
1652               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1653                          "actual argument", sym->name, &e->where);
1654             }
1655
1656           if (sym->attr.contained && !sym->attr.use_assoc
1657               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1658             {
1659               if (gfc_notify_std (GFC_STD_F2008,
1660                                   "Fortran 2008: Internal procedure '%s' is"
1661                                   " used as actual argument at %L",
1662                                   sym->name, &e->where) == FAILURE)
1663                 return FAILURE;
1664             }
1665
1666           if (sym->attr.elemental && !sym->attr.intrinsic)
1667             {
1668               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1669                          "allowed as an actual argument at %L", sym->name,
1670                          &e->where);
1671             }
1672
1673           /* Check if a generic interface has a specific procedure
1674             with the same name before emitting an error.  */
1675           if (sym->attr.generic && count_specific_procs (e) != 1)
1676             return FAILURE;
1677           
1678           /* Just in case a specific was found for the expression.  */
1679           sym = e->symtree->n.sym;
1680
1681           /* If the symbol is the function that names the current (or
1682              parent) scope, then we really have a variable reference.  */
1683
1684           if (gfc_is_function_return_value (sym, sym->ns))
1685             goto got_variable;
1686
1687           /* If all else fails, see if we have a specific intrinsic.  */
1688           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1689             {
1690               gfc_intrinsic_sym *isym;
1691
1692               isym = gfc_find_function (sym->name);
1693               if (isym == NULL || !isym->specific)
1694                 {
1695                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1696                              "for the reference '%s' at %L", sym->name,
1697                              &e->where);
1698                   return FAILURE;
1699                 }
1700               sym->ts = isym->ts;
1701               sym->attr.intrinsic = 1;
1702               sym->attr.function = 1;
1703             }
1704
1705           if (gfc_resolve_expr (e) == FAILURE)
1706             return FAILURE;
1707           goto argument_list;
1708         }
1709
1710       /* See if the name is a module procedure in a parent unit.  */
1711
1712       if (was_declared (sym) || sym->ns->parent == NULL)
1713         goto got_variable;
1714
1715       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1716         {
1717           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1718           return FAILURE;
1719         }
1720
1721       if (parent_st == NULL)
1722         goto got_variable;
1723
1724       sym = parent_st->n.sym;
1725       e->symtree = parent_st;           /* Point to the right thing.  */
1726
1727       if (sym->attr.flavor == FL_PROCEDURE
1728           || sym->attr.intrinsic
1729           || sym->attr.external)
1730         {
1731           if (gfc_resolve_expr (e) == FAILURE)
1732             return FAILURE;
1733           goto argument_list;
1734         }
1735
1736     got_variable:
1737       e->expr_type = EXPR_VARIABLE;
1738       e->ts = sym->ts;
1739       if (sym->as != NULL)
1740         {
1741           e->rank = sym->as->rank;
1742           e->ref = gfc_get_ref ();
1743           e->ref->type = REF_ARRAY;
1744           e->ref->u.ar.type = AR_FULL;
1745           e->ref->u.ar.as = sym->as;
1746         }
1747
1748       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1749          primary.c (match_actual_arg). If above code determines that it
1750          is a  variable instead, it needs to be resolved as it was not
1751          done at the beginning of this function.  */
1752       save_need_full_assumed_size = need_full_assumed_size;
1753       if (e->expr_type != EXPR_VARIABLE)
1754         need_full_assumed_size = 0;
1755       if (gfc_resolve_expr (e) != SUCCESS)
1756         return FAILURE;
1757       need_full_assumed_size = save_need_full_assumed_size;
1758
1759     argument_list:
1760       /* Check argument list functions %VAL, %LOC and %REF.  There is
1761          nothing to do for %REF.  */
1762       if (arg->name && arg->name[0] == '%')
1763         {
1764           if (strncmp ("%VAL", arg->name, 4) == 0)
1765             {
1766               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1767                 {
1768                   gfc_error ("By-value argument at %L is not of numeric "
1769                              "type", &e->where);
1770                   return FAILURE;
1771                 }
1772
1773               if (e->rank)
1774                 {
1775                   gfc_error ("By-value argument at %L cannot be an array or "
1776                              "an array section", &e->where);
1777                 return FAILURE;
1778                 }
1779
1780               /* Intrinsics are still PROC_UNKNOWN here.  However,
1781                  since same file external procedures are not resolvable
1782                  in gfortran, it is a good deal easier to leave them to
1783                  intrinsic.c.  */
1784               if (ptype != PROC_UNKNOWN
1785                   && ptype != PROC_DUMMY
1786                   && ptype != PROC_EXTERNAL
1787                   && ptype != PROC_MODULE)
1788                 {
1789                   gfc_error ("By-value argument at %L is not allowed "
1790                              "in this context", &e->where);
1791                   return FAILURE;
1792                 }
1793             }
1794
1795           /* Statement functions have already been excluded above.  */
1796           else if (strncmp ("%LOC", arg->name, 4) == 0
1797                    && e->ts.type == BT_PROCEDURE)
1798             {
1799               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1800                 {
1801                   gfc_error ("Passing internal procedure at %L by location "
1802                              "not allowed", &e->where);
1803                   return FAILURE;
1804                 }
1805             }
1806         }
1807
1808       /* Fortran 2008, C1237.  */
1809       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1810           && gfc_has_ultimate_pointer (e))
1811         {
1812           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1813                      "component", &e->where);
1814           return FAILURE;
1815         }
1816     }
1817
1818   return SUCCESS;
1819 }
1820
1821
1822 /* Do the checks of the actual argument list that are specific to elemental
1823    procedures.  If called with c == NULL, we have a function, otherwise if
1824    expr == NULL, we have a subroutine.  */
1825
1826 static gfc_try
1827 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1828 {
1829   gfc_actual_arglist *arg0;
1830   gfc_actual_arglist *arg;
1831   gfc_symbol *esym = NULL;
1832   gfc_intrinsic_sym *isym = NULL;
1833   gfc_expr *e = NULL;
1834   gfc_intrinsic_arg *iformal = NULL;
1835   gfc_formal_arglist *eformal = NULL;
1836   bool formal_optional = false;
1837   bool set_by_optional = false;
1838   int i;
1839   int rank = 0;
1840
1841   /* Is this an elemental procedure?  */
1842   if (expr && expr->value.function.actual != NULL)
1843     {
1844       if (expr->value.function.esym != NULL
1845           && expr->value.function.esym->attr.elemental)
1846         {
1847           arg0 = expr->value.function.actual;
1848           esym = expr->value.function.esym;
1849         }
1850       else if (expr->value.function.isym != NULL
1851                && expr->value.function.isym->elemental)
1852         {
1853           arg0 = expr->value.function.actual;
1854           isym = expr->value.function.isym;
1855         }
1856       else
1857         return SUCCESS;
1858     }
1859   else if (c && c->ext.actual != NULL)
1860     {
1861       arg0 = c->ext.actual;
1862       
1863       if (c->resolved_sym)
1864         esym = c->resolved_sym;
1865       else
1866         esym = c->symtree->n.sym;
1867       gcc_assert (esym);
1868
1869       if (!esym->attr.elemental)
1870         return SUCCESS;
1871     }
1872   else
1873     return SUCCESS;
1874
1875   /* The rank of an elemental is the rank of its array argument(s).  */
1876   for (arg = arg0; arg; arg = arg->next)
1877     {
1878       if (arg->expr != NULL && arg->expr->rank > 0)
1879         {
1880           rank = arg->expr->rank;
1881           if (arg->expr->expr_type == EXPR_VARIABLE
1882               && arg->expr->symtree->n.sym->attr.optional)
1883             set_by_optional = true;
1884
1885           /* Function specific; set the result rank and shape.  */
1886           if (expr)
1887             {
1888               expr->rank = rank;
1889               if (!expr->shape && arg->expr->shape)
1890                 {
1891                   expr->shape = gfc_get_shape (rank);
1892                   for (i = 0; i < rank; i++)
1893                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1894                 }
1895             }
1896           break;
1897         }
1898     }
1899
1900   /* If it is an array, it shall not be supplied as an actual argument
1901      to an elemental procedure unless an array of the same rank is supplied
1902      as an actual argument corresponding to a nonoptional dummy argument of
1903      that elemental procedure(12.4.1.5).  */
1904   formal_optional = false;
1905   if (isym)
1906     iformal = isym->formal;
1907   else
1908     eformal = esym->formal;
1909
1910   for (arg = arg0; arg; arg = arg->next)
1911     {
1912       if (eformal)
1913         {
1914           if (eformal->sym && eformal->sym->attr.optional)
1915             formal_optional = true;
1916           eformal = eformal->next;
1917         }
1918       else if (isym && iformal)
1919         {
1920           if (iformal->optional)
1921             formal_optional = true;
1922           iformal = iformal->next;
1923         }
1924       else if (isym)
1925         formal_optional = true;
1926
1927       if (pedantic && arg->expr != NULL
1928           && arg->expr->expr_type == EXPR_VARIABLE
1929           && arg->expr->symtree->n.sym->attr.optional
1930           && formal_optional
1931           && arg->expr->rank
1932           && (set_by_optional || arg->expr->rank != rank)
1933           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1934         {
1935           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1936                        "MISSING, it cannot be the actual argument of an "
1937                        "ELEMENTAL procedure unless there is a non-optional "
1938                        "argument with the same rank (12.4.1.5)",
1939                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1940           return FAILURE;
1941         }
1942     }
1943
1944   for (arg = arg0; arg; arg = arg->next)
1945     {
1946       if (arg->expr == NULL || arg->expr->rank == 0)
1947         continue;
1948
1949       /* Being elemental, the last upper bound of an assumed size array
1950          argument must be present.  */
1951       if (resolve_assumed_size_actual (arg->expr))
1952         return FAILURE;
1953
1954       /* Elemental procedure's array actual arguments must conform.  */
1955       if (e != NULL)
1956         {
1957           if (gfc_check_conformance (arg->expr, e,
1958                                      "elemental procedure") == FAILURE)
1959             return FAILURE;
1960         }
1961       else
1962         e = arg->expr;
1963     }
1964
1965   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1966      is an array, the intent inout/out variable needs to be also an array.  */
1967   if (rank > 0 && esym && expr == NULL)
1968     for (eformal = esym->formal, arg = arg0; arg && eformal;
1969          arg = arg->next, eformal = eformal->next)
1970       if ((eformal->sym->attr.intent == INTENT_OUT
1971            || eformal->sym->attr.intent == INTENT_INOUT)
1972           && arg->expr && arg->expr->rank == 0)
1973         {
1974           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1975                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1976                      "actual argument is an array", &arg->expr->where,
1977                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1978                      : "INOUT", eformal->sym->name, esym->name);
1979           return FAILURE;
1980         }
1981   return SUCCESS;
1982 }
1983
1984
1985 /* This function does the checking of references to global procedures
1986    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1987    77 and 95 standards.  It checks for a gsymbol for the name, making
1988    one if it does not already exist.  If it already exists, then the
1989    reference being resolved must correspond to the type of gsymbol.
1990    Otherwise, the new symbol is equipped with the attributes of the
1991    reference.  The corresponding code that is called in creating
1992    global entities is parse.c.
1993
1994    In addition, for all but -std=legacy, the gsymbols are used to
1995    check the interfaces of external procedures from the same file.
1996    The namespace of the gsymbol is resolved and then, once this is
1997    done the interface is checked.  */
1998
1999
2000 static bool
2001 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
2002 {
2003   if (!gsym_ns->proc_name->attr.recursive)
2004     return true;
2005
2006   if (sym->ns == gsym_ns)
2007     return false;
2008
2009   if (sym->ns->parent && sym->ns->parent == gsym_ns)
2010     return false;
2011
2012   return true;
2013 }
2014
2015 static bool
2016 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
2017 {
2018   if (gsym_ns->entries)
2019     {
2020       gfc_entry_list *entry = gsym_ns->entries;
2021
2022       for (; entry; entry = entry->next)
2023         {
2024           if (strcmp (sym->name, entry->sym->name) == 0)
2025             {
2026               if (strcmp (gsym_ns->proc_name->name,
2027                           sym->ns->proc_name->name) == 0)
2028                 return false;
2029
2030               if (sym->ns->parent
2031                   && strcmp (gsym_ns->proc_name->name,
2032                              sym->ns->parent->proc_name->name) == 0)
2033                 return false;
2034             }
2035         }
2036     }
2037   return true;
2038 }
2039
2040 static void
2041 resolve_global_procedure (gfc_symbol *sym, locus *where,
2042                           gfc_actual_arglist **actual, int sub)
2043 {
2044   gfc_gsymbol * gsym;
2045   gfc_namespace *ns;
2046   enum gfc_symbol_type type;
2047
2048   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
2049
2050   gsym = gfc_get_gsymbol (sym->name);
2051
2052   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
2053     gfc_global_used (gsym, where);
2054
2055   if (gfc_option.flag_whole_file
2056         && (sym->attr.if_source == IFSRC_UNKNOWN
2057             || sym->attr.if_source == IFSRC_IFBODY)
2058         && gsym->type != GSYM_UNKNOWN
2059         && gsym->ns
2060         && gsym->ns->resolved != -1
2061         && gsym->ns->proc_name
2062         && not_in_recursive (sym, gsym->ns)
2063         && not_entry_self_reference (sym, gsym->ns))
2064     {
2065       gfc_symbol *def_sym;
2066
2067       /* Resolve the gsymbol namespace if needed.  */
2068       if (!gsym->ns->resolved)
2069         {
2070           gfc_dt_list *old_dt_list;
2071           struct gfc_omp_saved_state old_omp_state;
2072
2073           /* Stash away derived types so that the backend_decls do not
2074              get mixed up.  */
2075           old_dt_list = gfc_derived_types;
2076           gfc_derived_types = NULL;
2077           /* And stash away openmp state.  */
2078           gfc_omp_save_and_clear_state (&old_omp_state);
2079
2080           gfc_resolve (gsym->ns);
2081
2082           /* Store the new derived types with the global namespace.  */
2083           if (gfc_derived_types)
2084             gsym->ns->derived_types = gfc_derived_types;
2085
2086           /* Restore the derived types of this namespace.  */
2087           gfc_derived_types = old_dt_list;
2088           /* And openmp state.  */
2089           gfc_omp_restore_state (&old_omp_state);
2090         }
2091
2092       /* Make sure that translation for the gsymbol occurs before
2093          the procedure currently being resolved.  */
2094       ns = gfc_global_ns_list;
2095       for (; ns && ns != gsym->ns; ns = ns->sibling)
2096         {
2097           if (ns->sibling == gsym->ns)
2098             {
2099               ns->sibling = gsym->ns->sibling;
2100               gsym->ns->sibling = gfc_global_ns_list;
2101               gfc_global_ns_list = gsym->ns;
2102               break;
2103             }
2104         }
2105
2106       def_sym = gsym->ns->proc_name;
2107       if (def_sym->attr.entry_master)
2108         {
2109           gfc_entry_list *entry;
2110           for (entry = gsym->ns->entries; entry; entry = entry->next)
2111             if (strcmp (entry->sym->name, sym->name) == 0)
2112               {
2113                 def_sym = entry->sym;
2114                 break;
2115               }
2116         }
2117
2118       /* Differences in constant character lengths.  */
2119       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
2120         {
2121           long int l1 = 0, l2 = 0;
2122           gfc_charlen *cl1 = sym->ts.u.cl;
2123           gfc_charlen *cl2 = def_sym->ts.u.cl;
2124
2125           if (cl1 != NULL
2126               && cl1->length != NULL
2127               && cl1->length->expr_type == EXPR_CONSTANT)
2128             l1 = mpz_get_si (cl1->length->value.integer);
2129
2130           if (cl2 != NULL
2131               && cl2->length != NULL
2132               && cl2->length->expr_type == EXPR_CONSTANT)
2133             l2 = mpz_get_si (cl2->length->value.integer);
2134
2135           if (l1 && l2 && l1 != l2)
2136             gfc_error ("Character length mismatch in return type of "
2137                        "function '%s' at %L (%ld/%ld)", sym->name,
2138                        &sym->declared_at, l1, l2);
2139         }
2140
2141      /* Type mismatch of function return type and expected type.  */
2142      if (sym->attr.function
2143          && !gfc_compare_types (&sym->ts, &def_sym->ts))
2144         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
2145                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2146                    gfc_typename (&def_sym->ts));
2147
2148       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
2149         {
2150           gfc_formal_arglist *arg = def_sym->formal;
2151           for ( ; arg; arg = arg->next)
2152             if (!arg->sym)
2153               continue;
2154             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
2155             else if (arg->sym->attr.allocatable
2156                      || arg->sym->attr.asynchronous
2157                      || arg->sym->attr.optional
2158                      || arg->sym->attr.pointer
2159                      || arg->sym->attr.target
2160                      || arg->sym->attr.value
2161                      || arg->sym->attr.volatile_)
2162               {
2163                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
2164                            "has an attribute that requires an explicit "
2165                            "interface for this procedure", arg->sym->name,
2166                            sym->name, &sym->declared_at);
2167                 break;
2168               }
2169             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
2170             else if (arg->sym && arg->sym->as
2171                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
2172               {
2173                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
2174                            "argument '%s' must have an explicit interface",
2175                            sym->name, &sym->declared_at, arg->sym->name);
2176                 break;
2177               }
2178             /* F2008, 12.4.2.2 (2c)  */
2179             else if (arg->sym->attr.codimension)
2180               {
2181                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
2182                            "'%s' must have an explicit interface",
2183                            sym->name, &sym->declared_at, arg->sym->name);
2184                 break;
2185               }
2186             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
2187             else if (false) /* TODO: is a parametrized derived type  */
2188               {
2189                 gfc_error ("Procedure '%s' at %L with parametrized derived "
2190                            "type argument '%s' must have an explicit "
2191                            "interface", sym->name, &sym->declared_at,
2192                            arg->sym->name);
2193                 break;
2194               }
2195             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
2196             else if (arg->sym->ts.type == BT_CLASS)
2197               {
2198                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
2199                            "argument '%s' must have an explicit interface",
2200                            sym->name, &sym->declared_at, arg->sym->name);
2201                 break;
2202               }
2203         }
2204
2205       if (def_sym->attr.function)
2206         {
2207           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
2208           if (def_sym->as && def_sym->as->rank
2209               && (!sym->as || sym->as->rank != def_sym->as->rank))
2210             gfc_error ("The reference to function '%s' at %L either needs an "
2211                        "explicit INTERFACE or the rank is incorrect", sym->name,
2212                        where);
2213
2214           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
2215           if ((def_sym->result->attr.pointer
2216                || def_sym->result->attr.allocatable)
2217                && (sym->attr.if_source != IFSRC_IFBODY
2218                    || def_sym->result->attr.pointer
2219                         != sym->result->attr.pointer
2220                    || def_sym->result->attr.allocatable
2221                         != sym->result->attr.allocatable))
2222             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
2223                        "result must have an explicit interface", sym->name,
2224                        where);
2225
2226           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
2227           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
2228               && def_sym->ts.type == BT_CHARACTER && def_sym->ts.u.cl->length != NULL)
2229             {
2230               gfc_charlen *cl = sym->ts.u.cl;
2231
2232               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
2233                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
2234                 {
2235                   gfc_error ("Nonconstant character-length function '%s' at %L "
2236                              "must have an explicit interface", sym->name,
2237                              &sym->declared_at);
2238                 }
2239             }
2240         }
2241
2242       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2243       if (def_sym->attr.elemental && !sym->attr.elemental)
2244         {
2245           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2246                      "interface", sym->name, &sym->declared_at);
2247         }
2248
2249       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2250       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2251         {
2252           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2253                      "an explicit interface", sym->name, &sym->declared_at);
2254         }
2255
2256       if (gfc_option.flag_whole_file == 1
2257           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2258               && !(gfc_option.warn_std & GFC_STD_GNU)))
2259         gfc_errors_to_warnings (1);
2260
2261       if (sym->attr.if_source != IFSRC_IFBODY)  
2262         gfc_procedure_use (def_sym, actual, where);
2263
2264       gfc_errors_to_warnings (0);
2265     }
2266
2267   if (gsym->type == GSYM_UNKNOWN)
2268     {
2269       gsym->type = type;
2270       gsym->where = *where;
2271     }
2272
2273   gsym->used = 1;
2274 }
2275
2276
2277 /************* Function resolution *************/
2278
2279 /* Resolve a function call known to be generic.
2280    Section 14.1.2.4.1.  */
2281
2282 static match
2283 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2284 {
2285   gfc_symbol *s;
2286
2287   if (sym->attr.generic)
2288     {
2289       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2290       if (s != NULL)
2291         {
2292           expr->value.function.name = s->name;
2293           expr->value.function.esym = s;
2294
2295           if (s->ts.type != BT_UNKNOWN)
2296             expr->ts = s->ts;
2297           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2298             expr->ts = s->result->ts;
2299
2300           if (s->as != NULL)
2301             expr->rank = s->as->rank;
2302           else if (s->result != NULL && s->result->as != NULL)
2303             expr->rank = s->result->as->rank;
2304
2305           gfc_set_sym_referenced (expr->value.function.esym);
2306
2307           return MATCH_YES;
2308         }
2309
2310       /* TODO: Need to search for elemental references in generic
2311          interface.  */
2312     }
2313
2314   if (sym->attr.intrinsic)
2315     return gfc_intrinsic_func_interface (expr, 0);
2316
2317   return MATCH_NO;
2318 }
2319
2320
2321 static gfc_try
2322 resolve_generic_f (gfc_expr *expr)
2323 {
2324   gfc_symbol *sym;
2325   match m;
2326
2327   sym = expr->symtree->n.sym;
2328
2329   for (;;)
2330     {
2331       m = resolve_generic_f0 (expr, sym);
2332       if (m == MATCH_YES)
2333         return SUCCESS;
2334       else if (m == MATCH_ERROR)
2335         return FAILURE;
2336
2337 generic:
2338       if (sym->ns->parent == NULL)
2339         break;
2340       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2341
2342       if (sym == NULL)
2343         break;
2344       if (!generic_sym (sym))
2345         goto generic;
2346     }
2347
2348   /* Last ditch attempt.  See if the reference is to an intrinsic
2349      that possesses a matching interface.  14.1.2.4  */
2350   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
2351     {
2352       gfc_error ("There is no specific function for the generic '%s' at %L",
2353                  expr->symtree->n.sym->name, &expr->where);
2354       return FAILURE;
2355     }
2356
2357   m = gfc_intrinsic_func_interface (expr, 0);
2358   if (m == MATCH_YES)
2359     return SUCCESS;
2360   if (m == MATCH_NO)
2361     gfc_error ("Generic function '%s' at %L is not consistent with a "
2362                "specific intrinsic interface", expr->symtree->n.sym->name,
2363                &expr->where);
2364
2365   return FAILURE;
2366 }
2367
2368
2369 /* Resolve a function call known to be specific.  */
2370
2371 static match
2372 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2373 {
2374   match m;
2375
2376   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2377     {
2378       if (sym->attr.dummy)
2379         {
2380           sym->attr.proc = PROC_DUMMY;
2381           goto found;
2382         }
2383
2384       sym->attr.proc = PROC_EXTERNAL;
2385       goto found;
2386     }
2387
2388   if (sym->attr.proc == PROC_MODULE
2389       || sym->attr.proc == PROC_ST_FUNCTION
2390       || sym->attr.proc == PROC_INTERNAL)
2391     goto found;
2392
2393   if (sym->attr.intrinsic)
2394     {
2395       m = gfc_intrinsic_func_interface (expr, 1);
2396       if (m == MATCH_YES)
2397         return MATCH_YES;
2398       if (m == MATCH_NO)
2399         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2400                    "with an intrinsic", sym->name, &expr->where);
2401
2402       return MATCH_ERROR;
2403     }
2404
2405   return MATCH_NO;
2406
2407 found:
2408   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2409
2410   if (sym->result)
2411     expr->ts = sym->result->ts;
2412   else
2413     expr->ts = sym->ts;
2414   expr->value.function.name = sym->name;
2415   expr->value.function.esym = sym;
2416   if (sym->as != NULL)
2417     expr->rank = sym->as->rank;
2418
2419   return MATCH_YES;
2420 }
2421
2422
2423 static gfc_try
2424 resolve_specific_f (gfc_expr *expr)
2425 {
2426   gfc_symbol *sym;
2427   match m;
2428
2429   sym = expr->symtree->n.sym;
2430
2431   for (;;)
2432     {
2433       m = resolve_specific_f0 (sym, expr);
2434       if (m == MATCH_YES)
2435         return SUCCESS;
2436       if (m == MATCH_ERROR)
2437         return FAILURE;
2438
2439       if (sym->ns->parent == NULL)
2440         break;
2441
2442       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2443
2444       if (sym == NULL)
2445         break;
2446     }
2447
2448   gfc_error ("Unable to resolve the specific function '%s' at %L",
2449              expr->symtree->n.sym->name, &expr->where);
2450
2451   return SUCCESS;
2452 }
2453
2454
2455 /* Resolve a procedure call not known to be generic nor specific.  */
2456
2457 static gfc_try
2458 resolve_unknown_f (gfc_expr *expr)
2459 {
2460   gfc_symbol *sym;
2461   gfc_typespec *ts;
2462
2463   sym = expr->symtree->n.sym;
2464
2465   if (sym->attr.dummy)
2466     {
2467       sym->attr.proc = PROC_DUMMY;
2468       expr->value.function.name = sym->name;
2469       goto set_type;
2470     }
2471
2472   /* See if we have an intrinsic function reference.  */
2473
2474   if (gfc_is_intrinsic (sym, 0, expr->where))
2475     {
2476       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2477         return SUCCESS;
2478       return FAILURE;
2479     }
2480
2481   /* The reference is to an external name.  */
2482
2483   sym->attr.proc = PROC_EXTERNAL;
2484   expr->value.function.name = sym->name;
2485   expr->value.function.esym = expr->symtree->n.sym;
2486
2487   if (sym->as != NULL)
2488     expr->rank = sym->as->rank;
2489
2490   /* Type of the expression is either the type of the symbol or the
2491      default type of the symbol.  */
2492
2493 set_type:
2494   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2495
2496   if (sym->ts.type != BT_UNKNOWN)
2497     expr->ts = sym->ts;
2498   else
2499     {
2500       ts = gfc_get_default_type (sym->name, sym->ns);
2501
2502       if (ts->type == BT_UNKNOWN)
2503         {
2504           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2505                      sym->name, &expr->where);
2506           return FAILURE;
2507         }
2508       else
2509         expr->ts = *ts;
2510     }
2511
2512   return SUCCESS;
2513 }
2514
2515
2516 /* Return true, if the symbol is an external procedure.  */
2517 static bool
2518 is_external_proc (gfc_symbol *sym)
2519 {
2520   if (!sym->attr.dummy && !sym->attr.contained
2521         && !(sym->attr.intrinsic
2522               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2523         && sym->attr.proc != PROC_ST_FUNCTION
2524         && !sym->attr.proc_pointer
2525         && !sym->attr.use_assoc
2526         && sym->name)
2527     return true;
2528
2529   return false;
2530 }
2531
2532
2533 /* Figure out if a function reference is pure or not.  Also set the name
2534    of the function for a potential error message.  Return nonzero if the
2535    function is PURE, zero if not.  */
2536 static int
2537 pure_stmt_function (gfc_expr *, gfc_symbol *);
2538
2539 static int
2540 pure_function (gfc_expr *e, const char **name)
2541 {
2542   int pure;
2543
2544   *name = NULL;
2545
2546   if (e->symtree != NULL
2547         && e->symtree->n.sym != NULL
2548         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2549     return pure_stmt_function (e, e->symtree->n.sym);
2550
2551   if (e->value.function.esym)
2552     {
2553       pure = gfc_pure (e->value.function.esym);
2554       *name = e->value.function.esym->name;
2555     }
2556   else if (e->value.function.isym)
2557     {
2558       pure = e->value.function.isym->pure
2559              || e->value.function.isym->elemental;
2560       *name = e->value.function.isym->name;
2561     }
2562   else
2563     {
2564       /* Implicit functions are not pure.  */
2565       pure = 0;
2566       *name = e->value.function.name;
2567     }
2568
2569   return pure;
2570 }
2571
2572
2573 static bool
2574 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2575                  int *f ATTRIBUTE_UNUSED)
2576 {
2577   const char *name;
2578
2579   /* Don't bother recursing into other statement functions
2580      since they will be checked individually for purity.  */
2581   if (e->expr_type != EXPR_FUNCTION
2582         || !e->symtree
2583         || e->symtree->n.sym == sym
2584         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2585     return false;
2586
2587   return pure_function (e, &name) ? false : true;
2588 }
2589
2590
2591 static int
2592 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2593 {
2594   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2595 }
2596
2597
2598 static gfc_try
2599 is_scalar_expr_ptr (gfc_expr *expr)
2600 {
2601   gfc_try retval = SUCCESS;
2602   gfc_ref *ref;
2603   int start;
2604   int end;
2605
2606   /* See if we have a gfc_ref, which means we have a substring, array
2607      reference, or a component.  */
2608   if (expr->ref != NULL)
2609     {
2610       ref = expr->ref;
2611       while (ref->next != NULL)
2612         ref = ref->next;
2613
2614       switch (ref->type)
2615         {
2616         case REF_SUBSTRING:
2617           if (ref->u.ss.start == NULL || ref->u.ss.end == NULL
2618               || gfc_dep_compare_expr (ref->u.ss.start, ref->u.ss.end) != 0)
2619             retval = FAILURE;
2620           break;
2621
2622         case REF_ARRAY:
2623           if (ref->u.ar.type == AR_ELEMENT)
2624             retval = SUCCESS;
2625           else if (ref->u.ar.type == AR_FULL)
2626             {
2627               /* The user can give a full array if the array is of size 1.  */
2628               if (ref->u.ar.as != NULL
2629                   && ref->u.ar.as->rank == 1
2630                   && ref->u.ar.as->type == AS_EXPLICIT
2631                   && ref->u.ar.as->lower[0] != NULL
2632                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2633                   && ref->u.ar.as->upper[0] != NULL
2634                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2635                 {
2636                   /* If we have a character string, we need to check if
2637                      its length is one.  */
2638                   if (expr->ts.type == BT_CHARACTER)
2639                     {
2640                       if (expr->ts.u.cl == NULL
2641                           || expr->ts.u.cl->length == NULL
2642                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2643                           != 0)
2644                         retval = FAILURE;
2645                     }
2646                   else
2647                     {
2648                       /* We have constant lower and upper bounds.  If the
2649                          difference between is 1, it can be considered a
2650                          scalar.  
2651                          FIXME: Use gfc_dep_compare_expr instead.  */
2652                       start = (int) mpz_get_si
2653                                 (ref->u.ar.as->lower[0]->value.integer);
2654                       end = (int) mpz_get_si
2655                                 (ref->u.ar.as->upper[0]->value.integer);
2656                       if (end - start + 1 != 1)
2657                         retval = FAILURE;
2658                    }
2659                 }
2660               else
2661                 retval = FAILURE;
2662             }
2663           else
2664             retval = FAILURE;
2665           break;
2666         default:
2667           retval = SUCCESS;
2668           break;
2669         }
2670     }
2671   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2672     {
2673       /* Character string.  Make sure it's of length 1.  */
2674       if (expr->ts.u.cl == NULL
2675           || expr->ts.u.cl->length == NULL
2676           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2677         retval = FAILURE;
2678     }
2679   else if (expr->rank != 0)
2680     retval = FAILURE;
2681
2682   return retval;
2683 }
2684
2685
2686 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2687    and, in the case of c_associated, set the binding label based on
2688    the arguments.  */
2689
2690 static gfc_try
2691 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2692                           gfc_symbol **new_sym)
2693 {
2694   char name[GFC_MAX_SYMBOL_LEN + 1];
2695   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2696   int optional_arg = 0;
2697   gfc_try retval = SUCCESS;
2698   gfc_symbol *args_sym;
2699   gfc_typespec *arg_ts;
2700   symbol_attribute arg_attr;
2701
2702   if (args->expr->expr_type == EXPR_CONSTANT
2703       || args->expr->expr_type == EXPR_OP
2704       || args->expr->expr_type == EXPR_NULL)
2705     {
2706       gfc_error ("Argument to '%s' at %L is not a variable",
2707                  sym->name, &(args->expr->where));
2708       return FAILURE;
2709     }
2710
2711   args_sym = args->expr->symtree->n.sym;
2712
2713   /* The typespec for the actual arg should be that stored in the expr
2714      and not necessarily that of the expr symbol (args_sym), because
2715      the actual expression could be a part-ref of the expr symbol.  */
2716   arg_ts = &(args->expr->ts);
2717   arg_attr = gfc_expr_attr (args->expr);
2718     
2719   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2720     {
2721       /* If the user gave two args then they are providing something for
2722          the optional arg (the second cptr).  Therefore, set the name and
2723          binding label to the c_associated for two cptrs.  Otherwise,
2724          set c_associated to expect one cptr.  */
2725       if (args->next)
2726         {
2727           /* two args.  */
2728           sprintf (name, "%s_2", sym->name);
2729           sprintf (binding_label, "%s_2", sym->binding_label);
2730           optional_arg = 1;
2731         }
2732       else
2733         {
2734           /* one arg.  */
2735           sprintf (name, "%s_1", sym->name);
2736           sprintf (binding_label, "%s_1", sym->binding_label);
2737           optional_arg = 0;
2738         }
2739
2740       /* Get a new symbol for the version of c_associated that
2741          will get called.  */
2742       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2743     }
2744   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2745            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2746     {
2747       sprintf (name, "%s", sym->name);
2748       sprintf (binding_label, "%s", sym->binding_label);
2749
2750       /* Error check the call.  */
2751       if (args->next != NULL)
2752         {
2753           gfc_error_now ("More actual than formal arguments in '%s' "
2754                          "call at %L", name, &(args->expr->where));
2755           retval = FAILURE;
2756         }
2757       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2758         {
2759           gfc_ref *ref;
2760           bool seen_section;
2761
2762           /* Make sure we have either the target or pointer attribute.  */
2763           if (!arg_attr.target && !arg_attr.pointer)
2764             {
2765               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2766                              "a TARGET or an associated pointer",
2767                              args_sym->name,
2768                              sym->name, &(args->expr->where));
2769               retval = FAILURE;
2770             }
2771
2772           if (gfc_is_coindexed (args->expr))
2773             {
2774               gfc_error_now ("Coindexed argument not permitted"
2775                              " in '%s' call at %L", name,
2776                              &(args->expr->where));
2777               retval = FAILURE;
2778             }
2779
2780           /* Follow references to make sure there are no array
2781              sections.  */
2782           seen_section = false;
2783
2784           for (ref=args->expr->ref; ref; ref = ref->next)
2785             {
2786               if (ref->type == REF_ARRAY)
2787                 {
2788                   if (ref->u.ar.type == AR_SECTION)
2789                     seen_section = true;
2790
2791                   if (ref->u.ar.type != AR_ELEMENT)
2792                     {
2793                       gfc_ref *r;
2794                       for (r = ref->next; r; r=r->next)
2795                         if (r->type == REF_COMPONENT)
2796                           {
2797                             gfc_error_now ("Array section not permitted"
2798                                            " in '%s' call at %L", name,
2799                                            &(args->expr->where));
2800                             retval = FAILURE;
2801                             break;
2802                           }
2803                     }
2804                 }
2805             }
2806
2807           if (seen_section && retval == SUCCESS)
2808             gfc_warning ("Array section in '%s' call at %L", name,
2809                          &(args->expr->where));
2810                          
2811           /* See if we have interoperable type and type param.  */
2812           if (gfc_verify_c_interop (arg_ts) == SUCCESS
2813               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2814             {
2815               if (args_sym->attr.target == 1)
2816                 {
2817                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2818                      has the target attribute and is interoperable.  */
2819                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2820                      allocatable variable that has the TARGET attribute and
2821                      is not an array of zero size.  */
2822                   if (args_sym->attr.allocatable == 1)
2823                     {
2824                       if (args_sym->attr.dimension != 0 
2825                           && (args_sym->as && args_sym->as->rank == 0))
2826                         {
2827                           gfc_error_now ("Allocatable variable '%s' used as a "
2828                                          "parameter to '%s' at %L must not be "
2829                                          "an array of zero size",
2830                                          args_sym->name, sym->name,
2831                                          &(args->expr->where));
2832                           retval = FAILURE;
2833                         }
2834                     }
2835                   else
2836                     {
2837                       /* A non-allocatable target variable with C
2838                          interoperable type and type parameters must be
2839                          interoperable.  */
2840                       if (args_sym && args_sym->attr.dimension)
2841                         {
2842                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2843                             {
2844                               gfc_error ("Assumed-shape array '%s' at %L "
2845                                          "cannot be an argument to the "
2846                                          "procedure '%s' because "
2847                                          "it is not C interoperable",
2848                                          args_sym->name,
2849                                          &(args->expr->where), sym->name);
2850                               retval = FAILURE;
2851                             }
2852                           else if (args_sym->as->type == AS_DEFERRED)
2853                             {
2854                               gfc_error ("Deferred-shape array '%s' at %L "
2855                                          "cannot be an argument to the "
2856                                          "procedure '%s' because "
2857                                          "it is not C interoperable",
2858                                          args_sym->name,
2859                                          &(args->expr->where), sym->name);
2860                               retval = FAILURE;
2861                             }
2862                         }
2863                               
2864                       /* Make sure it's not a character string.  Arrays of
2865                          any type should be ok if the variable is of a C
2866                          interoperable type.  */
2867                       if (arg_ts->type == BT_CHARACTER)
2868                         if (arg_ts->u.cl != NULL
2869                             && (arg_ts->u.cl->length == NULL
2870                                 || arg_ts->u.cl->length->expr_type
2871                                    != EXPR_CONSTANT
2872                                 || mpz_cmp_si
2873                                     (arg_ts->u.cl->length->value.integer, 1)
2874                                    != 0)
2875                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2876                           {
2877                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2878                                            "at %L must have a length of 1",
2879                                            args_sym->name, sym->name,
2880                                            &(args->expr->where));
2881                             retval = FAILURE;
2882                           }
2883                     }
2884                 }
2885               else if (arg_attr.pointer
2886                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2887                 {
2888                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2889                      scalar pointer.  */
2890                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2891                                  "associated scalar POINTER", args_sym->name,
2892                                  sym->name, &(args->expr->where));
2893                   retval = FAILURE;
2894                 }
2895             }
2896           else
2897             {
2898               /* The parameter is not required to be C interoperable.  If it
2899                  is not C interoperable, it must be a nonpolymorphic scalar
2900                  with no length type parameters.  It still must have either
2901                  the pointer or target attribute, and it can be
2902                  allocatable (but must be allocated when c_loc is called).  */
2903               if (args->expr->rank != 0 
2904                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2905                 {
2906                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2907                                  "scalar", args_sym->name, sym->name,
2908                                  &(args->expr->where));
2909                   retval = FAILURE;
2910                 }
2911               else if (arg_ts->type == BT_CHARACTER 
2912                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2913                 {
2914                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2915                                  "%L must have a length of 1",
2916                                  args_sym->name, sym->name,
2917                                  &(args->expr->where));
2918                   retval = FAILURE;
2919                 }
2920               else if (arg_ts->type == BT_CLASS)
2921                 {
2922                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
2923                                  "polymorphic", args_sym->name, sym->name,
2924                                  &(args->expr->where));
2925                   retval = FAILURE;
2926                 }
2927             }
2928         }
2929       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2930         {
2931           if (args_sym->attr.flavor != FL_PROCEDURE)
2932             {
2933               /* TODO: Update this error message to allow for procedure
2934                  pointers once they are implemented.  */
2935               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2936                              "procedure",
2937                              args_sym->name, sym->name,
2938                              &(args->expr->where));
2939               retval = FAILURE;
2940             }
2941           else if (args_sym->attr.is_bind_c != 1)
2942             {
2943               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2944                              "BIND(C)",
2945                              args_sym->name, sym->name,
2946                              &(args->expr->where));
2947               retval = FAILURE;
2948             }
2949         }
2950       
2951       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2952       *new_sym = sym;
2953     }
2954   else
2955     {
2956       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2957                           "iso_c_binding function: '%s'!\n", sym->name);
2958     }
2959
2960   return retval;
2961 }
2962
2963
2964 /* Resolve a function call, which means resolving the arguments, then figuring
2965    out which entity the name refers to.  */
2966
2967 static gfc_try
2968 resolve_function (gfc_expr *expr)
2969 {
2970   gfc_actual_arglist *arg;
2971   gfc_symbol *sym;
2972   const char *name;
2973   gfc_try t;
2974   int temp;
2975   procedure_type p = PROC_INTRINSIC;
2976   bool no_formal_args;
2977
2978   sym = NULL;
2979   if (expr->symtree)
2980     sym = expr->symtree->n.sym;
2981
2982   /* If this is a procedure pointer component, it has already been resolved.  */
2983   if (gfc_is_proc_ptr_comp (expr, NULL))
2984     return SUCCESS;
2985   
2986   if (sym && sym->attr.intrinsic
2987       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2988     return FAILURE;
2989
2990   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2991     {
2992       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2993       return FAILURE;
2994     }
2995
2996   /* If this ia a deferred TBP with an abstract interface (which may
2997      of course be referenced), expr->value.function.esym will be set.  */
2998   if (sym && sym->attr.abstract && !expr->value.function.esym)
2999     {
3000       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3001                  sym->name, &expr->where);
3002       return FAILURE;
3003     }
3004
3005   /* Switch off assumed size checking and do this again for certain kinds
3006      of procedure, once the procedure itself is resolved.  */
3007   need_full_assumed_size++;
3008
3009   if (expr->symtree && expr->symtree->n.sym)
3010     p = expr->symtree->n.sym->attr.proc;
3011
3012   if (expr->value.function.isym && expr->value.function.isym->inquiry)
3013     inquiry_argument = true;
3014   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
3015
3016   if (resolve_actual_arglist (expr->value.function.actual,
3017                               p, no_formal_args) == FAILURE)
3018     {
3019       inquiry_argument = false;
3020       return FAILURE;
3021     }
3022
3023   inquiry_argument = false;
3024  
3025   /* Need to setup the call to the correct c_associated, depending on
3026      the number of cptrs to user gives to compare.  */
3027   if (sym && sym->attr.is_iso_c == 1)
3028     {
3029       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
3030           == FAILURE)
3031         return FAILURE;
3032       
3033       /* Get the symtree for the new symbol (resolved func).
3034          the old one will be freed later, when it's no longer used.  */
3035       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
3036     }
3037   
3038   /* Resume assumed_size checking.  */
3039   need_full_assumed_size--;
3040
3041   /* If the procedure is external, check for usage.  */
3042   if (sym && is_external_proc (sym))
3043     resolve_global_procedure (sym, &expr->where,
3044                               &expr->value.function.actual, 0);
3045
3046   if (sym && sym->ts.type == BT_CHARACTER
3047       && sym->ts.u.cl
3048       && sym->ts.u.cl->length == NULL
3049       && !sym->attr.dummy
3050       && !sym->ts.deferred
3051       && expr->value.function.esym == NULL
3052       && !sym->attr.contained)
3053     {
3054       /* Internal procedures are taken care of in resolve_contained_fntype.  */
3055       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
3056                  "be used at %L since it is not a dummy argument",
3057                  sym->name, &expr->where);
3058       return FAILURE;
3059     }
3060
3061   /* See if function is already resolved.  */
3062
3063   if (expr->value.function.name != NULL)
3064     {
3065       if (expr->ts.type == BT_UNKNOWN)
3066         expr->ts = sym->ts;
3067       t = SUCCESS;
3068     }
3069   else
3070     {
3071       /* Apply the rules of section 14.1.2.  */
3072
3073       switch (procedure_kind (sym))
3074         {
3075         case PTYPE_GENERIC:
3076           t = resolve_generic_f (expr);
3077           break;
3078
3079         case PTYPE_SPECIFIC:
3080           t = resolve_specific_f (expr);
3081           break;
3082
3083         case PTYPE_UNKNOWN:
3084           t = resolve_unknown_f (expr);
3085           break;
3086
3087         default:
3088           gfc_internal_error ("resolve_function(): bad function type");
3089         }
3090     }
3091
3092   /* If the expression is still a function (it might have simplified),
3093      then we check to see if we are calling an elemental function.  */
3094
3095   if (expr->expr_type != EXPR_FUNCTION)
3096     return t;
3097
3098   temp = need_full_assumed_size;
3099   need_full_assumed_size = 0;
3100
3101   if (resolve_elemental_actual (expr, NULL) == FAILURE)
3102     return FAILURE;
3103
3104   if (omp_workshare_flag
3105       && expr->value.function.esym
3106       && ! gfc_elemental (expr->value.function.esym))
3107     {
3108       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
3109                  "in WORKSHARE construct", expr->value.function.esym->name,
3110                  &expr->where);
3111       t = FAILURE;
3112     }
3113
3114 #define GENERIC_ID expr->value.function.isym->id
3115   else if (expr->value.function.actual != NULL
3116            && expr->value.function.isym != NULL
3117            && GENERIC_ID != GFC_ISYM_LBOUND
3118            && GENERIC_ID != GFC_ISYM_LEN
3119            && GENERIC_ID != GFC_ISYM_LOC
3120            && GENERIC_ID != GFC_ISYM_PRESENT)
3121     {
3122       /* Array intrinsics must also have the last upper bound of an
3123          assumed size array argument.  UBOUND and SIZE have to be
3124          excluded from the check if the second argument is anything
3125          than a constant.  */
3126
3127       for (arg = expr->value.function.actual; arg; arg = arg->next)
3128         {
3129           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3130               && arg->next != NULL && arg->next->expr)
3131             {
3132               if (arg->next->expr->expr_type != EXPR_CONSTANT)
3133                 break;
3134
3135               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
3136                 break;
3137
3138               if ((int)mpz_get_si (arg->next->expr->value.integer)
3139                         < arg->expr->rank)
3140                 break;
3141             }
3142
3143           if (arg->expr != NULL
3144               && arg->expr->rank > 0
3145               && resolve_assumed_size_actual (arg->expr))
3146             return FAILURE;
3147         }
3148     }
3149 #undef GENERIC_ID
3150
3151   need_full_assumed_size = temp;
3152   name = NULL;
3153
3154   if (!pure_function (expr, &name) && name)
3155     {
3156       if (forall_flag)
3157         {
3158           gfc_error ("Reference to non-PURE function '%s' at %L inside a "
3159                      "FORALL %s", name, &expr->where,
3160                      forall_flag == 2 ? "mask" : "block");
3161           t = FAILURE;
3162         }
3163       else if (do_concurrent_flag)
3164         {
3165           gfc_error ("Reference to non-PURE function '%s' at %L inside a "
3166                      "DO CONCURRENT %s", name, &expr->where,
3167                      do_concurrent_flag == 2 ? "mask" : "block");
3168           t = FAILURE;
3169         }
3170       else if (gfc_pure (NULL))
3171         {
3172           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
3173                      "procedure within a PURE procedure", name, &expr->where);
3174           t = FAILURE;
3175         }
3176     }
3177
3178   if (!pure_function (expr, &name) && name && gfc_implicit_pure (NULL))
3179     gfc_current_ns->proc_name->attr.implicit_pure = 0;
3180
3181   /* Functions without the RECURSIVE attribution are not allowed to
3182    * call themselves.  */
3183   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3184     {
3185       gfc_symbol *esym;
3186       esym = expr->value.function.esym;
3187
3188       if (is_illegal_recursion (esym, gfc_current_ns))
3189       {
3190         if (esym->attr.entry && esym->ns->entries)
3191           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3192                      " function '%s' is not RECURSIVE",
3193                      esym->name, &expr->where, esym->ns->entries->sym->name);
3194         else
3195           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
3196                      " is not RECURSIVE", esym->name, &expr->where);
3197
3198         t = FAILURE;
3199       }
3200     }
3201
3202   /* Character lengths of use associated functions may contains references to
3203      symbols not referenced from the current program unit otherwise.  Make sure
3204      those symbols are marked as referenced.  */
3205
3206   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3207       && expr->value.function.esym->attr.use_assoc)
3208     {
3209       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3210     }
3211
3212   /* Make sure that the expression has a typespec that works.  */
3213   if (expr->ts.type == BT_UNKNOWN)
3214     {
3215       if (expr->symtree->n.sym->result
3216             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3217             && !expr->symtree->n.sym->result->attr.proc_pointer)
3218         expr->ts = expr->symtree->n.sym->result->ts;
3219     }
3220
3221   return t;
3222 }
3223
3224
3225 /************* Subroutine resolution *************/
3226
3227 static void
3228 pure_subroutine (gfc_code *c, gfc_symbol *sym)
3229 {
3230   if (gfc_pure (sym))
3231     return;
3232
3233   if (forall_flag)
3234     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
3235                sym->name, &c->loc);
3236   else if (do_concurrent_flag)
3237     gfc_error ("Subroutine call to '%s' in DO CONCURRENT block at %L is not "
3238                "PURE", sym->name, &c->loc);
3239   else if (gfc_pure (NULL))
3240     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
3241                &c->loc);
3242 }
3243
3244
3245 static match
3246 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3247 {
3248   gfc_symbol *s;
3249
3250   if (sym->attr.generic)
3251     {
3252       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3253       if (s != NULL)
3254         {
3255           c->resolved_sym = s;
3256           pure_subroutine (c, s);
3257           return MATCH_YES;
3258         }
3259
3260       /* TODO: Need to search for elemental references in generic interface.  */
3261     }
3262
3263   if (sym->attr.intrinsic)
3264     return gfc_intrinsic_sub_interface (c, 0);
3265
3266   return MATCH_NO;
3267 }
3268
3269
3270 static gfc_try
3271 resolve_generic_s (gfc_code *c)
3272 {
3273   gfc_symbol *sym;
3274   match m;
3275
3276   sym = c->symtree->n.sym;
3277
3278   for (;;)
3279     {
3280       m = resolve_generic_s0 (c, sym);
3281       if (m == MATCH_YES)
3282         return SUCCESS;
3283       else if (m == MATCH_ERROR)
3284         return FAILURE;
3285
3286 generic:
3287       if (sym->ns->parent == NULL)
3288         break;
3289       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3290
3291       if (sym == NULL)
3292         break;
3293       if (!generic_sym (sym))
3294         goto generic;
3295     }
3296
3297   /* Last ditch attempt.  See if the reference is to an intrinsic
3298      that possesses a matching interface.  14.1.2.4  */
3299   sym = c->symtree->n.sym;
3300
3301   if (!gfc_is_intrinsic (sym, 1, c->loc))
3302     {
3303       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3304                  sym->name, &c->loc);
3305       return FAILURE;
3306     }
3307
3308   m = gfc_intrinsic_sub_interface (c, 0);
3309   if (m == MATCH_YES)
3310     return SUCCESS;
3311   if (m == MATCH_NO)
3312     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3313                "intrinsic subroutine interface", sym->name, &c->loc);
3314
3315   return FAILURE;
3316 }
3317
3318
3319 /* Set the name and binding label of the subroutine symbol in the call
3320    expression represented by 'c' to include the type and kind of the
3321    second parameter.  This function is for resolving the appropriate
3322    version of c_f_pointer() and c_f_procpointer().  For example, a
3323    call to c_f_pointer() for a default integer pointer could have a
3324    name of c_f_pointer_i4.  If no second arg exists, which is an error
3325    for these two functions, it defaults to the generic symbol's name
3326    and binding label.  */
3327
3328 static void
3329 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3330                     char *name, char *binding_label)
3331 {
3332   gfc_expr *arg = NULL;
3333   char type;
3334   int kind;
3335
3336   /* The second arg of c_f_pointer and c_f_procpointer determines
3337      the type and kind for the procedure name.  */
3338   arg = c->ext.actual->next->expr;
3339
3340   if (arg != NULL)
3341     {
3342       /* Set up the name to have the given symbol's name,
3343          plus the type and kind.  */
3344       /* a derived type is marked with the type letter 'u' */
3345       if (arg->ts.type == BT_DERIVED)
3346         {
3347           type = 'd';
3348           kind = 0; /* set the kind as 0 for now */
3349         }
3350       else
3351         {
3352           type = gfc_type_letter (arg->ts.type);
3353           kind = arg->ts.kind;
3354         }
3355
3356       if (arg->ts.type == BT_CHARACTER)
3357         /* Kind info for character strings not needed.  */
3358         kind = 0;
3359
3360       sprintf (name, "%s_%c%d", sym->name, type, kind);
3361       /* Set up the binding label as the given symbol's label plus
3362          the type and kind.  */
3363       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
3364     }
3365   else
3366     {
3367       /* If the second arg is missing, set the name and label as
3368          was, cause it should at least be found, and the missing
3369          arg error will be caught by compare_parameters().  */
3370       sprintf (name, "%s", sym->name);
3371       sprintf (binding_label, "%s", sym->binding_label);
3372     }
3373    
3374   return;
3375 }
3376
3377
3378 /* Resolve a generic version of the iso_c_binding procedure given
3379    (sym) to the specific one based on the type and kind of the
3380    argument(s).  Currently, this function resolves c_f_pointer() and
3381    c_f_procpointer based on the type and kind of the second argument
3382    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3383    Upon successfully exiting, c->resolved_sym will hold the resolved
3384    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3385    otherwise.  */
3386
3387 match
3388 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3389 {
3390   gfc_symbol *new_sym;
3391   /* this is fine, since we know the names won't use the max */
3392   char name[GFC_MAX_SYMBOL_LEN + 1];
3393   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3394   /* default to success; will override if find error */
3395   match m = MATCH_YES;
3396
3397   /* Make sure the actual arguments are in the necessary order (based on the 
3398      formal args) before resolving.  */
3399   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3400
3401   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3402       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3403     {
3404       set_name_and_label (c, sym, name, binding_label);
3405       
3406       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3407         {
3408           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3409             {
3410               /* Make sure we got a third arg if the second arg has non-zero
3411                  rank.  We must also check that the type and rank are
3412                  correct since we short-circuit this check in
3413                  gfc_procedure_use() (called above to sort actual args).  */
3414               if (c->ext.actual->next->expr->rank != 0)
3415                 {
3416                   if(c->ext.actual->next->next == NULL 
3417                      || c->ext.actual->next->next->expr == NULL)
3418                     {
3419                       m = MATCH_ERROR;
3420                       gfc_error ("Missing SHAPE parameter for call to %s "
3421                                  "at %L", sym->name, &(c->loc));
3422                     }
3423                   else if (c->ext.actual->next->next->expr->ts.type
3424                            != BT_INTEGER
3425                            || c->ext.actual->next->next->expr->rank != 1)
3426                     {
3427                       m = MATCH_ERROR;
3428                       gfc_error ("SHAPE parameter for call to %s at %L must "
3429                                  "be a rank 1 INTEGER array", sym->name,
3430                                  &(c->loc));
3431                     }
3432                 }
3433             }
3434         }
3435       
3436       if (m != MATCH_ERROR)
3437         {
3438           /* the 1 means to add the optional arg to formal list */
3439           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3440          
3441           /* for error reporting, say it's declared where the original was */
3442           new_sym->declared_at = sym->declared_at;
3443         }
3444     }
3445   else
3446     {
3447       /* no differences for c_loc or c_funloc */
3448       new_sym = sym;
3449     }
3450
3451   /* set the resolved symbol */
3452   if (m != MATCH_ERROR)
3453     c->resolved_sym = new_sym;
3454   else
3455     c->resolved_sym = sym;
3456   
3457   return m;
3458 }
3459
3460
3461 /* Resolve a subroutine call known to be specific.  */
3462
3463 static match
3464 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3465 {
3466   match m;
3467
3468   if(sym->attr.is_iso_c)
3469     {
3470       m = gfc_iso_c_sub_interface (c,sym);
3471       return m;
3472     }
3473   
3474   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3475     {
3476       if (sym->attr.dummy)
3477         {
3478           sym->attr.proc = PROC_DUMMY;
3479           goto found;
3480         }
3481
3482       sym->attr.proc = PROC_EXTERNAL;
3483       goto found;
3484     }
3485
3486   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3487     goto found;
3488
3489   if (sym->attr.intrinsic)
3490     {
3491       m = gfc_intrinsic_sub_interface (c, 1);
3492       if (m == MATCH_YES)
3493         return MATCH_YES;
3494       if (m == MATCH_NO)
3495         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3496                    "with an intrinsic", sym->name, &c->loc);
3497
3498       return MATCH_ERROR;
3499     }
3500
3501   return MATCH_NO;
3502
3503 found:
3504   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3505
3506   c->resolved_sym = sym;
3507   pure_subroutine (c, sym);
3508
3509   return MATCH_YES;
3510 }
3511
3512
3513 static gfc_try
3514 resolve_specific_s (gfc_code *c)
3515 {
3516   gfc_symbol *sym;
3517   match m;
3518
3519   sym = c->symtree->n.sym;
3520
3521   for (;;)
3522     {
3523       m = resolve_specific_s0 (c, sym);
3524       if (m == MATCH_YES)
3525         return SUCCESS;
3526       if (m == MATCH_ERROR)
3527         return FAILURE;
3528
3529       if (sym->ns->parent == NULL)
3530         break;
3531
3532       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3533
3534       if (sym == NULL)
3535         break;
3536     }
3537
3538   sym = c->symtree->n.sym;
3539   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3540              sym->name, &c->loc);
3541
3542   return FAILURE;
3543 }
3544
3545
3546 /* Resolve a subroutine call not known to be generic nor specific.  */
3547
3548 static gfc_try
3549 resolve_unknown_s (gfc_code *c)
3550 {
3551   gfc_symbol *sym;
3552
3553   sym = c->symtree->n.sym;
3554
3555   if (sym->attr.dummy)
3556     {
3557       sym->attr.proc = PROC_DUMMY;
3558       goto found;
3559     }
3560
3561   /* See if we have an intrinsic function reference.  */
3562
3563   if (gfc_is_intrinsic (sym, 1, c->loc))
3564     {
3565       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3566         return SUCCESS;
3567       return FAILURE;
3568     }
3569
3570   /* The reference is to an external name.  */
3571
3572 found:
3573   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3574
3575   c->resolved_sym = sym;
3576
3577   pure_subroutine (c, sym);
3578
3579   return SUCCESS;
3580 }
3581
3582
3583 /* Resolve a subroutine call.  Although it was tempting to use the same code
3584    for functions, subroutines and functions are stored differently and this
3585    makes things awkward.  */
3586
3587 static gfc_try
3588 resolve_call (gfc_code *c)
3589 {
3590   gfc_try t;
3591   procedure_type ptype = PROC_INTRINSIC;
3592   gfc_symbol *csym, *sym;
3593   bool no_formal_args;
3594
3595   csym = c->symtree ? c->symtree->n.sym : NULL;
3596
3597   if (csym && csym->ts.type != BT_UNKNOWN)
3598     {
3599       gfc_error ("'%s' at %L has a type, which is not consistent with "
3600                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3601       return FAILURE;
3602     }
3603
3604   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3605     {
3606       gfc_symtree *st;
3607       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3608       sym = st ? st->n.sym : NULL;
3609       if (sym && csym != sym
3610               && sym->ns == gfc_current_ns
3611               && sym->attr.flavor == FL_PROCEDURE
3612               && sym->attr.contained)
3613         {
3614           sym->refs++;
3615           if (csym->attr.generic)
3616             c->symtree->n.sym = sym;
3617           else
3618             c->symtree = st;
3619           csym = c->symtree->n.sym;
3620         }
3621     }
3622
3623   /* If this ia a deferred TBP with an abstract interface
3624      (which may of course be referenced), c->expr1 will be set.  */
3625   if (csym && csym->attr.abstract && !c->expr1)
3626     {
3627       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3628                  csym->name, &c->loc);
3629       return FAILURE;
3630     }
3631
3632   /* Subroutines without the RECURSIVE attribution are not allowed to
3633    * call themselves.  */
3634   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3635     {
3636       if (csym->attr.entry && csym->ns->entries)
3637         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3638                    " subroutine '%s' is not RECURSIVE",
3639                    csym->name, &c->loc, csym->ns->entries->sym->name);
3640       else
3641         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3642                    " is not RECURSIVE", csym->name, &c->loc);
3643
3644       t = FAILURE;
3645     }
3646
3647   /* Switch off assumed size checking and do this again for certain kinds
3648      of procedure, once the procedure itself is resolved.  */
3649   need_full_assumed_size++;
3650
3651   if (csym)
3652     ptype = csym->attr.proc;
3653
3654   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3655   if (resolve_actual_arglist (c->ext.actual, ptype,
3656                               no_formal_args) == FAILURE)
3657     return FAILURE;
3658
3659   /* Resume assumed_size checking.  */
3660   need_full_assumed_size--;
3661
3662   /* If external, check for usage.  */
3663   if (csym && is_external_proc (csym))
3664     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3665
3666   t = SUCCESS;
3667   if (c->resolved_sym == NULL)
3668     {
3669       c->resolved_isym = NULL;
3670       switch (procedure_kind (csym))
3671         {
3672         case PTYPE_GENERIC:
3673           t = resolve_generic_s (c);
3674           break;
3675
3676         case PTYPE_SPECIFIC:
3677           t = resolve_specific_s (c);
3678           break;
3679
3680         case PTYPE_UNKNOWN:
3681           t = resolve_unknown_s (c);
3682           break;
3683
3684         default:
3685           gfc_internal_error ("resolve_subroutine(): bad function type");
3686         }
3687     }
3688
3689   /* Some checks of elemental subroutine actual arguments.  */
3690   if (resolve_elemental_actual (NULL, c) == FAILURE)
3691     return FAILURE;
3692
3693   return t;
3694 }
3695
3696
3697 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3698    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3699    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3700    if their shapes do not match.  If either op1->shape or op2->shape is
3701    NULL, return SUCCESS.  */
3702
3703 static gfc_try
3704 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3705 {
3706   gfc_try t;
3707   int i;
3708
3709   t = SUCCESS;
3710
3711   if (op1->shape != NULL && op2->shape != NULL)
3712     {
3713       for (i = 0; i < op1->rank; i++)
3714         {
3715           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3716            {
3717              gfc_error ("Shapes for operands at %L and %L are not conformable",
3718                          &op1->where, &op2->where);
3719              t = FAILURE;
3720              break;
3721            }
3722         }
3723     }
3724
3725   return t;
3726 }
3727
3728
3729 /* Resolve an operator expression node.  This can involve replacing the
3730    operation with a user defined function call.  */
3731
3732 static gfc_try
3733 resolve_operator (gfc_expr *e)
3734 {
3735   gfc_expr *op1, *op2;
3736   char msg[200];
3737   bool dual_locus_error;
3738   gfc_try t;
3739
3740   /* Resolve all subnodes-- give them types.  */
3741
3742   switch (e->value.op.op)
3743     {
3744     default:
3745       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3746         return FAILURE;
3747
3748     /* Fall through...  */
3749
3750     case INTRINSIC_NOT:
3751     case INTRINSIC_UPLUS:
3752     case INTRINSIC_UMINUS:
3753     case INTRINSIC_PARENTHESES:
3754       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3755         return FAILURE;
3756       break;
3757     }
3758
3759   /* Typecheck the new node.  */
3760
3761   op1 = e->value.op.op1;
3762   op2 = e->value.op.op2;
3763   dual_locus_error = false;
3764
3765   if ((op1 && op1->expr_type == EXPR_NULL)
3766       || (op2 && op2->expr_type == EXPR_NULL))
3767     {
3768       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3769       goto bad_op;
3770     }
3771
3772   switch (e->value.op.op)
3773     {
3774     case INTRINSIC_UPLUS:
3775     case INTRINSIC_UMINUS:
3776       if (op1->ts.type == BT_INTEGER
3777           || op1->ts.type == BT_REAL
3778           || op1->ts.type == BT_COMPLEX)
3779         {
3780           e->ts = op1->ts;
3781           break;
3782         }
3783
3784       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3785                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3786       goto bad_op;
3787
3788     case INTRINSIC_PLUS:
3789     case INTRINSIC_MINUS:
3790     case INTRINSIC_TIMES:
3791     case INTRINSIC_DIVIDE:
3792     case INTRINSIC_POWER:
3793       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3794         {
3795           gfc_type_convert_binary (e, 1);
3796           break;
3797         }
3798
3799       sprintf (msg,
3800                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3801                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3802                gfc_typename (&op2->ts));
3803       goto bad_op;
3804
3805     case INTRINSIC_CONCAT:
3806       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3807           && op1->ts.kind == op2->ts.kind)
3808         {
3809           e->ts.type = BT_CHARACTER;
3810           e->ts.kind = op1->ts.kind;
3811           break;
3812         }
3813
3814       sprintf (msg,
3815                _("Operands of string concatenation operator at %%L are %s/%s"),
3816                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3817       goto bad_op;
3818
3819     case INTRINSIC_AND:
3820     case INTRINSIC_OR:
3821     case INTRINSIC_EQV:
3822     case INTRINSIC_NEQV:
3823       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3824         {
3825           e->ts.type = BT_LOGICAL;
3826           e->ts.kind = gfc_kind_max (op1, op2);
3827           if (op1->ts.kind < e->ts.kind)
3828             gfc_convert_type (op1, &e->ts, 2);
3829           else if (op2->ts.kind < e->ts.kind)
3830             gfc_convert_type (op2, &e->ts, 2);
3831           break;
3832         }
3833
3834       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3835                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3836                gfc_typename (&op2->ts));
3837
3838       goto bad_op;
3839
3840     case INTRINSIC_NOT:
3841       if (op1->ts.type == BT_LOGICAL)
3842         {
3843           e->ts.type = BT_LOGICAL;
3844           e->ts.kind = op1->ts.kind;
3845           break;
3846         }
3847
3848       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3849                gfc_typename (&op1->ts));
3850       goto bad_op;
3851
3852     case INTRINSIC_GT:
3853     case INTRINSIC_GT_OS:
3854     case INTRINSIC_GE:
3855     case INTRINSIC_GE_OS:
3856     case INTRINSIC_LT:
3857     case INTRINSIC_LT_OS:
3858     case INTRINSIC_LE:
3859     case INTRINSIC_LE_OS:
3860       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3861         {
3862           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3863           goto bad_op;
3864         }
3865
3866       /* Fall through...  */
3867
3868     case INTRINSIC_EQ:
3869     case INTRINSIC_EQ_OS:
3870     case INTRINSIC_NE:
3871     case INTRINSIC_NE_OS:
3872       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3873           && op1->ts.kind == op2->ts.kind)
3874         {
3875           e->ts.type = BT_LOGICAL;
3876           e->ts.kind = gfc_default_logical_kind;
3877           break;
3878         }
3879
3880       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3881         {
3882           gfc_type_convert_binary (e, 1);
3883
3884           e->ts.type = BT_LOGICAL;
3885           e->ts.kind = gfc_default_logical_kind;
3886           break;
3887         }
3888
3889       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3890         sprintf (msg,
3891                  _("Logicals at %%L must be compared with %s instead of %s"),
3892                  (e->value.op.op == INTRINSIC_EQ 
3893                   || e->value.op.op == INTRINSIC_EQ_OS)
3894                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3895       else
3896         sprintf (msg,
3897                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3898                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3899                  gfc_typename (&op2->ts));
3900
3901       goto bad_op;
3902
3903     case INTRINSIC_USER:
3904       if (e->value.op.uop->op == NULL)
3905         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3906       else if (op2 == NULL)
3907         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3908                  e->value.op.uop->name, gfc_typename (&op1->ts));
3909       else
3910         {
3911           sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3912                    e->value.op.uop->name, gfc_typename (&op1->ts),
3913                    gfc_typename (&op2->ts));
3914           e->value.op.uop->op->sym->attr.referenced = 1;
3915         }
3916
3917       goto bad_op;
3918
3919     case INTRINSIC_PARENTHESES:
3920       e->ts = op1->ts;
3921       if (e->ts.type == BT_CHARACTER)
3922         e->ts.u.cl = op1->ts.u.cl;
3923       break;
3924
3925     default:
3926       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3927     }
3928
3929   /* Deal with arrayness of an operand through an operator.  */
3930
3931   t = SUCCESS;
3932
3933   switch (e->value.op.op)
3934     {
3935     case INTRINSIC_PLUS:
3936     case INTRINSIC_MINUS:
3937     case INTRINSIC_TIMES:
3938     case INTRINSIC_DIVIDE:
3939     case INTRINSIC_POWER:
3940     case INTRINSIC_CONCAT:
3941     case INTRINSIC_AND:
3942     case INTRINSIC_OR:
3943     case INTRINSIC_EQV:
3944     case INTRINSIC_NEQV:
3945     case INTRINSIC_EQ:
3946     case INTRINSIC_EQ_OS:
3947     case INTRINSIC_NE:
3948     case INTRINSIC_NE_OS:
3949     case INTRINSIC_GT:
3950     case INTRINSIC_GT_OS:
3951     case INTRINSIC_GE:
3952     case INTRINSIC_GE_OS:
3953     case INTRINSIC_LT:
3954     case INTRINSIC_LT_OS:
3955     case INTRINSIC_LE:
3956     case INTRINSIC_LE_OS:
3957
3958       if (op1->rank == 0 && op2->rank == 0)
3959         e->rank = 0;
3960
3961       if (op1->rank == 0 && op2->rank != 0)
3962         {
3963           e->rank = op2->rank;
3964
3965           if (e->shape == NULL)
3966             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3967         }
3968
3969       if (op1->rank != 0 && op2->rank == 0)
3970         {
3971           e->rank = op1->rank;
3972
3973           if (e->shape == NULL)
3974             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3975         }
3976
3977       if (op1->rank != 0 && op2->rank != 0)
3978         {
3979           if (op1->rank == op2->rank)
3980             {
3981               e->rank = op1->rank;
3982               if (e->shape == NULL)
3983                 {
3984                   t = compare_shapes (op1, op2);
3985                   if (t == FAILURE)
3986                     e->shape = NULL;
3987                   else
3988                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
3989                 }
3990             }
3991           else
3992             {
3993               /* Allow higher level expressions to work.  */
3994               e->rank = 0;
3995
3996               /* Try user-defined operators, and otherwise throw an error.  */
3997               dual_locus_error = true;
3998               sprintf (msg,
3999                        _("Inconsistent ranks for operator at %%L and %%L"));
4000               goto bad_op;
4001             }
4002         }
4003
4004       break;
4005
4006     case INTRINSIC_PARENTHESES:
4007     case INTRINSIC_NOT:
4008     case INTRINSIC_UPLUS:
4009     case INTRINSIC_UMINUS:
4010       /* Simply copy arrayness attribute */
4011       e->rank = op1->rank;
4012
4013       if (e->shape == NULL)
4014         e->shape = gfc_copy_shape (op1->shape, op1->rank);
4015
4016       break;
4017
4018     default:
4019       break;
4020     }
4021
4022   /* Attempt to simplify the expression.  */
4023   if (t == SUCCESS)
4024     {
4025       t = gfc_simplify_expr (e, 0);
4026       /* Some calls do not succeed in simplification and return FAILURE
4027          even though there is no error; e.g. variable references to
4028          PARAMETER arrays.  */
4029       if (!gfc_is_constant_expr (e))
4030         t = SUCCESS;
4031     }
4032   return t;
4033
4034 bad_op:
4035
4036   {
4037     match m = gfc_extend_expr (e);
4038     if (m == MATCH_YES)
4039       return SUCCESS;
4040     if (m == MATCH_ERROR)
4041       return FAILURE;
4042   }
4043
4044   if (dual_locus_error)
4045     gfc_error (msg, &op1->where, &op2->where);
4046   else
4047     gfc_error (msg, &e->where);
4048
4049   return FAILURE;
4050 }
4051
4052
4053 /************** Array resolution subroutines **************/
4054
4055 typedef enum
4056 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
4057 comparison;
4058
4059 /* Compare two integer expressions.  */
4060
4061 static comparison
4062 compare_bound (gfc_expr *a, gfc_expr *b)
4063 {
4064   int i;
4065
4066   if (a == NULL || a->expr_type != EXPR_CONSTANT
4067       || b == NULL || b->expr_type != EXPR_CONSTANT)
4068     return CMP_UNKNOWN;
4069
4070   /* If either of the types isn't INTEGER, we must have
4071      raised an error earlier.  */
4072
4073   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
4074     return CMP_UNKNOWN;
4075
4076   i = mpz_cmp (a->value.integer, b->value.integer);
4077
4078   if (i < 0)
4079     return CMP_LT;
4080   if (i > 0)
4081     return CMP_GT;
4082   return CMP_EQ;
4083 }
4084
4085
4086 /* Compare an integer expression with an integer.  */
4087
4088 static comparison
4089 compare_bound_int (gfc_expr *a, int b)
4090 {
4091   int i;
4092
4093   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4094     return CMP_UNKNOWN;
4095
4096   if (a->ts.type != BT_INTEGER)
4097     gfc_internal_error ("compare_bound_int(): Bad expression");
4098
4099   i = mpz_cmp_si (a->value.integer, b);
4100
4101   if (i < 0)
4102     return CMP_LT;
4103   if (i > 0)
4104     return CMP_GT;
4105   return CMP_EQ;
4106 }
4107
4108
4109 /* Compare an integer expression with a mpz_t.  */
4110
4111 static comparison
4112 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
4113 {
4114   int i;
4115
4116   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4117     return CMP_UNKNOWN;
4118
4119   if (a->ts.type != BT_INTEGER)
4120     gfc_internal_error ("compare_bound_int(): Bad expression");
4121
4122   i = mpz_cmp (a->value.integer, b);
4123
4124   if (i < 0)
4125     return CMP_LT;
4126   if (i > 0)
4127     return CMP_GT;
4128   return CMP_EQ;
4129 }
4130
4131
4132 /* Compute the last value of a sequence given by a triplet.  
4133    Return 0 if it wasn't able to compute the last value, or if the
4134    sequence if empty, and 1 otherwise.  */
4135
4136 static int
4137 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
4138                                 gfc_expr *stride, mpz_t last)
4139 {
4140   mpz_t rem;
4141
4142   if (start == NULL || start->expr_type != EXPR_CONSTANT
4143       || end == NULL || end->expr_type != EXPR_CONSTANT
4144       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
4145     return 0;
4146
4147   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
4148       || (stride != NULL && stride->ts.type != BT_INTEGER))
4149     return 0;
4150
4151   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
4152     {
4153       if (compare_bound (start, end) == CMP_GT)
4154         return 0;
4155       mpz_set (last, end->value.integer);
4156       return 1;
4157     }
4158
4159   if (compare_bound_int (stride, 0) == CMP_GT)
4160     {
4161       /* Stride is positive */
4162       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
4163         return 0;
4164     }
4165   else
4166     {
4167       /* Stride is negative */
4168       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
4169         return 0;
4170     }
4171
4172   mpz_init (rem);
4173   mpz_sub (rem, end->value.integer, start->value.integer);
4174   mpz_tdiv_r (rem, rem, stride->value.integer);
4175   mpz_sub (last, end->value.integer, rem);
4176   mpz_clear (rem);
4177
4178   return 1;
4179 }
4180
4181
4182 /* Compare a single dimension of an array reference to the array
4183    specification.  */
4184
4185 static gfc_try
4186 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
4187 {
4188   mpz_t last_value;
4189
4190   if (ar->dimen_type[i] == DIMEN_STAR)
4191     {
4192       gcc_assert (ar->stride[i] == NULL);
4193       /* This implies [*] as [*:] and [*:3] are not possible.  */
4194       if (ar->start[i] == NULL)
4195         {
4196           gcc_assert (ar->end[i] == NULL);
4197           return SUCCESS;
4198         }
4199     }
4200
4201 /* Given start, end and stride values, calculate the minimum and
4202    maximum referenced indexes.  */
4203
4204   switch (ar->dimen_type[i])
4205     {
4206     case DIMEN_VECTOR:
4207     case DIMEN_THIS_IMAGE:
4208       break;
4209
4210     case DIMEN_STAR:
4211     case DIMEN_ELEMENT:
4212       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4213         {
4214           if (i < as->rank)
4215             gfc_warning ("Array reference at %L is out of bounds "
4216                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
4217                          mpz_get_si (ar->start[i]->value.integer),
4218                          mpz_get_si (as->lower[i]->value.integer), i+1);
4219           else
4220             gfc_warning ("Array reference at %L is out of bounds "
4221                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
4222                          mpz_get_si (ar->start[i]->value.integer),
4223                          mpz_get_si (as->lower[i]->value.integer),
4224                          i + 1 - as->rank);
4225           return SUCCESS;
4226         }
4227       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4228         {
4229           if (i < as->rank)
4230             gfc_warning ("Array reference at %L is out of bounds "
4231                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
4232                          mpz_get_si (ar->start[i]->value.integer),
4233                          mpz_get_si (as->upper[i]->value.integer), i+1);
4234           else
4235             gfc_warning ("Array reference at %L is out of bounds "
4236                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
4237                          mpz_get_si (ar->start[i]->value.integer),
4238                          mpz_get_si (as->upper[i]->value.integer),
4239                          i + 1 - as->rank);
4240           return SUCCESS;
4241         }
4242
4243       break;
4244
4245     case DIMEN_RANGE:
4246       {
4247 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4248 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4249
4250         comparison comp_start_end = compare_bound (AR_START, AR_END);
4251
4252         /* Check for zero stride, which is not allowed.  */
4253         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4254           {
4255             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4256             return FAILURE;
4257           }
4258
4259         /* if start == len || (stride > 0 && start < len)
4260                            || (stride < 0 && start > len),
4261            then the array section contains at least one element.  In this
4262            case, there is an out-of-bounds access if
4263            (start < lower || start > upper).  */
4264         if (compare_bound (AR_START, AR_END) == CMP_EQ
4265             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4266                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4267             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4268                 && comp_start_end == CMP_GT))
4269           {
4270             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4271               {
4272                 gfc_warning ("Lower array reference at %L is out of bounds "
4273                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4274                        mpz_get_si (AR_START->value.integer),
4275                        mpz_get_si (as->lower[i]->value.integer), i+1);
4276                 return SUCCESS;
4277               }
4278             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4279               {
4280                 gfc_warning ("Lower array reference at %L is out of bounds "
4281                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4282                        mpz_get_si (AR_START->value.integer),
4283                        mpz_get_si (as->upper[i]->value.integer), i+1);
4284                 return SUCCESS;
4285               }
4286           }
4287
4288         /* If we can compute the highest index of the array section,
4289            then it also has to be between lower and upper.  */
4290         mpz_init (last_value);
4291         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4292                                             last_value))
4293           {
4294             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4295               {
4296                 gfc_warning ("Upper array reference at %L is out of bounds "
4297                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4298                        mpz_get_si (last_value),
4299                        mpz_get_si (as->lower[i]->value.integer), i+1);
4300                 mpz_clear (last_value);
4301                 return SUCCESS;
4302               }
4303             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4304               {
4305                 gfc_warning ("Upper array reference at %L is out of bounds "
4306                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4307                        mpz_get_si (last_value),
4308                        mpz_get_si (as->upper[i]->value.integer), i+1);
4309                 mpz_clear (last_value);
4310                 return SUCCESS;
4311               }
4312           }
4313         mpz_clear (last_value);
4314
4315 #undef AR_START
4316 #undef AR_END
4317       }
4318       break;
4319
4320     default:
4321       gfc_internal_error ("check_dimension(): Bad array reference");
4322     }
4323
4324   return SUCCESS;
4325 }
4326
4327
4328 /* Compare an array reference with an array specification.  */
4329
4330 static gfc_try
4331 compare_spec_to_ref (gfc_array_ref *ar)
4332 {
4333   gfc_array_spec *as;
4334   int i;
4335
4336   as = ar->as;
4337   i = as->rank - 1;
4338   /* TODO: Full array sections are only allowed as actual parameters.  */
4339   if (as->type == AS_ASSUMED_SIZE
4340       && (/*ar->type == AR_FULL
4341           ||*/ (ar->type == AR_SECTION
4342               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4343     {
4344       gfc_error ("Rightmost upper bound of assumed size array section "
4345                  "not specified at %L", &ar->where);
4346       return FAILURE;
4347     }
4348
4349   if (ar->type == AR_FULL)
4350     return SUCCESS;
4351
4352   if (as->rank != ar->dimen)
4353     {
4354       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4355                  &ar->where, ar->dimen, as->rank);
4356       return FAILURE;
4357     }
4358
4359   /* ar->codimen == 0 is a local array.  */
4360   if (as->corank != ar->codimen && ar->codimen != 0)
4361     {
4362       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4363                  &ar->where, ar->codimen, as->corank);
4364       return FAILURE;
4365     }
4366
4367   for (i = 0; i < as->rank; i++)
4368     if (check_dimension (i, ar, as) == FAILURE)
4369       return FAILURE;
4370
4371   /* Local access has no coarray spec.  */
4372   if (ar->codimen != 0)
4373     for (i = as->rank; i < as->rank + as->corank; i++)
4374       {
4375         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate
4376             && ar->dimen_type[i] != DIMEN_THIS_IMAGE)
4377           {
4378             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4379                        i + 1 - as->rank, &ar->where);
4380             return FAILURE;
4381           }
4382         if (check_dimension (i, ar, as) == FAILURE)
4383           return FAILURE;
4384       }
4385
4386   return SUCCESS;
4387 }
4388
4389
4390 /* Resolve one part of an array index.  */
4391
4392 static gfc_try
4393 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4394                      int force_index_integer_kind)
4395 {
4396   gfc_typespec ts;
4397
4398   if (index == NULL)
4399     return SUCCESS;
4400
4401   if (gfc_resolve_expr (index) == FAILURE)
4402     return FAILURE;
4403
4404   if (check_scalar && index->rank != 0)
4405     {
4406       gfc_error ("Array index at %L must be scalar", &index->where);
4407       return FAILURE;
4408     }
4409
4410   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4411     {
4412       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4413                  &index->where, gfc_basic_typename (index->ts.type));
4414       return FAILURE;
4415     }
4416
4417   if (index->ts.type == BT_REAL)
4418     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4419                         &index->where) == FAILURE)
4420       return FAILURE;
4421
4422   if ((index->ts.kind != gfc_index_integer_kind
4423        && force_index_integer_kind)
4424       || index->ts.type != BT_INTEGER)
4425     {
4426       gfc_clear_ts (&ts);
4427       ts.type = BT_INTEGER;
4428       ts.kind = gfc_index_integer_kind;
4429
4430       gfc_convert_type_warn (index, &ts, 2, 0);
4431     }
4432
4433   return SUCCESS;
4434 }
4435
4436 /* Resolve one part of an array index.  */
4437
4438 gfc_try
4439 gfc_resolve_index (gfc_expr *index, int check_scalar)
4440 {
4441   return gfc_resolve_index_1 (index, check_scalar, 1);
4442 }
4443
4444 /* Resolve a dim argument to an intrinsic function.  */
4445
4446 gfc_try
4447 gfc_resolve_dim_arg (gfc_expr *dim)
4448 {
4449   if (dim == NULL)
4450     return SUCCESS;
4451
4452   if (gfc_resolve_expr (dim) == FAILURE)
4453     return FAILURE;
4454
4455   if (dim->rank != 0)
4456     {
4457       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4458       return FAILURE;
4459
4460     }
4461
4462   if (dim->ts.type != BT_INTEGER)
4463     {
4464       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4465       return FAILURE;
4466     }
4467
4468   if (dim->ts.kind != gfc_index_integer_kind)
4469     {
4470       gfc_typespec ts;
4471
4472       gfc_clear_ts (&ts);
4473       ts.type = BT_INTEGER;
4474       ts.kind = gfc_index_integer_kind;
4475
4476       gfc_convert_type_warn (dim, &ts, 2, 0);
4477     }
4478
4479   return SUCCESS;
4480 }
4481
4482 /* Given an expression that contains array references, update those array
4483    references to point to the right array specifications.  While this is
4484    filled in during matching, this information is difficult to save and load
4485    in a module, so we take care of it here.
4486
4487    The idea here is that the original array reference comes from the
4488    base symbol.  We traverse the list of reference structures, setting
4489    the stored reference to references.  Component references can
4490    provide an additional array specification.  */
4491
4492 static void
4493 find_array_spec (gfc_expr *e)
4494 {
4495   gfc_array_spec *as;
4496   gfc_component *c;
4497   gfc_symbol *derived;
4498   gfc_ref *ref;
4499
4500   if (e->symtree->n.sym->ts.type == BT_CLASS)
4501     as = CLASS_DATA (e->symtree->n.sym)->as;
4502   else
4503     as = e->symtree->n.sym->as;
4504   derived = NULL;
4505
4506   for (ref = e->ref; ref; ref = ref->next)
4507     switch (ref->type)
4508       {
4509       case REF_ARRAY:
4510         if (as == NULL)
4511           gfc_internal_error ("find_array_spec(): Missing spec");
4512
4513         ref->u.ar.as = as;
4514         as = NULL;
4515         break;
4516
4517       case REF_COMPONENT:
4518         if (derived == NULL)
4519           derived = e->symtree->n.sym->ts.u.derived;
4520
4521         if (derived->attr.is_class)
4522           derived = derived->components->ts.u.derived;
4523
4524         c = derived->components;
4525
4526         for (; c; c = c->next)
4527           if (c == ref->u.c.component)
4528             {
4529               /* Track the sequence of component references.  */
4530               if (c->ts.type == BT_DERIVED)
4531                 derived = c->ts.u.derived;
4532               break;
4533             }
4534
4535         if (c == NULL)
4536           gfc_internal_error ("find_array_spec(): Component not found");
4537
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   /* On the other hand, the parser may not have known this is an array;
5057      in this case, we have to add a FULL reference.  */
5058   if (sym->assoc && sym->attr.dimension && !e->ref)
5059     {
5060       e->ref = gfc_get_ref ();
5061       e->ref->type = REF_ARRAY;
5062       e->ref->u.ar.type = AR_FULL;
5063       e->ref->u.ar.dimen = 0;
5064     }
5065
5066   if (e->ref && resolve_ref (e) == FAILURE)
5067     return FAILURE;
5068
5069   if (sym->attr.flavor == FL_PROCEDURE
5070       && (!sym->attr.function
5071           || (sym->attr.function && sym->result
5072               && sym->result->attr.proc_pointer
5073               && !sym->result->attr.function)))
5074     {
5075       e->ts.type = BT_PROCEDURE;
5076       goto resolve_procedure;
5077     }
5078
5079   if (sym->ts.type != BT_UNKNOWN)
5080     gfc_variable_attr (e, &e->ts);
5081   else
5082     {
5083       /* Must be a simple variable reference.  */
5084       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
5085         return FAILURE;
5086       e->ts = sym->ts;
5087     }
5088
5089   if (check_assumed_size_reference (sym, e))
5090     return FAILURE;
5091
5092   /* Deal with forward references to entries during resolve_code, to
5093      satisfy, at least partially, 12.5.2.5.  */
5094   if (gfc_current_ns->entries
5095       && current_entry_id == sym->entry_id
5096       && cs_base
5097       && cs_base->current
5098       && cs_base->current->op != EXEC_ENTRY)
5099     {
5100       gfc_entry_list *entry;
5101       gfc_formal_arglist *formal;
5102       int n;
5103       bool seen;
5104
5105       /* If the symbol is a dummy...  */
5106       if (sym->attr.dummy && sym->ns == gfc_current_ns)
5107         {
5108           entry = gfc_current_ns->entries;
5109           seen = false;
5110
5111           /* ...test if the symbol is a parameter of previous entries.  */
5112           for (; entry && entry->id <= current_entry_id; entry = entry->next)
5113             for (formal = entry->sym->formal; formal; formal = formal->next)
5114               {
5115                 if (formal->sym && sym->name == formal->sym->name)
5116                   seen = true;
5117               }
5118
5119           /*  If it has not been seen as a dummy, this is an error.  */
5120           if (!seen)
5121             {
5122               if (specification_expr)
5123                 gfc_error ("Variable '%s', used in a specification expression"
5124                            ", is referenced at %L before the ENTRY statement "
5125                            "in which it is a parameter",
5126                            sym->name, &cs_base->current->loc);
5127               else
5128                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
5129                            "statement in which it is a parameter",
5130                            sym->name, &cs_base->current->loc);
5131               t = FAILURE;
5132             }
5133         }
5134
5135       /* Now do the same check on the specification expressions.  */
5136       specification_expr = 1;
5137       if (sym->ts.type == BT_CHARACTER
5138           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
5139         t = FAILURE;
5140
5141       if (sym->as)
5142         for (n = 0; n < sym->as->rank; n++)
5143           {
5144              specification_expr = 1;
5145              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
5146                t = FAILURE;
5147              specification_expr = 1;
5148              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
5149                t = FAILURE;
5150           }
5151       specification_expr = 0;
5152
5153       if (t == SUCCESS)
5154         /* Update the symbol's entry level.  */
5155         sym->entry_id = current_entry_id + 1;
5156     }
5157
5158   /* If a symbol has been host_associated mark it.  This is used latter,
5159      to identify if aliasing is possible via host association.  */
5160   if (sym->attr.flavor == FL_VARIABLE
5161         && gfc_current_ns->parent
5162         && (gfc_current_ns->parent == sym->ns
5163               || (gfc_current_ns->parent->parent
5164                     && gfc_current_ns->parent->parent == sym->ns)))
5165     sym->attr.host_assoc = 1;
5166
5167 resolve_procedure:
5168   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
5169     t = FAILURE;
5170
5171   /* F2008, C617 and C1229.  */
5172   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5173       && gfc_is_coindexed (e))
5174     {
5175       gfc_ref *ref, *ref2 = NULL;
5176
5177       for (ref = e->ref; ref; ref = ref->next)
5178         {
5179           if (ref->type == REF_COMPONENT)
5180             ref2 = ref;
5181           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5182             break;
5183         }
5184
5185       for ( ; ref; ref = ref->next)
5186         if (ref->type == REF_COMPONENT)
5187           break;
5188
5189       /* Expression itself is not coindexed object.  */
5190       if (ref && e->ts.type == BT_CLASS)
5191         {
5192           gfc_error ("Polymorphic subobject of coindexed object at %L",
5193                      &e->where);
5194           t = FAILURE;
5195         }
5196
5197       /* Expression itself is coindexed object.  */
5198       if (ref == NULL)
5199         {
5200           gfc_component *c;
5201           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5202           for ( ; c; c = c->next)
5203             if (c->attr.allocatable && c->ts.type == BT_CLASS)
5204               {
5205                 gfc_error ("Coindexed object with polymorphic allocatable "
5206                          "subcomponent at %L", &e->where);
5207                 t = FAILURE;
5208                 break;
5209               }
5210         }
5211     }
5212
5213   return t;
5214 }
5215
5216
5217 /* Checks to see that the correct symbol has been host associated.
5218    The only situation where this arises is that in which a twice
5219    contained function is parsed after the host association is made.
5220    Therefore, on detecting this, change the symbol in the expression
5221    and convert the array reference into an actual arglist if the old
5222    symbol is a variable.  */
5223 static bool
5224 check_host_association (gfc_expr *e)
5225 {
5226   gfc_symbol *sym, *old_sym;
5227   gfc_symtree *st;
5228   int n;
5229   gfc_ref *ref;
5230   gfc_actual_arglist *arg, *tail = NULL;
5231   bool retval = e->expr_type == EXPR_FUNCTION;
5232
5233   /*  If the expression is the result of substitution in
5234       interface.c(gfc_extend_expr) because there is no way in
5235       which the host association can be wrong.  */
5236   if (e->symtree == NULL
5237         || e->symtree->n.sym == NULL
5238         || e->user_operator)
5239     return retval;
5240
5241   old_sym = e->symtree->n.sym;
5242
5243   if (gfc_current_ns->parent
5244         && old_sym->ns != gfc_current_ns)
5245     {
5246       /* Use the 'USE' name so that renamed module symbols are
5247          correctly handled.  */
5248       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5249
5250       if (sym && old_sym != sym
5251               && sym->ts.type == old_sym->ts.type
5252               && sym->attr.flavor == FL_PROCEDURE
5253               && sym->attr.contained)
5254         {
5255           /* Clear the shape, since it might not be valid.  */
5256           gfc_free_shape (&e->shape, e->rank);
5257
5258           /* Give the expression the right symtree!  */
5259           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5260           gcc_assert (st != NULL);
5261
5262           if (old_sym->attr.flavor == FL_PROCEDURE
5263                 || e->expr_type == EXPR_FUNCTION)
5264             {
5265               /* Original was function so point to the new symbol, since
5266                  the actual argument list is already attached to the
5267                  expression. */
5268               e->value.function.esym = NULL;
5269               e->symtree = st;
5270             }
5271           else
5272             {
5273               /* Original was variable so convert array references into
5274                  an actual arglist. This does not need any checking now
5275                  since resolve_function will take care of it.  */
5276               e->value.function.actual = NULL;
5277               e->expr_type = EXPR_FUNCTION;
5278               e->symtree = st;
5279
5280               /* Ambiguity will not arise if the array reference is not
5281                  the last reference.  */
5282               for (ref = e->ref; ref; ref = ref->next)
5283                 if (ref->type == REF_ARRAY && ref->next == NULL)
5284                   break;
5285
5286               gcc_assert (ref->type == REF_ARRAY);
5287
5288               /* Grab the start expressions from the array ref and
5289                  copy them into actual arguments.  */
5290               for (n = 0; n < ref->u.ar.dimen; n++)
5291                 {
5292                   arg = gfc_get_actual_arglist ();
5293                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5294                   if (e->value.function.actual == NULL)
5295                     tail = e->value.function.actual = arg;
5296                   else
5297                     {
5298                       tail->next = arg;
5299                       tail = arg;
5300                     }
5301                 }
5302
5303               /* Dump the reference list and set the rank.  */
5304               gfc_free_ref_list (e->ref);
5305               e->ref = NULL;
5306               e->rank = sym->as ? sym->as->rank : 0;
5307             }
5308
5309           gfc_resolve_expr (e);
5310           sym->refs++;
5311         }
5312     }
5313   /* This might have changed!  */
5314   return e->expr_type == EXPR_FUNCTION;
5315 }
5316
5317
5318 static void
5319 gfc_resolve_character_operator (gfc_expr *e)
5320 {
5321   gfc_expr *op1 = e->value.op.op1;
5322   gfc_expr *op2 = e->value.op.op2;
5323   gfc_expr *e1 = NULL;
5324   gfc_expr *e2 = NULL;
5325
5326   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5327
5328   if (op1->ts.u.cl && op1->ts.u.cl->length)
5329     e1 = gfc_copy_expr (op1->ts.u.cl->length);
5330   else if (op1->expr_type == EXPR_CONSTANT)
5331     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5332                            op1->value.character.length);
5333
5334   if (op2->ts.u.cl && op2->ts.u.cl->length)
5335     e2 = gfc_copy_expr (op2->ts.u.cl->length);
5336   else if (op2->expr_type == EXPR_CONSTANT)
5337     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5338                            op2->value.character.length);
5339
5340   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5341
5342   if (!e1 || !e2)
5343     return;
5344
5345   e->ts.u.cl->length = gfc_add (e1, e2);
5346   e->ts.u.cl->length->ts.type = BT_INTEGER;
5347   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5348   gfc_simplify_expr (e->ts.u.cl->length, 0);
5349   gfc_resolve_expr (e->ts.u.cl->length);
5350
5351   return;
5352 }
5353
5354
5355 /*  Ensure that an character expression has a charlen and, if possible, a
5356     length expression.  */
5357
5358 static void
5359 fixup_charlen (gfc_expr *e)
5360 {
5361   /* The cases fall through so that changes in expression type and the need
5362      for multiple fixes are picked up.  In all circumstances, a charlen should
5363      be available for the middle end to hang a backend_decl on.  */
5364   switch (e->expr_type)
5365     {
5366     case EXPR_OP:
5367       gfc_resolve_character_operator (e);
5368
5369     case EXPR_ARRAY:
5370       if (e->expr_type == EXPR_ARRAY)
5371         gfc_resolve_character_array_constructor (e);
5372
5373     case EXPR_SUBSTRING:
5374       if (!e->ts.u.cl && e->ref)
5375         gfc_resolve_substring_charlen (e);
5376
5377     default:
5378       if (!e->ts.u.cl)
5379         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5380
5381       break;
5382     }
5383 }
5384
5385
5386 /* Update an actual argument to include the passed-object for type-bound
5387    procedures at the right position.  */
5388
5389 static gfc_actual_arglist*
5390 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5391                      const char *name)
5392 {
5393   gcc_assert (argpos > 0);
5394
5395   if (argpos == 1)
5396     {
5397       gfc_actual_arglist* result;
5398
5399       result = gfc_get_actual_arglist ();
5400       result->expr = po;
5401       result->next = lst;
5402       if (name)
5403         result->name = name;
5404
5405       return result;
5406     }
5407
5408   if (lst)
5409     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5410   else
5411     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5412   return lst;
5413 }
5414
5415
5416 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5417
5418 static gfc_expr*
5419 extract_compcall_passed_object (gfc_expr* e)
5420 {
5421   gfc_expr* po;
5422
5423   gcc_assert (e->expr_type == EXPR_COMPCALL);
5424
5425   if (e->value.compcall.base_object)
5426     po = gfc_copy_expr (e->value.compcall.base_object);
5427   else
5428     {
5429       po = gfc_get_expr ();
5430       po->expr_type = EXPR_VARIABLE;
5431       po->symtree = e->symtree;
5432       po->ref = gfc_copy_ref (e->ref);
5433       po->where = e->where;
5434     }
5435
5436   if (gfc_resolve_expr (po) == FAILURE)
5437     return NULL;
5438
5439   return po;
5440 }
5441
5442
5443 /* Update the arglist of an EXPR_COMPCALL expression to include the
5444    passed-object.  */
5445
5446 static gfc_try
5447 update_compcall_arglist (gfc_expr* e)
5448 {
5449   gfc_expr* po;
5450   gfc_typebound_proc* tbp;
5451
5452   tbp = e->value.compcall.tbp;
5453
5454   if (tbp->error)
5455     return FAILURE;
5456
5457   po = extract_compcall_passed_object (e);
5458   if (!po)
5459     return FAILURE;
5460
5461   if (tbp->nopass || e->value.compcall.ignore_pass)
5462     {
5463       gfc_free_expr (po);
5464       return SUCCESS;
5465     }
5466
5467   gcc_assert (tbp->pass_arg_num > 0);
5468   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5469                                                   tbp->pass_arg_num,
5470                                                   tbp->pass_arg);
5471
5472   return SUCCESS;
5473 }
5474
5475
5476 /* Extract the passed object from a PPC call (a copy of it).  */
5477
5478 static gfc_expr*
5479 extract_ppc_passed_object (gfc_expr *e)
5480 {
5481   gfc_expr *po;
5482   gfc_ref **ref;
5483
5484   po = gfc_get_expr ();
5485   po->expr_type = EXPR_VARIABLE;
5486   po->symtree = e->symtree;
5487   po->ref = gfc_copy_ref (e->ref);
5488   po->where = e->where;
5489
5490   /* Remove PPC reference.  */
5491   ref = &po->ref;
5492   while ((*ref)->next)
5493     ref = &(*ref)->next;
5494   gfc_free_ref_list (*ref);
5495   *ref = NULL;
5496
5497   if (gfc_resolve_expr (po) == FAILURE)
5498     return NULL;
5499
5500   return po;
5501 }
5502
5503
5504 /* Update the actual arglist of a procedure pointer component to include the
5505    passed-object.  */
5506
5507 static gfc_try
5508 update_ppc_arglist (gfc_expr* e)
5509 {
5510   gfc_expr* po;
5511   gfc_component *ppc;
5512   gfc_typebound_proc* tb;
5513
5514   if (!gfc_is_proc_ptr_comp (e, &ppc))
5515     return FAILURE;
5516
5517   tb = ppc->tb;
5518
5519   if (tb->error)
5520     return FAILURE;
5521   else if (tb->nopass)
5522     return SUCCESS;
5523
5524   po = extract_ppc_passed_object (e);
5525   if (!po)
5526     return FAILURE;
5527
5528   /* F08:R739.  */
5529   if (po->rank > 0)
5530     {
5531       gfc_error ("Passed-object at %L must be scalar", &e->where);
5532       return FAILURE;
5533     }
5534
5535   /* F08:C611.  */
5536   if (po->ts.type == BT_DERIVED && po->ts.u.derived->attr.abstract)
5537     {
5538       gfc_error ("Base object for procedure-pointer component call at %L is of"
5539                  " ABSTRACT type '%s'", &e->where, po->ts.u.derived->name);
5540       return FAILURE;
5541     }
5542
5543   gcc_assert (tb->pass_arg_num > 0);
5544   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5545                                                   tb->pass_arg_num,
5546                                                   tb->pass_arg);
5547
5548   return SUCCESS;
5549 }
5550
5551
5552 /* Check that the object a TBP is called on is valid, i.e. it must not be
5553    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5554
5555 static gfc_try
5556 check_typebound_baseobject (gfc_expr* e)
5557 {
5558   gfc_expr* base;
5559   gfc_try return_value = FAILURE;
5560
5561   base = extract_compcall_passed_object (e);
5562   if (!base)
5563     return FAILURE;
5564
5565   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5566
5567   /* F08:C611.  */
5568   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5569     {
5570       gfc_error ("Base object for type-bound procedure call at %L is of"
5571                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5572       goto cleanup;
5573     }
5574
5575   /* F08:C1230. If the procedure called is NOPASS,
5576      the base object must be scalar.  */
5577   if (e->value.compcall.tbp->nopass && base->rank > 0)
5578     {
5579       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5580                  " be scalar", &e->where);
5581       goto cleanup;
5582     }
5583
5584   /* FIXME: Remove once PR 43214 is fixed (TBP with non-scalar PASS).  */
5585   if (base->rank > 0)
5586     {
5587       gfc_error ("Non-scalar base object at %L currently not implemented",
5588                  &e->where);
5589       goto cleanup;
5590     }
5591
5592   return_value = SUCCESS;
5593
5594 cleanup:
5595   gfc_free_expr (base);
5596   return return_value;
5597 }
5598
5599
5600 /* Resolve a call to a type-bound procedure, either function or subroutine,
5601    statically from the data in an EXPR_COMPCALL expression.  The adapted
5602    arglist and the target-procedure symtree are returned.  */
5603
5604 static gfc_try
5605 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5606                           gfc_actual_arglist** actual)
5607 {
5608   gcc_assert (e->expr_type == EXPR_COMPCALL);
5609   gcc_assert (!e->value.compcall.tbp->is_generic);
5610
5611   /* Update the actual arglist for PASS.  */
5612   if (update_compcall_arglist (e) == FAILURE)
5613     return FAILURE;
5614
5615   *actual = e->value.compcall.actual;
5616   *target = e->value.compcall.tbp->u.specific;
5617
5618   gfc_free_ref_list (e->ref);
5619   e->ref = NULL;
5620   e->value.compcall.actual = NULL;
5621
5622   return SUCCESS;
5623 }
5624
5625
5626 /* Get the ultimate declared type from an expression.  In addition,
5627    return the last class/derived type reference and the copy of the
5628    reference list.  */
5629 static gfc_symbol*
5630 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5631                         gfc_expr *e)
5632 {
5633   gfc_symbol *declared;
5634   gfc_ref *ref;
5635
5636   declared = NULL;
5637   if (class_ref)
5638     *class_ref = NULL;
5639   if (new_ref)
5640     *new_ref = gfc_copy_ref (e->ref);
5641
5642   for (ref = e->ref; ref; ref = ref->next)
5643     {
5644       if (ref->type != REF_COMPONENT)
5645         continue;
5646
5647       if (ref->u.c.component->ts.type == BT_CLASS
5648             || ref->u.c.component->ts.type == BT_DERIVED)
5649         {
5650           declared = ref->u.c.component->ts.u.derived;
5651           if (class_ref)
5652             *class_ref = ref;
5653         }
5654     }
5655
5656   if (declared == NULL)
5657     declared = e->symtree->n.sym->ts.u.derived;
5658
5659   return declared;
5660 }
5661
5662
5663 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5664    which of the specific bindings (if any) matches the arglist and transform
5665    the expression into a call of that binding.  */
5666
5667 static gfc_try
5668 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5669 {
5670   gfc_typebound_proc* genproc;
5671   const char* genname;
5672   gfc_symtree *st;
5673   gfc_symbol *derived;
5674
5675   gcc_assert (e->expr_type == EXPR_COMPCALL);
5676   genname = e->value.compcall.name;
5677   genproc = e->value.compcall.tbp;
5678
5679   if (!genproc->is_generic)
5680     return SUCCESS;
5681
5682   /* Try the bindings on this type and in the inheritance hierarchy.  */
5683   for (; genproc; genproc = genproc->overridden)
5684     {
5685       gfc_tbp_generic* g;
5686
5687       gcc_assert (genproc->is_generic);
5688       for (g = genproc->u.generic; g; g = g->next)
5689         {
5690           gfc_symbol* target;
5691           gfc_actual_arglist* args;
5692           bool matches;
5693
5694           gcc_assert (g->specific);
5695
5696           if (g->specific->error)
5697             continue;
5698
5699           target = g->specific->u.specific->n.sym;
5700
5701           /* Get the right arglist by handling PASS/NOPASS.  */
5702           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5703           if (!g->specific->nopass)
5704             {
5705               gfc_expr* po;
5706               po = extract_compcall_passed_object (e);
5707               if (!po)
5708                 return FAILURE;
5709
5710               gcc_assert (g->specific->pass_arg_num > 0);
5711               gcc_assert (!g->specific->error);
5712               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5713                                           g->specific->pass_arg);
5714             }
5715           resolve_actual_arglist (args, target->attr.proc,
5716                                   is_external_proc (target) && !target->formal);
5717
5718           /* Check if this arglist matches the formal.  */
5719           matches = gfc_arglist_matches_symbol (&args, target);
5720
5721           /* Clean up and break out of the loop if we've found it.  */
5722           gfc_free_actual_arglist (args);
5723           if (matches)
5724             {
5725               e->value.compcall.tbp = g->specific;
5726               genname = g->specific_st->name;
5727               /* Pass along the name for CLASS methods, where the vtab
5728                  procedure pointer component has to be referenced.  */
5729               if (name)
5730                 *name = genname;
5731               goto success;
5732             }
5733         }
5734     }
5735
5736   /* Nothing matching found!  */
5737   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5738              " '%s' at %L", genname, &e->where);
5739   return FAILURE;
5740
5741 success:
5742   /* Make sure that we have the right specific instance for the name.  */
5743   derived = get_declared_from_expr (NULL, NULL, e);
5744
5745   st = gfc_find_typebound_proc (derived, NULL, genname, true, &e->where);
5746   if (st)
5747     e->value.compcall.tbp = st->n.tb;
5748
5749   return SUCCESS;
5750 }
5751
5752
5753 /* Resolve a call to a type-bound subroutine.  */
5754
5755 static gfc_try
5756 resolve_typebound_call (gfc_code* c, const char **name)
5757 {
5758   gfc_actual_arglist* newactual;
5759   gfc_symtree* target;
5760
5761   /* Check that's really a SUBROUTINE.  */
5762   if (!c->expr1->value.compcall.tbp->subroutine)
5763     {
5764       gfc_error ("'%s' at %L should be a SUBROUTINE",
5765                  c->expr1->value.compcall.name, &c->loc);
5766       return FAILURE;
5767     }
5768
5769   if (check_typebound_baseobject (c->expr1) == FAILURE)
5770     return FAILURE;
5771
5772   /* Pass along the name for CLASS methods, where the vtab
5773      procedure pointer component has to be referenced.  */
5774   if (name)
5775     *name = c->expr1->value.compcall.name;
5776
5777   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5778     return FAILURE;
5779
5780   /* Transform into an ordinary EXEC_CALL for now.  */
5781
5782   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5783     return FAILURE;
5784
5785   c->ext.actual = newactual;
5786   c->symtree = target;
5787   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5788
5789   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5790
5791   gfc_free_expr (c->expr1);
5792   c->expr1 = gfc_get_expr ();
5793   c->expr1->expr_type = EXPR_FUNCTION;
5794   c->expr1->symtree = target;
5795   c->expr1->where = c->loc;
5796
5797   return resolve_call (c);
5798 }
5799
5800
5801 /* Resolve a component-call expression.  */
5802 static gfc_try
5803 resolve_compcall (gfc_expr* e, const char **name)
5804 {
5805   gfc_actual_arglist* newactual;
5806   gfc_symtree* target;
5807
5808   /* Check that's really a FUNCTION.  */
5809   if (!e->value.compcall.tbp->function)
5810     {
5811       gfc_error ("'%s' at %L should be a FUNCTION",
5812                  e->value.compcall.name, &e->where);
5813       return FAILURE;
5814     }
5815
5816   /* These must not be assign-calls!  */
5817   gcc_assert (!e->value.compcall.assign);
5818
5819   if (check_typebound_baseobject (e) == FAILURE)
5820     return FAILURE;
5821
5822   /* Pass along the name for CLASS methods, where the vtab
5823      procedure pointer component has to be referenced.  */
5824   if (name)
5825     *name = e->value.compcall.name;
5826
5827   if (resolve_typebound_generic_call (e, name) == FAILURE)
5828     return FAILURE;
5829   gcc_assert (!e->value.compcall.tbp->is_generic);
5830
5831   /* Take the rank from the function's symbol.  */
5832   if (e->value.compcall.tbp->u.specific->n.sym->as)
5833     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5834
5835   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5836      arglist to the TBP's binding target.  */
5837
5838   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5839     return FAILURE;
5840
5841   e->value.function.actual = newactual;
5842   e->value.function.name = NULL;
5843   e->value.function.esym = target->n.sym;
5844   e->value.function.isym = NULL;
5845   e->symtree = target;
5846   e->ts = target->n.sym->ts;
5847   e->expr_type = EXPR_FUNCTION;
5848
5849   /* Resolution is not necessary if this is a class subroutine; this
5850      function only has to identify the specific proc. Resolution of
5851      the call will be done next in resolve_typebound_call.  */
5852   return gfc_resolve_expr (e);
5853 }
5854
5855
5856
5857 /* Resolve a typebound function, or 'method'. First separate all
5858    the non-CLASS references by calling resolve_compcall directly.  */
5859
5860 static gfc_try
5861 resolve_typebound_function (gfc_expr* e)
5862 {
5863   gfc_symbol *declared;
5864   gfc_component *c;
5865   gfc_ref *new_ref;
5866   gfc_ref *class_ref;
5867   gfc_symtree *st;
5868   const char *name;
5869   gfc_typespec ts;
5870   gfc_expr *expr;
5871   bool overridable;
5872
5873   st = e->symtree;
5874
5875   /* Deal with typebound operators for CLASS objects.  */
5876   expr = e->value.compcall.base_object;
5877   overridable = !e->value.compcall.tbp->non_overridable;
5878   if (expr && expr->ts.type == BT_CLASS && e->value.compcall.name)
5879     {
5880       /* Since the typebound operators are generic, we have to ensure
5881          that any delays in resolution are corrected and that the vtab
5882          is present.  */
5883       ts = expr->ts;
5884       declared = ts.u.derived;
5885       c = gfc_find_component (declared, "_vptr", true, true);
5886       if (c->ts.u.derived == NULL)
5887         c->ts.u.derived = gfc_find_derived_vtab (declared);
5888
5889       if (resolve_compcall (e, &name) == FAILURE)
5890         return FAILURE;
5891
5892       /* Use the generic name if it is there.  */
5893       name = name ? name : e->value.function.esym->name;
5894       e->symtree = expr->symtree;
5895       e->ref = gfc_copy_ref (expr->ref);
5896       gfc_add_vptr_component (e);
5897       gfc_add_component_ref (e, name);
5898       e->value.function.esym = NULL;
5899       return SUCCESS;
5900     }
5901
5902   if (st == NULL)
5903     return resolve_compcall (e, NULL);
5904
5905   if (resolve_ref (e) == FAILURE)
5906     return FAILURE;
5907
5908   /* Get the CLASS declared type.  */
5909   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5910
5911   /* Weed out cases of the ultimate component being a derived type.  */
5912   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5913          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5914     {
5915       gfc_free_ref_list (new_ref);
5916       return resolve_compcall (e, NULL);
5917     }
5918
5919   c = gfc_find_component (declared, "_data", true, true);
5920   declared = c->ts.u.derived;
5921
5922   /* Treat the call as if it is a typebound procedure, in order to roll
5923      out the correct name for the specific function.  */
5924   if (resolve_compcall (e, &name) == FAILURE)
5925     return FAILURE;
5926   ts = e->ts;
5927
5928   if (overridable)
5929     {
5930       /* Convert the expression to a procedure pointer component call.  */
5931       e->value.function.esym = NULL;
5932       e->symtree = st;
5933
5934       if (new_ref)  
5935         e->ref = new_ref;
5936
5937       /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5938       gfc_add_vptr_component (e);
5939       gfc_add_component_ref (e, name);
5940
5941       /* Recover the typespec for the expression.  This is really only
5942         necessary for generic procedures, where the additional call
5943         to gfc_add_component_ref seems to throw the collection of the
5944         correct typespec.  */
5945       e->ts = ts;
5946     }
5947
5948   return SUCCESS;
5949 }
5950
5951 /* Resolve a typebound subroutine, or 'method'. First separate all
5952    the non-CLASS references by calling resolve_typebound_call
5953    directly.  */
5954
5955 static gfc_try
5956 resolve_typebound_subroutine (gfc_code *code)
5957 {
5958   gfc_symbol *declared;
5959   gfc_component *c;
5960   gfc_ref *new_ref;
5961   gfc_ref *class_ref;
5962   gfc_symtree *st;
5963   const char *name;
5964   gfc_typespec ts;
5965   gfc_expr *expr;
5966   bool overridable;
5967
5968   st = code->expr1->symtree;
5969
5970   /* Deal with typebound operators for CLASS objects.  */
5971   expr = code->expr1->value.compcall.base_object;
5972   overridable = !code->expr1->value.compcall.tbp->non_overridable;
5973   if (expr && expr->ts.type == BT_CLASS && code->expr1->value.compcall.name)
5974     {
5975       /* Since the typebound operators are generic, we have to ensure
5976          that any delays in resolution are corrected and that the vtab
5977          is present.  */
5978       declared = expr->ts.u.derived;
5979       c = gfc_find_component (declared, "_vptr", true, true);
5980       if (c->ts.u.derived == NULL)
5981         c->ts.u.derived = gfc_find_derived_vtab (declared);
5982
5983       if (resolve_typebound_call (code, &name) == FAILURE)
5984         return FAILURE;
5985
5986       /* Use the generic name if it is there.  */
5987       name = name ? name : code->expr1->value.function.esym->name;
5988       code->expr1->symtree = expr->symtree;
5989       code->expr1->ref = gfc_copy_ref (expr->ref);
5990       gfc_add_vptr_component (code->expr1);
5991       gfc_add_component_ref (code->expr1, name);
5992       code->expr1->value.function.esym = NULL;
5993       return SUCCESS;
5994     }
5995
5996   if (st == NULL)
5997     return resolve_typebound_call (code, NULL);
5998
5999   if (resolve_ref (code->expr1) == FAILURE)
6000     return FAILURE;
6001
6002   /* Get the CLASS declared type.  */
6003   get_declared_from_expr (&class_ref, &new_ref, code->expr1);
6004
6005   /* Weed out cases of the ultimate component being a derived type.  */
6006   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
6007          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
6008     {
6009       gfc_free_ref_list (new_ref);
6010       return resolve_typebound_call (code, NULL);
6011     }
6012
6013   if (resolve_typebound_call (code, &name) == FAILURE)
6014     return FAILURE;
6015   ts = code->expr1->ts;
6016
6017   if (overridable)
6018     {
6019       /* Convert the expression to a procedure pointer component call.  */
6020       code->expr1->value.function.esym = NULL;
6021       code->expr1->symtree = st;
6022
6023       if (new_ref)
6024         code->expr1->ref = new_ref;
6025
6026       /* '_vptr' points to the vtab, which contains the procedure pointers.  */
6027       gfc_add_vptr_component (code->expr1);
6028       gfc_add_component_ref (code->expr1, name);
6029
6030       /* Recover the typespec for the expression.  This is really only
6031         necessary for generic procedures, where the additional call
6032         to gfc_add_component_ref seems to throw the collection of the
6033         correct typespec.  */
6034       code->expr1->ts = ts;
6035     }
6036
6037   return SUCCESS;
6038 }
6039
6040
6041 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
6042
6043 static gfc_try
6044 resolve_ppc_call (gfc_code* c)
6045 {
6046   gfc_component *comp;
6047   bool b;
6048
6049   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
6050   gcc_assert (b);
6051
6052   c->resolved_sym = c->expr1->symtree->n.sym;
6053   c->expr1->expr_type = EXPR_VARIABLE;
6054
6055   if (!comp->attr.subroutine)
6056     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
6057
6058   if (resolve_ref (c->expr1) == FAILURE)
6059     return FAILURE;
6060
6061   if (update_ppc_arglist (c->expr1) == FAILURE)
6062     return FAILURE;
6063
6064   c->ext.actual = c->expr1->value.compcall.actual;
6065
6066   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
6067                               comp->formal == NULL) == FAILURE)
6068     return FAILURE;
6069
6070   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
6071
6072   return SUCCESS;
6073 }
6074
6075
6076 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
6077
6078 static gfc_try
6079 resolve_expr_ppc (gfc_expr* e)
6080 {
6081   gfc_component *comp;
6082   bool b;
6083
6084   b = gfc_is_proc_ptr_comp (e, &comp);
6085   gcc_assert (b);
6086
6087   /* Convert to EXPR_FUNCTION.  */
6088   e->expr_type = EXPR_FUNCTION;
6089   e->value.function.isym = NULL;
6090   e->value.function.actual = e->value.compcall.actual;
6091   e->ts = comp->ts;
6092   if (comp->as != NULL)
6093     e->rank = comp->as->rank;
6094
6095   if (!comp->attr.function)
6096     gfc_add_function (&comp->attr, comp->name, &e->where);
6097
6098   if (resolve_ref (e) == FAILURE)
6099     return FAILURE;
6100
6101   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
6102                               comp->formal == NULL) == FAILURE)
6103     return FAILURE;
6104
6105   if (update_ppc_arglist (e) == FAILURE)
6106     return FAILURE;
6107
6108   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
6109
6110   return SUCCESS;
6111 }
6112
6113
6114 static bool
6115 gfc_is_expandable_expr (gfc_expr *e)
6116 {
6117   gfc_constructor *con;
6118
6119   if (e->expr_type == EXPR_ARRAY)
6120     {
6121       /* Traverse the constructor looking for variables that are flavor
6122          parameter.  Parameters must be expanded since they are fully used at
6123          compile time.  */
6124       con = gfc_constructor_first (e->value.constructor);
6125       for (; con; con = gfc_constructor_next (con))
6126         {
6127           if (con->expr->expr_type == EXPR_VARIABLE
6128               && con->expr->symtree
6129               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
6130               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
6131             return true;
6132           if (con->expr->expr_type == EXPR_ARRAY
6133               && gfc_is_expandable_expr (con->expr))
6134             return true;
6135         }
6136     }
6137
6138   return false;
6139 }
6140
6141 /* Resolve an expression.  That is, make sure that types of operands agree
6142    with their operators, intrinsic operators are converted to function calls
6143    for overloaded types and unresolved function references are resolved.  */
6144
6145 gfc_try
6146 gfc_resolve_expr (gfc_expr *e)
6147 {
6148   gfc_try t;
6149   bool inquiry_save;
6150
6151   if (e == NULL)
6152     return SUCCESS;
6153
6154   /* inquiry_argument only applies to variables.  */
6155   inquiry_save = inquiry_argument;
6156   if (e->expr_type != EXPR_VARIABLE)
6157     inquiry_argument = false;
6158
6159   switch (e->expr_type)
6160     {
6161     case EXPR_OP:
6162       t = resolve_operator (e);
6163       break;
6164
6165     case EXPR_FUNCTION:
6166     case EXPR_VARIABLE:
6167
6168       if (check_host_association (e))
6169         t = resolve_function (e);
6170       else
6171         {
6172           t = resolve_variable (e);
6173           if (t == SUCCESS)
6174             expression_rank (e);
6175         }
6176
6177       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6178           && e->ref->type != REF_SUBSTRING)
6179         gfc_resolve_substring_charlen (e);
6180
6181       break;
6182
6183     case EXPR_COMPCALL:
6184       t = resolve_typebound_function (e);
6185       break;
6186
6187     case EXPR_SUBSTRING:
6188       t = resolve_ref (e);
6189       break;
6190
6191     case EXPR_CONSTANT:
6192     case EXPR_NULL:
6193       t = SUCCESS;
6194       break;
6195
6196     case EXPR_PPC:
6197       t = resolve_expr_ppc (e);
6198       break;
6199
6200     case EXPR_ARRAY:
6201       t = FAILURE;
6202       if (resolve_ref (e) == FAILURE)
6203         break;
6204
6205       t = gfc_resolve_array_constructor (e);
6206       /* Also try to expand a constructor.  */
6207       if (t == SUCCESS)
6208         {
6209           expression_rank (e);
6210           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6211             gfc_expand_constructor (e, false);
6212         }
6213
6214       /* This provides the opportunity for the length of constructors with
6215          character valued function elements to propagate the string length
6216          to the expression.  */
6217       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
6218         {
6219           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6220              here rather then add a duplicate test for it above.  */ 
6221           gfc_expand_constructor (e, false);
6222           t = gfc_resolve_character_array_constructor (e);
6223         }
6224
6225       break;
6226
6227     case EXPR_STRUCTURE:
6228       t = resolve_ref (e);
6229       if (t == FAILURE)
6230         break;
6231
6232       t = resolve_structure_cons (e, 0);
6233       if (t == FAILURE)
6234         break;
6235
6236       t = gfc_simplify_expr (e, 0);
6237       break;
6238
6239     default:
6240       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6241     }
6242
6243   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
6244     fixup_charlen (e);
6245
6246   inquiry_argument = inquiry_save;
6247
6248   return t;
6249 }
6250
6251
6252 /* Resolve an expression from an iterator.  They must be scalar and have
6253    INTEGER or (optionally) REAL type.  */
6254
6255 static gfc_try
6256 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6257                            const char *name_msgid)
6258 {
6259   if (gfc_resolve_expr (expr) == FAILURE)
6260     return FAILURE;
6261
6262   if (expr->rank != 0)
6263     {
6264       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6265       return FAILURE;
6266     }
6267
6268   if (expr->ts.type != BT_INTEGER)
6269     {
6270       if (expr->ts.type == BT_REAL)
6271         {
6272           if (real_ok)
6273             return gfc_notify_std (GFC_STD_F95_DEL,
6274                                    "Deleted feature: %s at %L must be integer",
6275                                    _(name_msgid), &expr->where);
6276           else
6277             {
6278               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6279                          &expr->where);
6280               return FAILURE;
6281             }
6282         }
6283       else
6284         {
6285           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6286           return FAILURE;
6287         }
6288     }
6289   return SUCCESS;
6290 }
6291
6292
6293 /* Resolve the expressions in an iterator structure.  If REAL_OK is
6294    false allow only INTEGER type iterators, otherwise allow REAL types.  */
6295
6296 gfc_try
6297 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
6298 {
6299   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
6300       == FAILURE)
6301     return FAILURE;
6302
6303   if (gfc_check_vardef_context (iter->var, false, false, _("iterator variable"))
6304       == FAILURE)
6305     return FAILURE;
6306
6307   if (gfc_resolve_iterator_expr (iter->start, real_ok,
6308                                  "Start expression in DO loop") == FAILURE)
6309     return FAILURE;
6310
6311   if (gfc_resolve_iterator_expr (iter->end, real_ok,
6312                                  "End expression in DO loop") == FAILURE)
6313     return FAILURE;
6314
6315   if (gfc_resolve_iterator_expr (iter->step, real_ok,
6316                                  "Step expression in DO loop") == FAILURE)
6317     return FAILURE;
6318
6319   if (iter->step->expr_type == EXPR_CONSTANT)
6320     {
6321       if ((iter->step->ts.type == BT_INTEGER
6322            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6323           || (iter->step->ts.type == BT_REAL
6324               && mpfr_sgn (iter->step->value.real) == 0))
6325         {
6326           gfc_error ("Step expression in DO loop at %L cannot be zero",
6327                      &iter->step->where);
6328           return FAILURE;
6329         }
6330     }
6331
6332   /* Convert start, end, and step to the same type as var.  */
6333   if (iter->start->ts.kind != iter->var->ts.kind
6334       || iter->start->ts.type != iter->var->ts.type)
6335     gfc_convert_type (iter->start, &iter->var->ts, 2);
6336
6337   if (iter->end->ts.kind != iter->var->ts.kind
6338       || iter->end->ts.type != iter->var->ts.type)
6339     gfc_convert_type (iter->end, &iter->var->ts, 2);
6340
6341   if (iter->step->ts.kind != iter->var->ts.kind
6342       || iter->step->ts.type != iter->var->ts.type)
6343     gfc_convert_type (iter->step, &iter->var->ts, 2);
6344
6345   if (iter->start->expr_type == EXPR_CONSTANT
6346       && iter->end->expr_type == EXPR_CONSTANT
6347       && iter->step->expr_type == EXPR_CONSTANT)
6348     {
6349       int sgn, cmp;
6350       if (iter->start->ts.type == BT_INTEGER)
6351         {
6352           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6353           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6354         }
6355       else
6356         {
6357           sgn = mpfr_sgn (iter->step->value.real);
6358           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6359         }
6360       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
6361         gfc_warning ("DO loop at %L will be executed zero times",
6362                      &iter->step->where);
6363     }
6364
6365   return SUCCESS;
6366 }
6367
6368
6369 /* Traversal function for find_forall_index.  f == 2 signals that
6370    that variable itself is not to be checked - only the references.  */
6371
6372 static bool
6373 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6374 {
6375   if (expr->expr_type != EXPR_VARIABLE)
6376     return false;
6377   
6378   /* A scalar assignment  */
6379   if (!expr->ref || *f == 1)
6380     {
6381       if (expr->symtree->n.sym == sym)
6382         return true;
6383       else
6384         return false;
6385     }
6386
6387   if (*f == 2)
6388     *f = 1;
6389   return false;
6390 }
6391
6392
6393 /* Check whether the FORALL index appears in the expression or not.
6394    Returns SUCCESS if SYM is found in EXPR.  */
6395
6396 gfc_try
6397 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6398 {
6399   if (gfc_traverse_expr (expr, sym, forall_index, f))
6400     return SUCCESS;
6401   else
6402     return FAILURE;
6403 }
6404
6405
6406 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6407    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6408    INTEGERs, and if stride is a constant it must be nonzero.
6409    Furthermore "A subscript or stride in a forall-triplet-spec shall
6410    not contain a reference to any index-name in the
6411    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6412
6413 static void
6414 resolve_forall_iterators (gfc_forall_iterator *it)
6415 {
6416   gfc_forall_iterator *iter, *iter2;
6417
6418   for (iter = it; iter; iter = iter->next)
6419     {
6420       if (gfc_resolve_expr (iter->var) == SUCCESS
6421           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6422         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6423                    &iter->var->where);
6424
6425       if (gfc_resolve_expr (iter->start) == SUCCESS
6426           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6427         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6428                    &iter->start->where);
6429       if (iter->var->ts.kind != iter->start->ts.kind)
6430         gfc_convert_type (iter->start, &iter->var->ts, 2);
6431
6432       if (gfc_resolve_expr (iter->end) == SUCCESS
6433           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6434         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6435                    &iter->end->where);
6436       if (iter->var->ts.kind != iter->end->ts.kind)
6437         gfc_convert_type (iter->end, &iter->var->ts, 2);
6438
6439       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6440         {
6441           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6442             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6443                        &iter->stride->where, "INTEGER");
6444
6445           if (iter->stride->expr_type == EXPR_CONSTANT
6446               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6447             gfc_error ("FORALL stride expression at %L cannot be zero",
6448                        &iter->stride->where);
6449         }
6450       if (iter->var->ts.kind != iter->stride->ts.kind)
6451         gfc_convert_type (iter->stride, &iter->var->ts, 2);
6452     }
6453
6454   for (iter = it; iter; iter = iter->next)
6455     for (iter2 = iter; iter2; iter2 = iter2->next)
6456       {
6457         if (find_forall_index (iter2->start,
6458                                iter->var->symtree->n.sym, 0) == SUCCESS
6459             || find_forall_index (iter2->end,
6460                                   iter->var->symtree->n.sym, 0) == SUCCESS
6461             || find_forall_index (iter2->stride,
6462                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6463           gfc_error ("FORALL index '%s' may not appear in triplet "
6464                      "specification at %L", iter->var->symtree->name,
6465                      &iter2->start->where);
6466       }
6467 }
6468
6469
6470 /* Given a pointer to a symbol that is a derived type, see if it's
6471    inaccessible, i.e. if it's defined in another module and the components are
6472    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6473    inaccessible components are found, nonzero otherwise.  */
6474
6475 static int
6476 derived_inaccessible (gfc_symbol *sym)
6477 {
6478   gfc_component *c;
6479
6480   if (sym->attr.use_assoc && sym->attr.private_comp)
6481     return 1;
6482
6483   for (c = sym->components; c; c = c->next)
6484     {
6485         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6486           return 1;
6487     }
6488
6489   return 0;
6490 }
6491
6492
6493 /* Resolve the argument of a deallocate expression.  The expression must be
6494    a pointer or a full array.  */
6495
6496 static gfc_try
6497 resolve_deallocate_expr (gfc_expr *e)
6498 {
6499   symbol_attribute attr;
6500   int allocatable, pointer;
6501   gfc_ref *ref;
6502   gfc_symbol *sym;
6503   gfc_component *c;
6504
6505   if (gfc_resolve_expr (e) == FAILURE)
6506     return FAILURE;
6507
6508   if (e->expr_type != EXPR_VARIABLE)
6509     goto bad;
6510
6511   sym = e->symtree->n.sym;
6512
6513   if (sym->ts.type == BT_CLASS)
6514     {
6515       allocatable = CLASS_DATA (sym)->attr.allocatable;
6516       pointer = CLASS_DATA (sym)->attr.class_pointer;
6517     }
6518   else
6519     {
6520       allocatable = sym->attr.allocatable;
6521       pointer = sym->attr.pointer;
6522     }
6523   for (ref = e->ref; ref; ref = ref->next)
6524     {
6525       switch (ref->type)
6526         {
6527         case REF_ARRAY:
6528           if (ref->u.ar.type != AR_FULL
6529               && !(ref->u.ar.type == AR_ELEMENT && ref->u.ar.as->rank == 0
6530                    && ref->u.ar.codimen && gfc_ref_this_image (ref)))
6531             allocatable = 0;
6532           break;
6533
6534         case REF_COMPONENT:
6535           c = ref->u.c.component;
6536           if (c->ts.type == BT_CLASS)
6537             {
6538               allocatable = CLASS_DATA (c)->attr.allocatable;
6539               pointer = CLASS_DATA (c)->attr.class_pointer;
6540             }
6541           else
6542             {
6543               allocatable = c->attr.allocatable;
6544               pointer = c->attr.pointer;
6545             }
6546           break;
6547
6548         case REF_SUBSTRING:
6549           allocatable = 0;
6550           break;
6551         }
6552     }
6553
6554   attr = gfc_expr_attr (e);
6555
6556   if (allocatable == 0 && attr.pointer == 0)
6557     {
6558     bad:
6559       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6560                  &e->where);
6561       return FAILURE;
6562     }
6563
6564   /* F2008, C644.  */
6565   if (gfc_is_coindexed (e))
6566     {
6567       gfc_error ("Coindexed allocatable object at %L", &e->where);
6568       return FAILURE;
6569     }
6570
6571   if (pointer
6572       && gfc_check_vardef_context (e, true, true, _("DEALLOCATE object"))
6573          == FAILURE)
6574     return FAILURE;
6575   if (gfc_check_vardef_context (e, false, true, _("DEALLOCATE object"))
6576       == FAILURE)
6577     return FAILURE;
6578
6579   return SUCCESS;
6580 }
6581
6582
6583 /* Returns true if the expression e contains a reference to the symbol sym.  */
6584 static bool
6585 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6586 {
6587   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6588     return true;
6589
6590   return false;
6591 }
6592
6593 bool
6594 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6595 {
6596   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6597 }
6598
6599
6600 /* Given the expression node e for an allocatable/pointer of derived type to be
6601    allocated, get the expression node to be initialized afterwards (needed for
6602    derived types with default initializers, and derived types with allocatable
6603    components that need nullification.)  */
6604
6605 gfc_expr *
6606 gfc_expr_to_initialize (gfc_expr *e)
6607 {
6608   gfc_expr *result;
6609   gfc_ref *ref;
6610   int i;
6611
6612   result = gfc_copy_expr (e);
6613
6614   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6615   for (ref = result->ref; ref; ref = ref->next)
6616     if (ref->type == REF_ARRAY && ref->next == NULL)
6617       {
6618         ref->u.ar.type = AR_FULL;
6619
6620         for (i = 0; i < ref->u.ar.dimen; i++)
6621           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6622
6623         break;
6624       }
6625
6626   gfc_free_shape (&result->shape, result->rank);
6627
6628   /* Recalculate rank, shape, etc.  */
6629   gfc_resolve_expr (result);
6630   return result;
6631 }
6632
6633
6634 /* If the last ref of an expression is an array ref, return a copy of the
6635    expression with that one removed.  Otherwise, a copy of the original
6636    expression.  This is used for allocate-expressions and pointer assignment
6637    LHS, where there may be an array specification that needs to be stripped
6638    off when using gfc_check_vardef_context.  */
6639
6640 static gfc_expr*
6641 remove_last_array_ref (gfc_expr* e)
6642 {
6643   gfc_expr* e2;
6644   gfc_ref** r;
6645
6646   e2 = gfc_copy_expr (e);
6647   for (r = &e2->ref; *r; r = &(*r)->next)
6648     if ((*r)->type == REF_ARRAY && !(*r)->next)
6649       {
6650         gfc_free_ref_list (*r);
6651         *r = NULL;
6652         break;
6653       }
6654
6655   return e2;
6656 }
6657
6658
6659 /* Used in resolve_allocate_expr to check that a allocation-object and
6660    a source-expr are conformable.  This does not catch all possible 
6661    cases; in particular a runtime checking is needed.  */
6662
6663 static gfc_try
6664 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6665 {
6666   gfc_ref *tail;
6667   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6668   
6669   /* First compare rank.  */
6670   if (tail && e1->rank != tail->u.ar.as->rank)
6671     {
6672       gfc_error ("Source-expr at %L must be scalar or have the "
6673                  "same rank as the allocate-object at %L",
6674                  &e1->where, &e2->where);
6675       return FAILURE;
6676     }
6677
6678   if (e1->shape)
6679     {
6680       int i;
6681       mpz_t s;
6682
6683       mpz_init (s);
6684
6685       for (i = 0; i < e1->rank; i++)
6686         {
6687           if (tail->u.ar.end[i])
6688             {
6689               mpz_set (s, tail->u.ar.end[i]->value.integer);
6690               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6691               mpz_add_ui (s, s, 1);
6692             }
6693           else
6694             {
6695               mpz_set (s, tail->u.ar.start[i]->value.integer);
6696             }
6697
6698           if (mpz_cmp (e1->shape[i], s) != 0)
6699             {
6700               gfc_error ("Source-expr at %L and allocate-object at %L must "
6701                          "have the same shape", &e1->where, &e2->where);
6702               mpz_clear (s);
6703               return FAILURE;
6704             }
6705         }
6706
6707       mpz_clear (s);
6708     }
6709
6710   return SUCCESS;
6711 }
6712
6713
6714 /* Resolve the expression in an ALLOCATE statement, doing the additional
6715    checks to see whether the expression is OK or not.  The expression must
6716    have a trailing array reference that gives the size of the array.  */
6717
6718 static gfc_try
6719 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6720 {
6721   int i, pointer, allocatable, dimension, is_abstract;
6722   int codimension;
6723   bool coindexed;
6724   symbol_attribute attr;
6725   gfc_ref *ref, *ref2;
6726   gfc_expr *e2;
6727   gfc_array_ref *ar;
6728   gfc_symbol *sym = NULL;
6729   gfc_alloc *a;
6730   gfc_component *c;
6731   gfc_try t;
6732
6733   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6734      checking of coarrays.  */
6735   for (ref = e->ref; ref; ref = ref->next)
6736     if (ref->next == NULL)
6737       break;
6738
6739   if (ref && ref->type == REF_ARRAY)
6740     ref->u.ar.in_allocate = true;
6741
6742   if (gfc_resolve_expr (e) == FAILURE)
6743     goto failure;
6744
6745   /* Make sure the expression is allocatable or a pointer.  If it is
6746      pointer, the next-to-last reference must be a pointer.  */
6747
6748   ref2 = NULL;
6749   if (e->symtree)
6750     sym = e->symtree->n.sym;
6751
6752   /* Check whether ultimate component is abstract and CLASS.  */
6753   is_abstract = 0;
6754
6755   if (e->expr_type != EXPR_VARIABLE)
6756     {
6757       allocatable = 0;
6758       attr = gfc_expr_attr (e);
6759       pointer = attr.pointer;
6760       dimension = attr.dimension;
6761       codimension = attr.codimension;
6762     }
6763   else
6764     {
6765       if (sym->ts.type == BT_CLASS)
6766         {
6767           allocatable = CLASS_DATA (sym)->attr.allocatable;
6768           pointer = CLASS_DATA (sym)->attr.class_pointer;
6769           dimension = CLASS_DATA (sym)->attr.dimension;
6770           codimension = CLASS_DATA (sym)->attr.codimension;
6771           is_abstract = CLASS_DATA (sym)->attr.abstract;
6772         }
6773       else
6774         {
6775           allocatable = sym->attr.allocatable;
6776           pointer = sym->attr.pointer;
6777           dimension = sym->attr.dimension;
6778           codimension = sym->attr.codimension;
6779         }
6780
6781       coindexed = false;
6782
6783       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6784         {
6785           switch (ref->type)
6786             {
6787               case REF_ARRAY:
6788                 if (ref->u.ar.codimen > 0)
6789                   {
6790                     int n;
6791                     for (n = ref->u.ar.dimen;
6792                          n < ref->u.ar.dimen + ref->u.ar.codimen; n++)
6793                       if (ref->u.ar.dimen_type[n] != DIMEN_THIS_IMAGE)
6794                         {
6795                           coindexed = true;
6796                           break;
6797                         }
6798                    }
6799
6800                 if (ref->next != NULL)
6801                   pointer = 0;
6802                 break;
6803
6804               case REF_COMPONENT:
6805                 /* F2008, C644.  */
6806                 if (coindexed)
6807                   {
6808                     gfc_error ("Coindexed allocatable object at %L",
6809                                &e->where);
6810                     goto failure;
6811                   }
6812
6813                 c = ref->u.c.component;
6814                 if (c->ts.type == BT_CLASS)
6815                   {
6816                     allocatable = CLASS_DATA (c)->attr.allocatable;
6817                     pointer = CLASS_DATA (c)->attr.class_pointer;
6818                     dimension = CLASS_DATA (c)->attr.dimension;
6819                     codimension = CLASS_DATA (c)->attr.codimension;
6820                     is_abstract = CLASS_DATA (c)->attr.abstract;
6821                   }
6822                 else
6823                   {
6824                     allocatable = c->attr.allocatable;
6825                     pointer = c->attr.pointer;
6826                     dimension = c->attr.dimension;
6827                     codimension = c->attr.codimension;
6828                     is_abstract = c->attr.abstract;
6829                   }
6830                 break;
6831
6832               case REF_SUBSTRING:
6833                 allocatable = 0;
6834                 pointer = 0;
6835                 break;
6836             }
6837         }
6838     }
6839
6840   if (allocatable == 0 && pointer == 0)
6841     {
6842       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6843                  &e->where);
6844       goto failure;
6845     }
6846
6847   /* Some checks for the SOURCE tag.  */
6848   if (code->expr3)
6849     {
6850       /* Check F03:C631.  */
6851       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6852         {
6853           gfc_error ("Type of entity at %L is type incompatible with "
6854                       "source-expr at %L", &e->where, &code->expr3->where);
6855           goto failure;
6856         }
6857
6858       /* Check F03:C632 and restriction following Note 6.18.  */
6859       if (code->expr3->rank > 0
6860           && conformable_arrays (code->expr3, e) == FAILURE)
6861         goto failure;
6862
6863       /* Check F03:C633.  */
6864       if (code->expr3->ts.kind != e->ts.kind)
6865         {
6866           gfc_error ("The allocate-object at %L and the source-expr at %L "
6867                       "shall have the same kind type parameter",
6868                       &e->where, &code->expr3->where);
6869           goto failure;
6870         }
6871
6872       /* Check F2008, C642.  */
6873       if (code->expr3->ts.type == BT_DERIVED
6874           && ((codimension && gfc_expr_attr (code->expr3).lock_comp)
6875               || (code->expr3->ts.u.derived->from_intmod
6876                      == INTMOD_ISO_FORTRAN_ENV
6877                   && code->expr3->ts.u.derived->intmod_sym_id
6878                      == ISOFORTRAN_LOCK_TYPE)))
6879         {
6880           gfc_error ("The source-expr at %L shall neither be of type "
6881                      "LOCK_TYPE nor have a LOCK_TYPE component if "
6882                       "allocate-object at %L is a coarray",
6883                       &code->expr3->where, &e->where);
6884           goto failure;
6885         }
6886     }
6887
6888   /* Check F08:C629.  */
6889   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
6890       && !code->expr3)
6891     {
6892       gcc_assert (e->ts.type == BT_CLASS);
6893       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6894                  "type-spec or source-expr", sym->name, &e->where);
6895       goto failure;
6896     }
6897
6898   /* In the variable definition context checks, gfc_expr_attr is used
6899      on the expression.  This is fooled by the array specification
6900      present in e, thus we have to eliminate that one temporarily.  */
6901   e2 = remove_last_array_ref (e);
6902   t = SUCCESS;
6903   if (t == SUCCESS && pointer)
6904     t = gfc_check_vardef_context (e2, true, true, _("ALLOCATE object"));
6905   if (t == SUCCESS)
6906     t = gfc_check_vardef_context (e2, false, true, _("ALLOCATE object"));
6907   gfc_free_expr (e2);
6908   if (t == FAILURE)
6909     goto failure;
6910
6911   if (!code->expr3)
6912     {
6913       /* Set up default initializer if needed.  */
6914       gfc_typespec ts;
6915       gfc_expr *init_e;
6916
6917       if (code->ext.alloc.ts.type == BT_DERIVED)
6918         ts = code->ext.alloc.ts;
6919       else
6920         ts = e->ts;
6921
6922       if (ts.type == BT_CLASS)
6923         ts = ts.u.derived->components->ts;
6924
6925       if (ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&ts)))
6926         {
6927           gfc_code *init_st = gfc_get_code ();
6928           init_st->loc = code->loc;
6929           init_st->op = EXEC_INIT_ASSIGN;
6930           init_st->expr1 = gfc_expr_to_initialize (e);
6931           init_st->expr2 = init_e;
6932           init_st->next = code->next;
6933           code->next = init_st;
6934         }
6935     }
6936   else if (code->expr3->mold && code->expr3->ts.type == BT_DERIVED)
6937     {
6938       /* Default initialization via MOLD (non-polymorphic).  */
6939       gfc_expr *rhs = gfc_default_initializer (&code->expr3->ts);
6940       gfc_resolve_expr (rhs);
6941       gfc_free_expr (code->expr3);
6942       code->expr3 = rhs;
6943     }
6944
6945   if (e->ts.type == BT_CLASS)
6946     {
6947       /* Make sure the vtab symbol is present when
6948          the module variables are generated.  */
6949       gfc_typespec ts = e->ts;
6950       if (code->expr3)
6951         ts = code->expr3->ts;
6952       else if (code->ext.alloc.ts.type == BT_DERIVED)
6953         ts = code->ext.alloc.ts;
6954       gfc_find_derived_vtab (ts.u.derived);
6955     }
6956
6957   if (dimension == 0 && codimension == 0)
6958     goto success;
6959
6960   /* Make sure the last reference node is an array specifiction.  */
6961
6962   if (!ref2 || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
6963       || (dimension && ref2->u.ar.dimen == 0))
6964     {
6965       gfc_error ("Array specification required in ALLOCATE statement "
6966                  "at %L", &e->where);
6967       goto failure;
6968     }
6969
6970   /* Make sure that the array section reference makes sense in the
6971     context of an ALLOCATE specification.  */
6972
6973   ar = &ref2->u.ar;
6974
6975   if (codimension)
6976     for (i = ar->dimen; i < ar->dimen + ar->codimen; i++)
6977       if (ar->dimen_type[i] == DIMEN_THIS_IMAGE)
6978         {
6979           gfc_error ("Coarray specification required in ALLOCATE statement "
6980                      "at %L", &e->where);
6981           goto failure;
6982         }
6983
6984   for (i = 0; i < ar->dimen; i++)
6985     {
6986       if (ref2->u.ar.type == AR_ELEMENT)
6987         goto check_symbols;
6988
6989       switch (ar->dimen_type[i])
6990         {
6991         case DIMEN_ELEMENT:
6992           break;
6993
6994         case DIMEN_RANGE:
6995           if (ar->start[i] != NULL
6996               && ar->end[i] != NULL
6997               && ar->stride[i] == NULL)
6998             break;
6999
7000           /* Fall Through...  */
7001
7002         case DIMEN_UNKNOWN:
7003         case DIMEN_VECTOR:
7004         case DIMEN_STAR:
7005         case DIMEN_THIS_IMAGE:
7006           gfc_error ("Bad array specification in ALLOCATE statement at %L",
7007                      &e->where);
7008           goto failure;
7009         }
7010
7011 check_symbols:
7012       for (a = code->ext.alloc.list; a; a = a->next)
7013         {
7014           sym = a->expr->symtree->n.sym;
7015
7016           /* TODO - check derived type components.  */
7017           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
7018             continue;
7019
7020           if ((ar->start[i] != NULL
7021                && gfc_find_sym_in_expr (sym, ar->start[i]))
7022               || (ar->end[i] != NULL
7023                   && gfc_find_sym_in_expr (sym, ar->end[i])))
7024             {
7025               gfc_error ("'%s' must not appear in the array specification at "
7026                          "%L in the same ALLOCATE statement where it is "
7027                          "itself allocated", sym->name, &ar->where);
7028               goto failure;
7029             }
7030         }
7031     }
7032
7033   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
7034     {
7035       if (ar->dimen_type[i] == DIMEN_ELEMENT
7036           || ar->dimen_type[i] == DIMEN_RANGE)
7037         {
7038           if (i == (ar->dimen + ar->codimen - 1))
7039             {
7040               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
7041                          "statement at %L", &e->where);
7042               goto failure;
7043             }
7044           break;
7045         }
7046
7047       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
7048           && ar->stride[i] == NULL)
7049         break;
7050
7051       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
7052                  &e->where);
7053       goto failure;
7054     }
7055
7056 success:
7057   return SUCCESS;
7058
7059 failure:
7060   return FAILURE;
7061 }
7062
7063 static void
7064 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
7065 {
7066   gfc_expr *stat, *errmsg, *pe, *qe;
7067   gfc_alloc *a, *p, *q;
7068
7069   stat = code->expr1;
7070   errmsg = code->expr2;
7071
7072   /* Check the stat variable.  */
7073   if (stat)
7074     {
7075       gfc_check_vardef_context (stat, false, false, _("STAT variable"));
7076
7077       if ((stat->ts.type != BT_INTEGER
7078            && !(stat->ref && (stat->ref->type == REF_ARRAY
7079                               || stat->ref->type == REF_COMPONENT)))
7080           || stat->rank > 0)
7081         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
7082                    "variable", &stat->where);
7083
7084       for (p = code->ext.alloc.list; p; p = p->next)
7085         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
7086           {
7087             gfc_ref *ref1, *ref2;
7088             bool found = true;
7089
7090             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
7091                  ref1 = ref1->next, ref2 = ref2->next)
7092               {
7093                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7094                   continue;
7095                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7096                   {
7097                     found = false;
7098                     break;
7099                   }
7100               }
7101
7102             if (found)
7103               {
7104                 gfc_error ("Stat-variable at %L shall not be %sd within "
7105                            "the same %s statement", &stat->where, fcn, fcn);
7106                 break;
7107               }
7108           }
7109     }
7110
7111   /* Check the errmsg variable.  */
7112   if (errmsg)
7113     {
7114       if (!stat)
7115         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
7116                      &errmsg->where);
7117
7118       gfc_check_vardef_context (errmsg, false, false, _("ERRMSG variable"));
7119
7120       if ((errmsg->ts.type != BT_CHARACTER
7121            && !(errmsg->ref
7122                 && (errmsg->ref->type == REF_ARRAY
7123                     || errmsg->ref->type == REF_COMPONENT)))
7124           || errmsg->rank > 0 )
7125         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
7126                    "variable", &errmsg->where);
7127
7128       for (p = code->ext.alloc.list; p; p = p->next)
7129         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
7130           {
7131             gfc_ref *ref1, *ref2;
7132             bool found = true;
7133
7134             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
7135                  ref1 = ref1->next, ref2 = ref2->next)
7136               {
7137                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7138                   continue;
7139                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7140                   {
7141                     found = false;
7142                     break;
7143                   }
7144               }
7145
7146             if (found)
7147               {
7148                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
7149                            "the same %s statement", &errmsg->where, fcn, fcn);
7150                 break;
7151               }
7152           }
7153     }
7154
7155   /* Check that an allocate-object appears only once in the statement.  
7156      FIXME: Checking derived types is disabled.  */
7157   for (p = code->ext.alloc.list; p; p = p->next)
7158     {
7159       pe = p->expr;
7160       for (q = p->next; q; q = q->next)
7161         {
7162           qe = q->expr;
7163           if (pe->symtree->n.sym->name == qe->symtree->n.sym->name)
7164             {
7165               /* This is a potential collision.  */
7166               gfc_ref *pr = pe->ref;
7167               gfc_ref *qr = qe->ref;
7168               
7169               /* Follow the references  until
7170                  a) They start to differ, in which case there is no error;
7171                  you can deallocate a%b and a%c in a single statement
7172                  b) Both of them stop, which is an error
7173                  c) One of them stops, which is also an error.  */
7174               while (1)
7175                 {
7176                   if (pr == NULL && qr == NULL)
7177                     {
7178                       gfc_error ("Allocate-object at %L also appears at %L",
7179                                  &pe->where, &qe->where);
7180                       break;
7181                     }
7182                   else if (pr != NULL && qr == NULL)
7183                     {
7184                       gfc_error ("Allocate-object at %L is subobject of"
7185                                  " object at %L", &pe->where, &qe->where);
7186                       break;
7187                     }
7188                   else if (pr == NULL && qr != NULL)
7189                     {
7190                       gfc_error ("Allocate-object at %L is subobject of"
7191                                  " object at %L", &qe->where, &pe->where);
7192                       break;
7193                     }
7194                   /* Here, pr != NULL && qr != NULL  */
7195                   gcc_assert(pr->type == qr->type);
7196                   if (pr->type == REF_ARRAY)
7197                     {
7198                       /* Handle cases like allocate(v(3)%x(3), v(2)%x(3)),
7199                          which are legal.  */
7200                       gcc_assert (qr->type == REF_ARRAY);
7201
7202                       if (pr->next && qr->next)
7203                         {
7204                           gfc_array_ref *par = &(pr->u.ar);
7205                           gfc_array_ref *qar = &(qr->u.ar);
7206                           if (gfc_dep_compare_expr (par->start[0],
7207                                                     qar->start[0]) != 0)
7208                               break;
7209                         }
7210                     }
7211                   else
7212                     {
7213                       if (pr->u.c.component->name != qr->u.c.component->name)
7214                         break;
7215                     }
7216                   
7217                   pr = pr->next;
7218                   qr = qr->next;
7219                 }
7220             }
7221         }
7222     }
7223
7224   if (strcmp (fcn, "ALLOCATE") == 0)
7225     {
7226       for (a = code->ext.alloc.list; a; a = a->next)
7227         resolve_allocate_expr (a->expr, code);
7228     }
7229   else
7230     {
7231       for (a = code->ext.alloc.list; a; a = a->next)
7232         resolve_deallocate_expr (a->expr);
7233     }
7234 }
7235
7236
7237 /************ SELECT CASE resolution subroutines ************/
7238
7239 /* Callback function for our mergesort variant.  Determines interval
7240    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7241    op1 > op2.  Assumes we're not dealing with the default case.  
7242    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7243    There are nine situations to check.  */
7244
7245 static int
7246 compare_cases (const gfc_case *op1, const gfc_case *op2)
7247 {
7248   int retval;
7249
7250   if (op1->low == NULL) /* op1 = (:L)  */
7251     {
7252       /* op2 = (:N), so overlap.  */
7253       retval = 0;
7254       /* op2 = (M:) or (M:N),  L < M  */
7255       if (op2->low != NULL
7256           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7257         retval = -1;
7258     }
7259   else if (op1->high == NULL) /* op1 = (K:)  */
7260     {
7261       /* op2 = (M:), so overlap.  */
7262       retval = 0;
7263       /* op2 = (:N) or (M:N), K > N  */
7264       if (op2->high != NULL
7265           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7266         retval = 1;
7267     }
7268   else /* op1 = (K:L)  */
7269     {
7270       if (op2->low == NULL)       /* op2 = (:N), K > N  */
7271         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7272                  ? 1 : 0;
7273       else if (op2->high == NULL) /* op2 = (M:), L < M  */
7274         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7275                  ? -1 : 0;
7276       else                      /* op2 = (M:N)  */
7277         {
7278           retval =  0;
7279           /* L < M  */
7280           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7281             retval =  -1;
7282           /* K > N  */
7283           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7284             retval =  1;
7285         }
7286     }
7287
7288   return retval;
7289 }
7290
7291
7292 /* Merge-sort a double linked case list, detecting overlap in the
7293    process.  LIST is the head of the double linked case list before it
7294    is sorted.  Returns the head of the sorted list if we don't see any
7295    overlap, or NULL otherwise.  */
7296
7297 static gfc_case *
7298 check_case_overlap (gfc_case *list)
7299 {
7300   gfc_case *p, *q, *e, *tail;
7301   int insize, nmerges, psize, qsize, cmp, overlap_seen;
7302
7303   /* If the passed list was empty, return immediately.  */
7304   if (!list)
7305     return NULL;
7306
7307   overlap_seen = 0;
7308   insize = 1;
7309
7310   /* Loop unconditionally.  The only exit from this loop is a return
7311      statement, when we've finished sorting the case list.  */
7312   for (;;)
7313     {
7314       p = list;
7315       list = NULL;
7316       tail = NULL;
7317
7318       /* Count the number of merges we do in this pass.  */
7319       nmerges = 0;
7320
7321       /* Loop while there exists a merge to be done.  */
7322       while (p)
7323         {
7324           int i;
7325
7326           /* Count this merge.  */
7327           nmerges++;
7328
7329           /* Cut the list in two pieces by stepping INSIZE places
7330              forward in the list, starting from P.  */
7331           psize = 0;
7332           q = p;
7333           for (i = 0; i < insize; i++)
7334             {
7335               psize++;
7336               q = q->right;
7337               if (!q)
7338                 break;
7339             }
7340           qsize = insize;
7341
7342           /* Now we have two lists.  Merge them!  */
7343           while (psize > 0 || (qsize > 0 && q != NULL))
7344             {
7345               /* See from which the next case to merge comes from.  */
7346               if (psize == 0)
7347                 {
7348                   /* P is empty so the next case must come from Q.  */
7349                   e = q;
7350                   q = q->right;
7351                   qsize--;
7352                 }
7353               else if (qsize == 0 || q == NULL)
7354                 {
7355                   /* Q is empty.  */
7356                   e = p;
7357                   p = p->right;
7358                   psize--;
7359                 }
7360               else
7361                 {
7362                   cmp = compare_cases (p, q);
7363                   if (cmp < 0)
7364                     {
7365                       /* The whole case range for P is less than the
7366                          one for Q.  */
7367                       e = p;
7368                       p = p->right;
7369                       psize--;
7370                     }
7371                   else if (cmp > 0)
7372                     {
7373                       /* The whole case range for Q is greater than
7374                          the case range for P.  */
7375                       e = q;
7376                       q = q->right;
7377                       qsize--;
7378                     }
7379                   else
7380                     {
7381                       /* The cases overlap, or they are the same
7382                          element in the list.  Either way, we must
7383                          issue an error and get the next case from P.  */
7384                       /* FIXME: Sort P and Q by line number.  */
7385                       gfc_error ("CASE label at %L overlaps with CASE "
7386                                  "label at %L", &p->where, &q->where);
7387                       overlap_seen = 1;
7388                       e = p;
7389                       p = p->right;
7390                       psize--;
7391                     }
7392                 }
7393
7394                 /* Add the next element to the merged list.  */
7395               if (tail)
7396                 tail->right = e;
7397               else
7398                 list = e;
7399               e->left = tail;
7400               tail = e;
7401             }
7402
7403           /* P has now stepped INSIZE places along, and so has Q.  So
7404              they're the same.  */
7405           p = q;
7406         }
7407       tail->right = NULL;
7408
7409       /* If we have done only one merge or none at all, we've
7410          finished sorting the cases.  */
7411       if (nmerges <= 1)
7412         {
7413           if (!overlap_seen)
7414             return list;
7415           else
7416             return NULL;
7417         }
7418
7419       /* Otherwise repeat, merging lists twice the size.  */
7420       insize *= 2;
7421     }
7422 }
7423
7424
7425 /* Check to see if an expression is suitable for use in a CASE statement.
7426    Makes sure that all case expressions are scalar constants of the same
7427    type.  Return FAILURE if anything is wrong.  */
7428
7429 static gfc_try
7430 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7431 {
7432   if (e == NULL) return SUCCESS;
7433
7434   if (e->ts.type != case_expr->ts.type)
7435     {
7436       gfc_error ("Expression in CASE statement at %L must be of type %s",
7437                  &e->where, gfc_basic_typename (case_expr->ts.type));
7438       return FAILURE;
7439     }
7440
7441   /* C805 (R808) For a given case-construct, each case-value shall be of
7442      the same type as case-expr.  For character type, length differences
7443      are allowed, but the kind type parameters shall be the same.  */
7444
7445   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7446     {
7447       gfc_error ("Expression in CASE statement at %L must be of kind %d",
7448                  &e->where, case_expr->ts.kind);
7449       return FAILURE;
7450     }
7451
7452   /* Convert the case value kind to that of case expression kind,
7453      if needed */
7454
7455   if (e->ts.kind != case_expr->ts.kind)
7456     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7457
7458   if (e->rank != 0)
7459     {
7460       gfc_error ("Expression in CASE statement at %L must be scalar",
7461                  &e->where);
7462       return FAILURE;
7463     }
7464
7465   return SUCCESS;
7466 }
7467
7468
7469 /* Given a completely parsed select statement, we:
7470
7471      - Validate all expressions and code within the SELECT.
7472      - Make sure that the selection expression is not of the wrong type.
7473      - Make sure that no case ranges overlap.
7474      - Eliminate unreachable cases and unreachable code resulting from
7475        removing case labels.
7476
7477    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7478    they are a hassle for code generation, and to prevent that, we just
7479    cut them out here.  This is not necessary for overlapping cases
7480    because they are illegal and we never even try to generate code.
7481
7482    We have the additional caveat that a SELECT construct could have
7483    been a computed GOTO in the source code. Fortunately we can fairly
7484    easily work around that here: The case_expr for a "real" SELECT CASE
7485    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7486    we have to do is make sure that the case_expr is a scalar integer
7487    expression.  */
7488
7489 static void
7490 resolve_select (gfc_code *code)
7491 {
7492   gfc_code *body;
7493   gfc_expr *case_expr;
7494   gfc_case *cp, *default_case, *tail, *head;
7495   int seen_unreachable;
7496   int seen_logical;
7497   int ncases;
7498   bt type;
7499   gfc_try t;
7500
7501   if (code->expr1 == NULL)
7502     {
7503       /* This was actually a computed GOTO statement.  */
7504       case_expr = code->expr2;
7505       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7506         gfc_error ("Selection expression in computed GOTO statement "
7507                    "at %L must be a scalar integer expression",
7508                    &case_expr->where);
7509
7510       /* Further checking is not necessary because this SELECT was built
7511          by the compiler, so it should always be OK.  Just move the
7512          case_expr from expr2 to expr so that we can handle computed
7513          GOTOs as normal SELECTs from here on.  */
7514       code->expr1 = code->expr2;
7515       code->expr2 = NULL;
7516       return;
7517     }
7518
7519   case_expr = code->expr1;
7520
7521   type = case_expr->ts.type;
7522   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7523     {
7524       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7525                  &case_expr->where, gfc_typename (&case_expr->ts));
7526
7527       /* Punt. Going on here just produce more garbage error messages.  */
7528       return;
7529     }
7530
7531   if (case_expr->rank != 0)
7532     {
7533       gfc_error ("Argument of SELECT statement at %L must be a scalar "
7534                  "expression", &case_expr->where);
7535
7536       /* Punt.  */
7537       return;
7538     }
7539
7540
7541   /* Raise a warning if an INTEGER case value exceeds the range of
7542      the case-expr. Later, all expressions will be promoted to the
7543      largest kind of all case-labels.  */
7544
7545   if (type == BT_INTEGER)
7546     for (body = code->block; body; body = body->block)
7547       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7548         {
7549           if (cp->low
7550               && gfc_check_integer_range (cp->low->value.integer,
7551                                           case_expr->ts.kind) != ARITH_OK)
7552             gfc_warning ("Expression in CASE statement at %L is "
7553                          "not in the range of %s", &cp->low->where,
7554                          gfc_typename (&case_expr->ts));
7555
7556           if (cp->high
7557               && cp->low != cp->high
7558               && gfc_check_integer_range (cp->high->value.integer,
7559                                           case_expr->ts.kind) != ARITH_OK)
7560             gfc_warning ("Expression in CASE statement at %L is "
7561                          "not in the range of %s", &cp->high->where,
7562                          gfc_typename (&case_expr->ts));
7563         }
7564
7565   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7566      of the SELECT CASE expression and its CASE values.  Walk the lists
7567      of case values, and if we find a mismatch, promote case_expr to
7568      the appropriate kind.  */
7569
7570   if (type == BT_LOGICAL || type == BT_INTEGER)
7571     {
7572       for (body = code->block; body; body = body->block)
7573         {
7574           /* Walk the case label list.  */
7575           for (cp = body->ext.block.case_list; cp; cp = cp->next)
7576             {
7577               /* Intercept the DEFAULT case.  It does not have a kind.  */
7578               if (cp->low == NULL && cp->high == NULL)
7579                 continue;
7580
7581               /* Unreachable case ranges are discarded, so ignore.  */
7582               if (cp->low != NULL && cp->high != NULL
7583                   && cp->low != cp->high
7584                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7585                 continue;
7586
7587               if (cp->low != NULL
7588                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7589                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7590
7591               if (cp->high != NULL
7592                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7593                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7594             }
7595          }
7596     }
7597
7598   /* Assume there is no DEFAULT case.  */
7599   default_case = NULL;
7600   head = tail = NULL;
7601   ncases = 0;
7602   seen_logical = 0;
7603
7604   for (body = code->block; body; body = body->block)
7605     {
7606       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7607       t = SUCCESS;
7608       seen_unreachable = 0;
7609
7610       /* Walk the case label list, making sure that all case labels
7611          are legal.  */
7612       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7613         {
7614           /* Count the number of cases in the whole construct.  */
7615           ncases++;
7616
7617           /* Intercept the DEFAULT case.  */
7618           if (cp->low == NULL && cp->high == NULL)
7619             {
7620               if (default_case != NULL)
7621                 {
7622                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7623                              "by a second DEFAULT CASE at %L",
7624                              &default_case->where, &cp->where);
7625                   t = FAILURE;
7626                   break;
7627                 }
7628               else
7629                 {
7630                   default_case = cp;
7631                   continue;
7632                 }
7633             }
7634
7635           /* Deal with single value cases and case ranges.  Errors are
7636              issued from the validation function.  */
7637           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7638               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7639             {
7640               t = FAILURE;
7641               break;
7642             }
7643
7644           if (type == BT_LOGICAL
7645               && ((cp->low == NULL || cp->high == NULL)
7646                   || cp->low != cp->high))
7647             {
7648               gfc_error ("Logical range in CASE statement at %L is not "
7649                          "allowed", &cp->low->where);
7650               t = FAILURE;
7651               break;
7652             }
7653
7654           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7655             {
7656               int value;
7657               value = cp->low->value.logical == 0 ? 2 : 1;
7658               if (value & seen_logical)
7659                 {
7660                   gfc_error ("Constant logical value in CASE statement "
7661                              "is repeated at %L",
7662                              &cp->low->where);
7663                   t = FAILURE;
7664                   break;
7665                 }
7666               seen_logical |= value;
7667             }
7668
7669           if (cp->low != NULL && cp->high != NULL
7670               && cp->low != cp->high
7671               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7672             {
7673               if (gfc_option.warn_surprising)
7674                 gfc_warning ("Range specification at %L can never "
7675                              "be matched", &cp->where);
7676
7677               cp->unreachable = 1;
7678               seen_unreachable = 1;
7679             }
7680           else
7681             {
7682               /* If the case range can be matched, it can also overlap with
7683                  other cases.  To make sure it does not, we put it in a
7684                  double linked list here.  We sort that with a merge sort
7685                  later on to detect any overlapping cases.  */
7686               if (!head)
7687                 {
7688                   head = tail = cp;
7689                   head->right = head->left = NULL;
7690                 }
7691               else
7692                 {
7693                   tail->right = cp;
7694                   tail->right->left = tail;
7695                   tail = tail->right;
7696                   tail->right = NULL;
7697                 }
7698             }
7699         }
7700
7701       /* It there was a failure in the previous case label, give up
7702          for this case label list.  Continue with the next block.  */
7703       if (t == FAILURE)
7704         continue;
7705
7706       /* See if any case labels that are unreachable have been seen.
7707          If so, we eliminate them.  This is a bit of a kludge because
7708          the case lists for a single case statement (label) is a
7709          single forward linked lists.  */
7710       if (seen_unreachable)
7711       {
7712         /* Advance until the first case in the list is reachable.  */
7713         while (body->ext.block.case_list != NULL
7714                && body->ext.block.case_list->unreachable)
7715           {
7716             gfc_case *n = body->ext.block.case_list;
7717             body->ext.block.case_list = body->ext.block.case_list->next;
7718             n->next = NULL;
7719             gfc_free_case_list (n);
7720           }
7721
7722         /* Strip all other unreachable cases.  */
7723         if (body->ext.block.case_list)
7724           {
7725             for (cp = body->ext.block.case_list; cp->next; cp = cp->next)
7726               {
7727                 if (cp->next->unreachable)
7728                   {
7729                     gfc_case *n = cp->next;
7730                     cp->next = cp->next->next;
7731                     n->next = NULL;
7732                     gfc_free_case_list (n);
7733                   }
7734               }
7735           }
7736       }
7737     }
7738
7739   /* See if there were overlapping cases.  If the check returns NULL,
7740      there was overlap.  In that case we don't do anything.  If head
7741      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7742      then used during code generation for SELECT CASE constructs with
7743      a case expression of a CHARACTER type.  */
7744   if (head)
7745     {
7746       head = check_case_overlap (head);
7747
7748       /* Prepend the default_case if it is there.  */
7749       if (head != NULL && default_case)
7750         {
7751           default_case->left = NULL;
7752           default_case->right = head;
7753           head->left = default_case;
7754         }
7755     }
7756
7757   /* Eliminate dead blocks that may be the result if we've seen
7758      unreachable case labels for a block.  */
7759   for (body = code; body && body->block; body = body->block)
7760     {
7761       if (body->block->ext.block.case_list == NULL)
7762         {
7763           /* Cut the unreachable block from the code chain.  */
7764           gfc_code *c = body->block;
7765           body->block = c->block;
7766
7767           /* Kill the dead block, but not the blocks below it.  */
7768           c->block = NULL;
7769           gfc_free_statements (c);
7770         }
7771     }
7772
7773   /* More than two cases is legal but insane for logical selects.
7774      Issue a warning for it.  */
7775   if (gfc_option.warn_surprising && type == BT_LOGICAL
7776       && ncases > 2)
7777     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7778                  &code->loc);
7779 }
7780
7781
7782 /* Check if a derived type is extensible.  */
7783
7784 bool
7785 gfc_type_is_extensible (gfc_symbol *sym)
7786 {
7787   return !(sym->attr.is_bind_c || sym->attr.sequence);
7788 }
7789
7790
7791 /* Resolve an associate name:  Resolve target and ensure the type-spec is
7792    correct as well as possibly the array-spec.  */
7793
7794 static void
7795 resolve_assoc_var (gfc_symbol* sym, bool resolve_target)
7796 {
7797   gfc_expr* target;
7798
7799   gcc_assert (sym->assoc);
7800   gcc_assert (sym->attr.flavor == FL_VARIABLE);
7801
7802   /* If this is for SELECT TYPE, the target may not yet be set.  In that
7803      case, return.  Resolution will be called later manually again when
7804      this is done.  */
7805   target = sym->assoc->target;
7806   if (!target)
7807     return;
7808   gcc_assert (!sym->assoc->dangling);
7809
7810   if (resolve_target && gfc_resolve_expr (target) != SUCCESS)
7811     return;
7812
7813   /* For variable targets, we get some attributes from the target.  */
7814   if (target->expr_type == EXPR_VARIABLE)
7815     {
7816       gfc_symbol* tsym;
7817
7818       gcc_assert (target->symtree);
7819       tsym = target->symtree->n.sym;
7820
7821       sym->attr.asynchronous = tsym->attr.asynchronous;
7822       sym->attr.volatile_ = tsym->attr.volatile_;
7823
7824       sym->attr.target = (tsym->attr.target || tsym->attr.pointer);
7825     }
7826
7827   /* Get type if this was not already set.  Note that it can be
7828      some other type than the target in case this is a SELECT TYPE
7829      selector!  So we must not update when the type is already there.  */
7830   if (sym->ts.type == BT_UNKNOWN)
7831     sym->ts = target->ts;
7832   gcc_assert (sym->ts.type != BT_UNKNOWN);
7833
7834   /* See if this is a valid association-to-variable.  */
7835   sym->assoc->variable = (target->expr_type == EXPR_VARIABLE
7836                           && !gfc_has_vector_subscript (target));
7837
7838   /* Finally resolve if this is an array or not.  */
7839   if (sym->attr.dimension && target->rank == 0)
7840     {
7841       gfc_error ("Associate-name '%s' at %L is used as array",
7842                  sym->name, &sym->declared_at);
7843       sym->attr.dimension = 0;
7844       return;
7845     }
7846   if (target->rank > 0)
7847     sym->attr.dimension = 1;
7848
7849   if (sym->attr.dimension)
7850     {
7851       sym->as = gfc_get_array_spec ();
7852       sym->as->rank = target->rank;
7853       sym->as->type = AS_DEFERRED;
7854
7855       /* Target must not be coindexed, thus the associate-variable
7856          has no corank.  */
7857       sym->as->corank = 0;
7858     }
7859 }
7860
7861
7862 /* Resolve a SELECT TYPE statement.  */
7863
7864 static void
7865 resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
7866 {
7867   gfc_symbol *selector_type;
7868   gfc_code *body, *new_st, *if_st, *tail;
7869   gfc_code *class_is = NULL, *default_case = NULL;
7870   gfc_case *c;
7871   gfc_symtree *st;
7872   char name[GFC_MAX_SYMBOL_LEN];
7873   gfc_namespace *ns;
7874   int error = 0;
7875
7876   ns = code->ext.block.ns;
7877   gfc_resolve (ns);
7878
7879   /* Check for F03:C813.  */
7880   if (code->expr1->ts.type != BT_CLASS
7881       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
7882     {
7883       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
7884                  "at %L", &code->loc);
7885       return;
7886     }
7887
7888   if (code->expr2)
7889     {
7890       if (code->expr1->symtree->n.sym->attr.untyped)
7891         code->expr1->symtree->n.sym->ts = code->expr2->ts;
7892       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
7893     }
7894   else
7895     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
7896
7897   /* Loop over TYPE IS / CLASS IS cases.  */
7898   for (body = code->block; body; body = body->block)
7899     {
7900       c = body->ext.block.case_list;
7901
7902       /* Check F03:C815.  */
7903       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7904           && !gfc_type_is_extensible (c->ts.u.derived))
7905         {
7906           gfc_error ("Derived type '%s' at %L must be extensible",
7907                      c->ts.u.derived->name, &c->where);
7908           error++;
7909           continue;
7910         }
7911
7912       /* Check F03:C816.  */
7913       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7914           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
7915         {
7916           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
7917                      c->ts.u.derived->name, &c->where, selector_type->name);
7918           error++;
7919           continue;
7920         }
7921
7922       /* Intercept the DEFAULT case.  */
7923       if (c->ts.type == BT_UNKNOWN)
7924         {
7925           /* Check F03:C818.  */
7926           if (default_case)
7927             {
7928               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7929                          "by a second DEFAULT CASE at %L",
7930                          &default_case->ext.block.case_list->where, &c->where);
7931               error++;
7932               continue;
7933             }
7934
7935           default_case = body;
7936         }
7937     }
7938     
7939   if (error > 0)
7940     return;
7941
7942   /* Transform SELECT TYPE statement to BLOCK and associate selector to
7943      target if present.  If there are any EXIT statements referring to the
7944      SELECT TYPE construct, this is no problem because the gfc_code
7945      reference stays the same and EXIT is equally possible from the BLOCK
7946      it is changed to.  */
7947   code->op = EXEC_BLOCK;
7948   if (code->expr2)
7949     {
7950       gfc_association_list* assoc;
7951
7952       assoc = gfc_get_association_list ();
7953       assoc->st = code->expr1->symtree;
7954       assoc->target = gfc_copy_expr (code->expr2);
7955       /* assoc->variable will be set by resolve_assoc_var.  */
7956       
7957       code->ext.block.assoc = assoc;
7958       code->expr1->symtree->n.sym->assoc = assoc;
7959
7960       resolve_assoc_var (code->expr1->symtree->n.sym, false);
7961     }
7962   else
7963     code->ext.block.assoc = NULL;
7964
7965   /* Add EXEC_SELECT to switch on type.  */
7966   new_st = gfc_get_code ();
7967   new_st->op = code->op;
7968   new_st->expr1 = code->expr1;
7969   new_st->expr2 = code->expr2;
7970   new_st->block = code->block;
7971   code->expr1 = code->expr2 =  NULL;
7972   code->block = NULL;
7973   if (!ns->code)
7974     ns->code = new_st;
7975   else
7976     ns->code->next = new_st;
7977   code = new_st;
7978   code->op = EXEC_SELECT;
7979   gfc_add_vptr_component (code->expr1);
7980   gfc_add_hash_component (code->expr1);
7981
7982   /* Loop over TYPE IS / CLASS IS cases.  */
7983   for (body = code->block; body; body = body->block)
7984     {
7985       c = body->ext.block.case_list;
7986
7987       if (c->ts.type == BT_DERIVED)
7988         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
7989                                              c->ts.u.derived->hash_value);
7990
7991       else if (c->ts.type == BT_UNKNOWN)
7992         continue;
7993
7994       /* Associate temporary to selector.  This should only be done
7995          when this case is actually true, so build a new ASSOCIATE
7996          that does precisely this here (instead of using the
7997          'global' one).  */
7998
7999       if (c->ts.type == BT_CLASS)
8000         sprintf (name, "__tmp_class_%s", c->ts.u.derived->name);
8001       else
8002         sprintf (name, "__tmp_type_%s", c->ts.u.derived->name);
8003       st = gfc_find_symtree (ns->sym_root, name);
8004       gcc_assert (st->n.sym->assoc);
8005       st->n.sym->assoc->target = gfc_get_variable_expr (code->expr1->symtree);
8006       if (c->ts.type == BT_DERIVED)
8007         gfc_add_data_component (st->n.sym->assoc->target);
8008
8009       new_st = gfc_get_code ();
8010       new_st->op = EXEC_BLOCK;
8011       new_st->ext.block.ns = gfc_build_block_ns (ns);
8012       new_st->ext.block.ns->code = body->next;
8013       body->next = new_st;
8014
8015       /* Chain in the new list only if it is marked as dangling.  Otherwise
8016          there is a CASE label overlap and this is already used.  Just ignore,
8017          the error is diagonsed elsewhere.  */
8018       if (st->n.sym->assoc->dangling)
8019         {
8020           new_st->ext.block.assoc = st->n.sym->assoc;
8021           st->n.sym->assoc->dangling = 0;
8022         }
8023
8024       resolve_assoc_var (st->n.sym, false);
8025     }
8026     
8027   /* Take out CLASS IS cases for separate treatment.  */
8028   body = code;
8029   while (body && body->block)
8030     {
8031       if (body->block->ext.block.case_list->ts.type == BT_CLASS)
8032         {
8033           /* Add to class_is list.  */
8034           if (class_is == NULL)
8035             { 
8036               class_is = body->block;
8037               tail = class_is;
8038             }
8039           else
8040             {
8041               for (tail = class_is; tail->block; tail = tail->block) ;
8042               tail->block = body->block;
8043               tail = tail->block;
8044             }
8045           /* Remove from EXEC_SELECT list.  */
8046           body->block = body->block->block;
8047           tail->block = NULL;
8048         }
8049       else
8050         body = body->block;
8051     }
8052
8053   if (class_is)
8054     {
8055       gfc_symbol *vtab;
8056       
8057       if (!default_case)
8058         {
8059           /* Add a default case to hold the CLASS IS cases.  */
8060           for (tail = code; tail->block; tail = tail->block) ;
8061           tail->block = gfc_get_code ();
8062           tail = tail->block;
8063           tail->op = EXEC_SELECT_TYPE;
8064           tail->ext.block.case_list = gfc_get_case ();
8065           tail->ext.block.case_list->ts.type = BT_UNKNOWN;
8066           tail->next = NULL;
8067           default_case = tail;
8068         }
8069
8070       /* More than one CLASS IS block?  */
8071       if (class_is->block)
8072         {
8073           gfc_code **c1,*c2;
8074           bool swapped;
8075           /* Sort CLASS IS blocks by extension level.  */
8076           do
8077             {
8078               swapped = false;
8079               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
8080                 {
8081                   c2 = (*c1)->block;
8082                   /* F03:C817 (check for doubles).  */
8083                   if ((*c1)->ext.block.case_list->ts.u.derived->hash_value
8084                       == c2->ext.block.case_list->ts.u.derived->hash_value)
8085                     {
8086                       gfc_error ("Double CLASS IS block in SELECT TYPE "
8087                                  "statement at %L",
8088                                  &c2->ext.block.case_list->where);
8089                       return;
8090                     }
8091                   if ((*c1)->ext.block.case_list->ts.u.derived->attr.extension
8092                       < c2->ext.block.case_list->ts.u.derived->attr.extension)
8093                     {
8094                       /* Swap.  */
8095                       (*c1)->block = c2->block;
8096                       c2->block = *c1;
8097                       *c1 = c2;
8098                       swapped = true;
8099                     }
8100                 }
8101             }
8102           while (swapped);
8103         }
8104         
8105       /* Generate IF chain.  */
8106       if_st = gfc_get_code ();
8107       if_st->op = EXEC_IF;
8108       new_st = if_st;
8109       for (body = class_is; body; body = body->block)
8110         {
8111           new_st->block = gfc_get_code ();
8112           new_st = new_st->block;
8113           new_st->op = EXEC_IF;
8114           /* Set up IF condition: Call _gfortran_is_extension_of.  */
8115           new_st->expr1 = gfc_get_expr ();
8116           new_st->expr1->expr_type = EXPR_FUNCTION;
8117           new_st->expr1->ts.type = BT_LOGICAL;
8118           new_st->expr1->ts.kind = 4;
8119           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
8120           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
8121           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
8122           /* Set up arguments.  */
8123           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
8124           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
8125           new_st->expr1->value.function.actual->expr->where = code->loc;
8126           gfc_add_vptr_component (new_st->expr1->value.function.actual->expr);
8127           vtab = gfc_find_derived_vtab (body->ext.block.case_list->ts.u.derived);
8128           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
8129           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
8130           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
8131           new_st->next = body->next;
8132         }
8133         if (default_case->next)
8134           {
8135             new_st->block = gfc_get_code ();
8136             new_st = new_st->block;
8137             new_st->op = EXEC_IF;
8138             new_st->next = default_case->next;
8139           }
8140           
8141         /* Replace CLASS DEFAULT code by the IF chain.  */
8142         default_case->next = if_st;
8143     }
8144
8145   /* Resolve the internal code.  This can not be done earlier because
8146      it requires that the sym->assoc of selectors is set already.  */
8147   gfc_current_ns = ns;
8148   gfc_resolve_blocks (code->block, gfc_current_ns);
8149   gfc_current_ns = old_ns;
8150
8151   resolve_select (code);
8152 }
8153
8154
8155 /* Resolve a transfer statement. This is making sure that:
8156    -- a derived type being transferred has only non-pointer components
8157    -- a derived type being transferred doesn't have private components, unless 
8158       it's being transferred from the module where the type was defined
8159    -- we're not trying to transfer a whole assumed size array.  */
8160
8161 static void
8162 resolve_transfer (gfc_code *code)
8163 {
8164   gfc_typespec *ts;
8165   gfc_symbol *sym;
8166   gfc_ref *ref;
8167   gfc_expr *exp;
8168
8169   exp = code->expr1;
8170
8171   while (exp != NULL && exp->expr_type == EXPR_OP
8172          && exp->value.op.op == INTRINSIC_PARENTHESES)
8173     exp = exp->value.op.op1;
8174
8175   if (exp && exp->expr_type == EXPR_NULL && exp->ts.type == BT_UNKNOWN)
8176     {
8177       gfc_error ("NULL intrinsic at %L in data transfer statement requires "
8178                  "MOLD=", &exp->where);
8179       return;
8180     }
8181
8182   if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
8183                       && exp->expr_type != EXPR_FUNCTION))
8184     return;
8185
8186   /* If we are reading, the variable will be changed.  Note that
8187      code->ext.dt may be NULL if the TRANSFER is related to
8188      an INQUIRE statement -- but in this case, we are not reading, either.  */
8189   if (code->ext.dt && code->ext.dt->dt_io_kind->value.iokind == M_READ
8190       && gfc_check_vardef_context (exp, false, false, _("item in READ"))
8191          == FAILURE)
8192     return;
8193
8194   sym = exp->symtree->n.sym;
8195   ts = &sym->ts;
8196
8197   /* Go to actual component transferred.  */
8198   for (ref = exp->ref; ref; ref = ref->next)
8199     if (ref->type == REF_COMPONENT)
8200       ts = &ref->u.c.component->ts;
8201
8202   if (ts->type == BT_CLASS)
8203     {
8204       /* FIXME: Test for defined input/output.  */
8205       gfc_error ("Data transfer element at %L cannot be polymorphic unless "
8206                 "it is processed by a defined input/output procedure",
8207                 &code->loc);
8208       return;
8209     }
8210
8211   if (ts->type == BT_DERIVED)
8212     {
8213       /* Check that transferred derived type doesn't contain POINTER
8214          components.  */
8215       if (ts->u.derived->attr.pointer_comp)
8216         {
8217           gfc_error ("Data transfer element at %L cannot have POINTER "
8218                      "components unless it is processed by a defined "
8219                      "input/output procedure", &code->loc);
8220           return;
8221         }
8222
8223       /* F08:C935.  */
8224       if (ts->u.derived->attr.proc_pointer_comp)
8225         {
8226           gfc_error ("Data transfer element at %L cannot have "
8227                      "procedure pointer components", &code->loc);
8228           return;
8229         }
8230
8231       if (ts->u.derived->attr.alloc_comp)
8232         {
8233           gfc_error ("Data transfer element at %L cannot have ALLOCATABLE "
8234                      "components unless it is processed by a defined "
8235                      "input/output procedure", &code->loc);
8236           return;
8237         }
8238
8239       if (derived_inaccessible (ts->u.derived))
8240         {
8241           gfc_error ("Data transfer element at %L cannot have "
8242                      "PRIVATE components",&code->loc);
8243           return;
8244         }
8245     }
8246
8247   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE && exp->ref
8248       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
8249     {
8250       gfc_error ("Data transfer element at %L cannot be a full reference to "
8251                  "an assumed-size array", &code->loc);
8252       return;
8253     }
8254 }
8255
8256
8257 /*********** Toplevel code resolution subroutines ***********/
8258
8259 /* Find the set of labels that are reachable from this block.  We also
8260    record the last statement in each block.  */
8261      
8262 static void
8263 find_reachable_labels (gfc_code *block)
8264 {
8265   gfc_code *c;
8266
8267   if (!block)
8268     return;
8269
8270   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
8271
8272   /* Collect labels in this block.  We don't keep those corresponding
8273      to END {IF|SELECT}, these are checked in resolve_branch by going
8274      up through the code_stack.  */
8275   for (c = block; c; c = c->next)
8276     {
8277       if (c->here && c->op != EXEC_END_NESTED_BLOCK)
8278         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
8279     }
8280
8281   /* Merge with labels from parent block.  */
8282   if (cs_base->prev)
8283     {
8284       gcc_assert (cs_base->prev->reachable_labels);
8285       bitmap_ior_into (cs_base->reachable_labels,
8286                        cs_base->prev->reachable_labels);
8287     }
8288 }
8289
8290
8291 static void
8292 resolve_lock_unlock (gfc_code *code)
8293 {
8294   if (code->expr1->ts.type != BT_DERIVED
8295       || code->expr1->expr_type != EXPR_VARIABLE
8296       || code->expr1->ts.u.derived->from_intmod != INTMOD_ISO_FORTRAN_ENV
8297       || code->expr1->ts.u.derived->intmod_sym_id != ISOFORTRAN_LOCK_TYPE
8298       || code->expr1->rank != 0
8299       || (!gfc_is_coarray (code->expr1) && !gfc_is_coindexed (code->expr1)))
8300     gfc_error ("Lock variable at %L must be a scalar of type LOCK_TYPE",
8301                &code->expr1->where);
8302
8303   /* Check STAT.  */
8304   if (code->expr2
8305       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8306           || code->expr2->expr_type != EXPR_VARIABLE))
8307     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8308                &code->expr2->where);
8309
8310   if (code->expr2
8311       && gfc_check_vardef_context (code->expr2, false, false,
8312                                    _("STAT variable")) == FAILURE)
8313     return;
8314
8315   /* Check ERRMSG.  */
8316   if (code->expr3
8317       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8318           || code->expr3->expr_type != EXPR_VARIABLE))
8319     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8320                &code->expr3->where);
8321
8322   if (code->expr3
8323       && gfc_check_vardef_context (code->expr3, false, false,
8324                                    _("ERRMSG variable")) == FAILURE)
8325     return;
8326
8327   /* Check ACQUIRED_LOCK.  */
8328   if (code->expr4
8329       && (code->expr4->ts.type != BT_LOGICAL || code->expr4->rank != 0
8330           || code->expr4->expr_type != EXPR_VARIABLE))
8331     gfc_error ("ACQUIRED_LOCK= argument at %L must be a scalar LOGICAL "
8332                "variable", &code->expr4->where);
8333
8334   if (code->expr4
8335       && gfc_check_vardef_context (code->expr4, false, false,
8336                                    _("ACQUIRED_LOCK variable")) == FAILURE)
8337     return;
8338 }
8339
8340
8341 static void
8342 resolve_sync (gfc_code *code)
8343 {
8344   /* Check imageset. The * case matches expr1 == NULL.  */
8345   if (code->expr1)
8346     {
8347       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
8348         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
8349                    "INTEGER expression", &code->expr1->where);
8350       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
8351           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
8352         gfc_error ("Imageset argument at %L must between 1 and num_images()",
8353                    &code->expr1->where);
8354       else if (code->expr1->expr_type == EXPR_ARRAY
8355                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
8356         {
8357            gfc_constructor *cons;
8358            cons = gfc_constructor_first (code->expr1->value.constructor);
8359            for (; cons; cons = gfc_constructor_next (cons))
8360              if (cons->expr->expr_type == EXPR_CONSTANT
8361                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
8362                gfc_error ("Imageset argument at %L must between 1 and "
8363                           "num_images()", &cons->expr->where);
8364         }
8365     }
8366
8367   /* Check STAT.  */
8368   if (code->expr2
8369       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8370           || code->expr2->expr_type != EXPR_VARIABLE))
8371     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8372                &code->expr2->where);
8373
8374   /* Check ERRMSG.  */
8375   if (code->expr3
8376       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8377           || code->expr3->expr_type != EXPR_VARIABLE))
8378     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8379                &code->expr3->where);
8380 }
8381
8382
8383 /* Given a branch to a label, see if the branch is conforming.
8384    The code node describes where the branch is located.  */
8385
8386 static void
8387 resolve_branch (gfc_st_label *label, gfc_code *code)
8388 {
8389   code_stack *stack;
8390
8391   if (label == NULL)
8392     return;
8393
8394   /* Step one: is this a valid branching target?  */
8395
8396   if (label->defined == ST_LABEL_UNKNOWN)
8397     {
8398       gfc_error ("Label %d referenced at %L is never defined", label->value,
8399                  &label->where);
8400       return;
8401     }
8402
8403   if (label->defined != ST_LABEL_TARGET)
8404     {
8405       gfc_error ("Statement at %L is not a valid branch target statement "
8406                  "for the branch statement at %L", &label->where, &code->loc);
8407       return;
8408     }
8409
8410   /* Step two: make sure this branch is not a branch to itself ;-)  */
8411
8412   if (code->here == label)
8413     {
8414       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
8415       return;
8416     }
8417
8418   /* Step three:  See if the label is in the same block as the
8419      branching statement.  The hard work has been done by setting up
8420      the bitmap reachable_labels.  */
8421
8422   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8423     {
8424       /* Check now whether there is a CRITICAL construct; if so, check
8425          whether the label is still visible outside of the CRITICAL block,
8426          which is invalid.  */
8427       for (stack = cs_base; stack; stack = stack->prev)
8428         {
8429           if (stack->current->op == EXEC_CRITICAL
8430               && bitmap_bit_p (stack->reachable_labels, label->value))
8431             gfc_error ("GOTO statement at %L leaves CRITICAL construct for "
8432                       "label at %L", &code->loc, &label->where);
8433           else if (stack->current->op == EXEC_DO_CONCURRENT
8434                    && bitmap_bit_p (stack->reachable_labels, label->value))
8435             gfc_error ("GOTO statement at %L leaves DO CONCURRENT construct "
8436                       "for label at %L", &code->loc, &label->where);
8437         }
8438
8439       return;
8440     }
8441
8442   /* Step four:  If we haven't found the label in the bitmap, it may
8443     still be the label of the END of the enclosing block, in which
8444     case we find it by going up the code_stack.  */
8445
8446   for (stack = cs_base; stack; stack = stack->prev)
8447     {
8448       if (stack->current->next && stack->current->next->here == label)
8449         break;
8450       if (stack->current->op == EXEC_CRITICAL)
8451         {
8452           /* Note: A label at END CRITICAL does not leave the CRITICAL
8453              construct as END CRITICAL is still part of it.  */
8454           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8455                       " at %L", &code->loc, &label->where);
8456           return;
8457         }
8458       else if (stack->current->op == EXEC_DO_CONCURRENT)
8459         {
8460           gfc_error ("GOTO statement at %L leaves DO CONCURRENT construct for "
8461                      "label at %L", &code->loc, &label->where);
8462           return;
8463         }
8464     }
8465
8466   if (stack)
8467     {
8468       gcc_assert (stack->current->next->op == EXEC_END_NESTED_BLOCK);
8469       return;
8470     }
8471
8472   /* The label is not in an enclosing block, so illegal.  This was
8473      allowed in Fortran 66, so we allow it as extension.  No
8474      further checks are necessary in this case.  */
8475   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
8476                   "as the GOTO statement at %L", &label->where,
8477                   &code->loc);
8478   return;
8479 }
8480
8481
8482 /* Check whether EXPR1 has the same shape as EXPR2.  */
8483
8484 static gfc_try
8485 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8486 {
8487   mpz_t shape[GFC_MAX_DIMENSIONS];
8488   mpz_t shape2[GFC_MAX_DIMENSIONS];
8489   gfc_try result = FAILURE;
8490   int i;
8491
8492   /* Compare the rank.  */
8493   if (expr1->rank != expr2->rank)
8494     return result;
8495
8496   /* Compare the size of each dimension.  */
8497   for (i=0; i<expr1->rank; i++)
8498     {
8499       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
8500         goto ignore;
8501
8502       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
8503         goto ignore;
8504
8505       if (mpz_cmp (shape[i], shape2[i]))
8506         goto over;
8507     }
8508
8509   /* When either of the two expression is an assumed size array, we
8510      ignore the comparison of dimension sizes.  */
8511 ignore:
8512   result = SUCCESS;
8513
8514 over:
8515   gfc_clear_shape (shape, i);
8516   gfc_clear_shape (shape2, i);
8517   return result;
8518 }
8519
8520
8521 /* Check whether a WHERE assignment target or a WHERE mask expression
8522    has the same shape as the outmost WHERE mask expression.  */
8523
8524 static void
8525 resolve_where (gfc_code *code, gfc_expr *mask)
8526 {
8527   gfc_code *cblock;
8528   gfc_code *cnext;
8529   gfc_expr *e = NULL;
8530
8531   cblock = code->block;
8532
8533   /* Store the first WHERE mask-expr of the WHERE statement or construct.
8534      In case of nested WHERE, only the outmost one is stored.  */
8535   if (mask == NULL) /* outmost WHERE */
8536     e = cblock->expr1;
8537   else /* inner WHERE */
8538     e = mask;
8539
8540   while (cblock)
8541     {
8542       if (cblock->expr1)
8543         {
8544           /* Check if the mask-expr has a consistent shape with the
8545              outmost WHERE mask-expr.  */
8546           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
8547             gfc_error ("WHERE mask at %L has inconsistent shape",
8548                        &cblock->expr1->where);
8549          }
8550
8551       /* the assignment statement of a WHERE statement, or the first
8552          statement in where-body-construct of a WHERE construct */
8553       cnext = cblock->next;
8554       while (cnext)
8555         {
8556           switch (cnext->op)
8557             {
8558             /* WHERE assignment statement */
8559             case EXEC_ASSIGN:
8560
8561               /* Check shape consistent for WHERE assignment target.  */
8562               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
8563                gfc_error ("WHERE assignment target at %L has "
8564                           "inconsistent shape", &cnext->expr1->where);
8565               break;
8566
8567   
8568             case EXEC_ASSIGN_CALL:
8569               resolve_call (cnext);
8570               if (!cnext->resolved_sym->attr.elemental)
8571                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8572                           &cnext->ext.actual->expr->where);
8573               break;
8574
8575             /* WHERE or WHERE construct is part of a where-body-construct */
8576             case EXEC_WHERE:
8577               resolve_where (cnext, e);
8578               break;
8579
8580             default:
8581               gfc_error ("Unsupported statement inside WHERE at %L",
8582                          &cnext->loc);
8583             }
8584          /* the next statement within the same where-body-construct */
8585          cnext = cnext->next;
8586        }
8587     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8588     cblock = cblock->block;
8589   }
8590 }
8591
8592
8593 /* Resolve assignment in FORALL construct.
8594    NVAR is the number of FORALL index variables, and VAR_EXPR records the
8595    FORALL index variables.  */
8596
8597 static void
8598 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8599 {
8600   int n;
8601
8602   for (n = 0; n < nvar; n++)
8603     {
8604       gfc_symbol *forall_index;
8605
8606       forall_index = var_expr[n]->symtree->n.sym;
8607
8608       /* Check whether the assignment target is one of the FORALL index
8609          variable.  */
8610       if ((code->expr1->expr_type == EXPR_VARIABLE)
8611           && (code->expr1->symtree->n.sym == forall_index))
8612         gfc_error ("Assignment to a FORALL index variable at %L",
8613                    &code->expr1->where);
8614       else
8615         {
8616           /* If one of the FORALL index variables doesn't appear in the
8617              assignment variable, then there could be a many-to-one
8618              assignment.  Emit a warning rather than an error because the
8619              mask could be resolving this problem.  */
8620           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
8621             gfc_warning ("The FORALL with index '%s' is not used on the "
8622                          "left side of the assignment at %L and so might "
8623                          "cause multiple assignment to this object",
8624                          var_expr[n]->symtree->name, &code->expr1->where);
8625         }
8626     }
8627 }
8628
8629
8630 /* Resolve WHERE statement in FORALL construct.  */
8631
8632 static void
8633 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
8634                                   gfc_expr **var_expr)
8635 {
8636   gfc_code *cblock;
8637   gfc_code *cnext;
8638
8639   cblock = code->block;
8640   while (cblock)
8641     {
8642       /* the assignment statement of a WHERE statement, or the first
8643          statement in where-body-construct of a WHERE construct */
8644       cnext = cblock->next;
8645       while (cnext)
8646         {
8647           switch (cnext->op)
8648             {
8649             /* WHERE assignment statement */
8650             case EXEC_ASSIGN:
8651               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
8652               break;
8653   
8654             /* WHERE operator assignment statement */
8655             case EXEC_ASSIGN_CALL:
8656               resolve_call (cnext);
8657               if (!cnext->resolved_sym->attr.elemental)
8658                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8659                           &cnext->ext.actual->expr->where);
8660               break;
8661
8662             /* WHERE or WHERE construct is part of a where-body-construct */
8663             case EXEC_WHERE:
8664               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
8665               break;
8666
8667             default:
8668               gfc_error ("Unsupported statement inside WHERE at %L",
8669                          &cnext->loc);
8670             }
8671           /* the next statement within the same where-body-construct */
8672           cnext = cnext->next;
8673         }
8674       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8675       cblock = cblock->block;
8676     }
8677 }
8678
8679
8680 /* Traverse the FORALL body to check whether the following errors exist:
8681    1. For assignment, check if a many-to-one assignment happens.
8682    2. For WHERE statement, check the WHERE body to see if there is any
8683       many-to-one assignment.  */
8684
8685 static void
8686 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
8687 {
8688   gfc_code *c;
8689
8690   c = code->block->next;
8691   while (c)
8692     {
8693       switch (c->op)
8694         {
8695         case EXEC_ASSIGN:
8696         case EXEC_POINTER_ASSIGN:
8697           gfc_resolve_assign_in_forall (c, nvar, var_expr);
8698           break;
8699
8700         case EXEC_ASSIGN_CALL:
8701           resolve_call (c);
8702           break;
8703
8704         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
8705            there is no need to handle it here.  */
8706         case EXEC_FORALL:
8707           break;
8708         case EXEC_WHERE:
8709           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
8710           break;
8711         default:
8712           break;
8713         }
8714       /* The next statement in the FORALL body.  */
8715       c = c->next;
8716     }
8717 }
8718
8719
8720 /* Counts the number of iterators needed inside a forall construct, including
8721    nested forall constructs. This is used to allocate the needed memory 
8722    in gfc_resolve_forall.  */
8723
8724 static int 
8725 gfc_count_forall_iterators (gfc_code *code)
8726 {
8727   int max_iters, sub_iters, current_iters;
8728   gfc_forall_iterator *fa;
8729
8730   gcc_assert(code->op == EXEC_FORALL);
8731   max_iters = 0;
8732   current_iters = 0;
8733
8734   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8735     current_iters ++;
8736   
8737   code = code->block->next;
8738
8739   while (code)
8740     {          
8741       if (code->op == EXEC_FORALL)
8742         {
8743           sub_iters = gfc_count_forall_iterators (code);
8744           if (sub_iters > max_iters)
8745             max_iters = sub_iters;
8746         }
8747       code = code->next;
8748     }
8749
8750   return current_iters + max_iters;
8751 }
8752
8753
8754 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8755    gfc_resolve_forall_body to resolve the FORALL body.  */
8756
8757 static void
8758 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8759 {
8760   static gfc_expr **var_expr;
8761   static int total_var = 0;
8762   static int nvar = 0;
8763   int old_nvar, tmp;
8764   gfc_forall_iterator *fa;
8765   int i;
8766
8767   old_nvar = nvar;
8768
8769   /* Start to resolve a FORALL construct   */
8770   if (forall_save == 0)
8771     {
8772       /* Count the total number of FORALL index in the nested FORALL
8773          construct in order to allocate the VAR_EXPR with proper size.  */
8774       total_var = gfc_count_forall_iterators (code);
8775
8776       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8777       var_expr = XCNEWVEC (gfc_expr *, total_var);
8778     }
8779
8780   /* The information about FORALL iterator, including FORALL index start, end
8781      and stride. The FORALL index can not appear in start, end or stride.  */
8782   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8783     {
8784       /* Check if any outer FORALL index name is the same as the current
8785          one.  */
8786       for (i = 0; i < nvar; i++)
8787         {
8788           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8789             {
8790               gfc_error ("An outer FORALL construct already has an index "
8791                          "with this name %L", &fa->var->where);
8792             }
8793         }
8794
8795       /* Record the current FORALL index.  */
8796       var_expr[nvar] = gfc_copy_expr (fa->var);
8797
8798       nvar++;
8799
8800       /* No memory leak.  */
8801       gcc_assert (nvar <= total_var);
8802     }
8803
8804   /* Resolve the FORALL body.  */
8805   gfc_resolve_forall_body (code, nvar, var_expr);
8806
8807   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8808   gfc_resolve_blocks (code->block, ns);
8809
8810   tmp = nvar;
8811   nvar = old_nvar;
8812   /* Free only the VAR_EXPRs allocated in this frame.  */
8813   for (i = nvar; i < tmp; i++)
8814      gfc_free_expr (var_expr[i]);
8815
8816   if (nvar == 0)
8817     {
8818       /* We are in the outermost FORALL construct.  */
8819       gcc_assert (forall_save == 0);
8820
8821       /* VAR_EXPR is not needed any more.  */
8822       free (var_expr);
8823       total_var = 0;
8824     }
8825 }
8826
8827
8828 /* Resolve a BLOCK construct statement.  */
8829
8830 static void
8831 resolve_block_construct (gfc_code* code)
8832 {
8833   /* Resolve the BLOCK's namespace.  */
8834   gfc_resolve (code->ext.block.ns);
8835
8836   /* For an ASSOCIATE block, the associations (and their targets) are already
8837      resolved during resolve_symbol.  */
8838 }
8839
8840
8841 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
8842    DO code nodes.  */
8843
8844 static void resolve_code (gfc_code *, gfc_namespace *);
8845
8846 void
8847 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8848 {
8849   gfc_try t;
8850
8851   for (; b; b = b->block)
8852     {
8853       t = gfc_resolve_expr (b->expr1);
8854       if (gfc_resolve_expr (b->expr2) == FAILURE)
8855         t = FAILURE;
8856
8857       switch (b->op)
8858         {
8859         case EXEC_IF:
8860           if (t == SUCCESS && b->expr1 != NULL
8861               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8862             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8863                        &b->expr1->where);
8864           break;
8865
8866         case EXEC_WHERE:
8867           if (t == SUCCESS
8868               && b->expr1 != NULL
8869               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8870             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8871                        &b->expr1->where);
8872           break;
8873
8874         case EXEC_GOTO:
8875           resolve_branch (b->label1, b);
8876           break;
8877
8878         case EXEC_BLOCK:
8879           resolve_block_construct (b);
8880           break;
8881
8882         case EXEC_SELECT:
8883         case EXEC_SELECT_TYPE:
8884         case EXEC_FORALL:
8885         case EXEC_DO:
8886         case EXEC_DO_WHILE:
8887         case EXEC_DO_CONCURRENT:
8888         case EXEC_CRITICAL:
8889         case EXEC_READ:
8890         case EXEC_WRITE:
8891         case EXEC_IOLENGTH:
8892         case EXEC_WAIT:
8893           break;
8894
8895         case EXEC_OMP_ATOMIC:
8896         case EXEC_OMP_CRITICAL:
8897         case EXEC_OMP_DO:
8898         case EXEC_OMP_MASTER:
8899         case EXEC_OMP_ORDERED:
8900         case EXEC_OMP_PARALLEL:
8901         case EXEC_OMP_PARALLEL_DO:
8902         case EXEC_OMP_PARALLEL_SECTIONS:
8903         case EXEC_OMP_PARALLEL_WORKSHARE:
8904         case EXEC_OMP_SECTIONS:
8905         case EXEC_OMP_SINGLE:
8906         case EXEC_OMP_TASK:
8907         case EXEC_OMP_TASKWAIT:
8908         case EXEC_OMP_TASKYIELD:
8909         case EXEC_OMP_WORKSHARE:
8910           break;
8911
8912         default:
8913           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
8914         }
8915
8916       resolve_code (b->next, ns);
8917     }
8918 }
8919
8920
8921 /* Does everything to resolve an ordinary assignment.  Returns true
8922    if this is an interface assignment.  */
8923 static bool
8924 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
8925 {
8926   bool rval = false;
8927   gfc_expr *lhs;
8928   gfc_expr *rhs;
8929   int llen = 0;
8930   int rlen = 0;
8931   int n;
8932   gfc_ref *ref;
8933
8934   if (gfc_extend_assign (code, ns) == SUCCESS)
8935     {
8936       gfc_expr** rhsptr;
8937
8938       if (code->op == EXEC_ASSIGN_CALL)
8939         {
8940           lhs = code->ext.actual->expr;
8941           rhsptr = &code->ext.actual->next->expr;
8942         }
8943       else
8944         {
8945           gfc_actual_arglist* args;
8946           gfc_typebound_proc* tbp;
8947
8948           gcc_assert (code->op == EXEC_COMPCALL);
8949
8950           args = code->expr1->value.compcall.actual;
8951           lhs = args->expr;
8952           rhsptr = &args->next->expr;
8953
8954           tbp = code->expr1->value.compcall.tbp;
8955           gcc_assert (!tbp->is_generic);
8956         }
8957
8958       /* Make a temporary rhs when there is a default initializer
8959          and rhs is the same symbol as the lhs.  */
8960       if ((*rhsptr)->expr_type == EXPR_VARIABLE
8961             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
8962             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
8963             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
8964         *rhsptr = gfc_get_parentheses (*rhsptr);
8965
8966       return true;
8967     }
8968
8969   lhs = code->expr1;
8970   rhs = code->expr2;
8971
8972   if (rhs->is_boz
8973       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
8974                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
8975                          &code->loc) == FAILURE)
8976     return false;
8977
8978   /* Handle the case of a BOZ literal on the RHS.  */
8979   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
8980     {
8981       int rc;
8982       if (gfc_option.warn_surprising)
8983         gfc_warning ("BOZ literal at %L is bitwise transferred "
8984                      "non-integer symbol '%s'", &code->loc,
8985                      lhs->symtree->n.sym->name);
8986
8987       if (!gfc_convert_boz (rhs, &lhs->ts))
8988         return false;
8989       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
8990         {
8991           if (rc == ARITH_UNDERFLOW)
8992             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
8993                        ". This check can be disabled with the option "
8994                        "-fno-range-check", &rhs->where);
8995           else if (rc == ARITH_OVERFLOW)
8996             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
8997                        ". This check can be disabled with the option "
8998                        "-fno-range-check", &rhs->where);
8999           else if (rc == ARITH_NAN)
9000             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
9001                        ". This check can be disabled with the option "
9002                        "-fno-range-check", &rhs->where);
9003           return false;
9004         }
9005     }
9006
9007   if (lhs->ts.type == BT_CHARACTER
9008         && gfc_option.warn_character_truncation)
9009     {
9010       if (lhs->ts.u.cl != NULL
9011             && lhs->ts.u.cl->length != NULL
9012             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9013         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
9014
9015       if (rhs->expr_type == EXPR_CONSTANT)
9016         rlen = rhs->value.character.length;
9017
9018       else if (rhs->ts.u.cl != NULL
9019                  && rhs->ts.u.cl->length != NULL
9020                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9021         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
9022
9023       if (rlen && llen && rlen > llen)
9024         gfc_warning_now ("CHARACTER expression will be truncated "
9025                          "in assignment (%d/%d) at %L",
9026                          llen, rlen, &code->loc);
9027     }
9028
9029   /* Ensure that a vector index expression for the lvalue is evaluated
9030      to a temporary if the lvalue symbol is referenced in it.  */
9031   if (lhs->rank)
9032     {
9033       for (ref = lhs->ref; ref; ref= ref->next)
9034         if (ref->type == REF_ARRAY)
9035           {
9036             for (n = 0; n < ref->u.ar.dimen; n++)
9037               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
9038                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
9039                                            ref->u.ar.start[n]))
9040                 ref->u.ar.start[n]
9041                         = gfc_get_parentheses (ref->u.ar.start[n]);
9042           }
9043     }
9044
9045   if (gfc_pure (NULL))
9046     {
9047       if (lhs->ts.type == BT_DERIVED
9048             && lhs->expr_type == EXPR_VARIABLE
9049             && lhs->ts.u.derived->attr.pointer_comp
9050             && rhs->expr_type == EXPR_VARIABLE
9051             && (gfc_impure_variable (rhs->symtree->n.sym)
9052                 || gfc_is_coindexed (rhs)))
9053         {
9054           /* F2008, C1283.  */
9055           if (gfc_is_coindexed (rhs))
9056             gfc_error ("Coindexed expression at %L is assigned to "
9057                         "a derived type variable with a POINTER "
9058                         "component in a PURE procedure",
9059                         &rhs->where);
9060           else
9061             gfc_error ("The impure variable at %L is assigned to "
9062                         "a derived type variable with a POINTER "
9063                         "component in a PURE procedure (12.6)",
9064                         &rhs->where);
9065           return rval;
9066         }
9067
9068       /* Fortran 2008, C1283.  */
9069       if (gfc_is_coindexed (lhs))
9070         {
9071           gfc_error ("Assignment to coindexed variable at %L in a PURE "
9072                      "procedure", &rhs->where);
9073           return rval;
9074         }
9075     }
9076
9077   if (gfc_implicit_pure (NULL))
9078     {
9079       if (lhs->expr_type == EXPR_VARIABLE
9080             && lhs->symtree->n.sym != gfc_current_ns->proc_name
9081             && lhs->symtree->n.sym->ns != gfc_current_ns)
9082         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9083
9084       if (lhs->ts.type == BT_DERIVED
9085             && lhs->expr_type == EXPR_VARIABLE
9086             && lhs->ts.u.derived->attr.pointer_comp
9087             && rhs->expr_type == EXPR_VARIABLE
9088             && (gfc_impure_variable (rhs->symtree->n.sym)
9089                 || gfc_is_coindexed (rhs)))
9090         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9091
9092       /* Fortran 2008, C1283.  */
9093       if (gfc_is_coindexed (lhs))
9094         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9095     }
9096
9097   /* F03:7.4.1.2.  */
9098   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
9099      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
9100   if (lhs->ts.type == BT_CLASS)
9101     {
9102       gfc_error ("Variable must not be polymorphic in assignment at %L",
9103                  &lhs->where);
9104       return false;
9105     }
9106
9107   /* F2008, Section 7.2.1.2.  */
9108   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
9109     {
9110       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
9111                  "component in assignment at %L", &lhs->where);
9112       return false;
9113     }
9114
9115   gfc_check_assign (lhs, rhs, 1);
9116   return false;
9117 }
9118
9119
9120 /* Given a block of code, recursively resolve everything pointed to by this
9121    code block.  */
9122
9123 static void
9124 resolve_code (gfc_code *code, gfc_namespace *ns)
9125 {
9126   int omp_workshare_save;
9127   int forall_save, do_concurrent_save;
9128   code_stack frame;
9129   gfc_try t;
9130
9131   frame.prev = cs_base;
9132   frame.head = code;
9133   cs_base = &frame;
9134
9135   find_reachable_labels (code);
9136
9137   for (; code; code = code->next)
9138     {
9139       frame.current = code;
9140       forall_save = forall_flag;
9141       do_concurrent_save = do_concurrent_flag;
9142
9143       if (code->op == EXEC_FORALL)
9144         {
9145           forall_flag = 1;
9146           gfc_resolve_forall (code, ns, forall_save);
9147           forall_flag = 2;
9148         }
9149       else if (code->block)
9150         {
9151           omp_workshare_save = -1;
9152           switch (code->op)
9153             {
9154             case EXEC_OMP_PARALLEL_WORKSHARE:
9155               omp_workshare_save = omp_workshare_flag;
9156               omp_workshare_flag = 1;
9157               gfc_resolve_omp_parallel_blocks (code, ns);
9158               break;
9159             case EXEC_OMP_PARALLEL:
9160             case EXEC_OMP_PARALLEL_DO:
9161             case EXEC_OMP_PARALLEL_SECTIONS:
9162             case EXEC_OMP_TASK:
9163               omp_workshare_save = omp_workshare_flag;
9164               omp_workshare_flag = 0;
9165               gfc_resolve_omp_parallel_blocks (code, ns);
9166               break;
9167             case EXEC_OMP_DO:
9168               gfc_resolve_omp_do_blocks (code, ns);
9169               break;
9170             case EXEC_SELECT_TYPE:
9171               /* Blocks are handled in resolve_select_type because we have
9172                  to transform the SELECT TYPE into ASSOCIATE first.  */
9173               break;
9174             case EXEC_DO_CONCURRENT:
9175               do_concurrent_flag = 1;
9176               gfc_resolve_blocks (code->block, ns);
9177               do_concurrent_flag = 2;
9178               break;
9179             case EXEC_OMP_WORKSHARE:
9180               omp_workshare_save = omp_workshare_flag;
9181               omp_workshare_flag = 1;
9182               /* FALLTHROUGH */
9183             default:
9184               gfc_resolve_blocks (code->block, ns);
9185               break;
9186             }
9187
9188           if (omp_workshare_save != -1)
9189             omp_workshare_flag = omp_workshare_save;
9190         }
9191
9192       t = SUCCESS;
9193       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
9194         t = gfc_resolve_expr (code->expr1);
9195       forall_flag = forall_save;
9196       do_concurrent_flag = do_concurrent_save;
9197
9198       if (gfc_resolve_expr (code->expr2) == FAILURE)
9199         t = FAILURE;
9200
9201       if (code->op == EXEC_ALLOCATE
9202           && gfc_resolve_expr (code->expr3) == FAILURE)
9203         t = FAILURE;
9204
9205       switch (code->op)
9206         {
9207         case EXEC_NOP:
9208         case EXEC_END_BLOCK:
9209         case EXEC_END_NESTED_BLOCK:
9210         case EXEC_CYCLE:
9211         case EXEC_PAUSE:
9212         case EXEC_STOP:
9213         case EXEC_ERROR_STOP:
9214         case EXEC_EXIT:
9215         case EXEC_CONTINUE:
9216         case EXEC_DT_END:
9217         case EXEC_ASSIGN_CALL:
9218         case EXEC_CRITICAL:
9219           break;
9220
9221         case EXEC_SYNC_ALL:
9222         case EXEC_SYNC_IMAGES:
9223         case EXEC_SYNC_MEMORY:
9224           resolve_sync (code);
9225           break;
9226
9227         case EXEC_LOCK:
9228         case EXEC_UNLOCK:
9229           resolve_lock_unlock (code);
9230           break;
9231
9232         case EXEC_ENTRY:
9233           /* Keep track of which entry we are up to.  */
9234           current_entry_id = code->ext.entry->id;
9235           break;
9236
9237         case EXEC_WHERE:
9238           resolve_where (code, NULL);
9239           break;
9240
9241         case EXEC_GOTO:
9242           if (code->expr1 != NULL)
9243             {
9244               if (code->expr1->ts.type != BT_INTEGER)
9245                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
9246                            "INTEGER variable", &code->expr1->where);
9247               else if (code->expr1->symtree->n.sym->attr.assign != 1)
9248                 gfc_error ("Variable '%s' has not been assigned a target "
9249                            "label at %L", code->expr1->symtree->n.sym->name,
9250                            &code->expr1->where);
9251             }
9252           else
9253             resolve_branch (code->label1, code);
9254           break;
9255
9256         case EXEC_RETURN:
9257           if (code->expr1 != NULL
9258                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
9259             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
9260                        "INTEGER return specifier", &code->expr1->where);
9261           break;
9262
9263         case EXEC_INIT_ASSIGN:
9264         case EXEC_END_PROCEDURE:
9265           break;
9266
9267         case EXEC_ASSIGN:
9268           if (t == FAILURE)
9269             break;
9270
9271           if (gfc_check_vardef_context (code->expr1, false, false,
9272                                         _("assignment")) == FAILURE)
9273             break;
9274
9275           if (resolve_ordinary_assign (code, ns))
9276             {
9277               if (code->op == EXEC_COMPCALL)
9278                 goto compcall;
9279               else
9280                 goto call;
9281             }
9282           break;
9283
9284         case EXEC_LABEL_ASSIGN:
9285           if (code->label1->defined == ST_LABEL_UNKNOWN)
9286             gfc_error ("Label %d referenced at %L is never defined",
9287                        code->label1->value, &code->label1->where);
9288           if (t == SUCCESS
9289               && (code->expr1->expr_type != EXPR_VARIABLE
9290                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
9291                   || code->expr1->symtree->n.sym->ts.kind
9292                      != gfc_default_integer_kind
9293                   || code->expr1->symtree->n.sym->as != NULL))
9294             gfc_error ("ASSIGN statement at %L requires a scalar "
9295                        "default INTEGER variable", &code->expr1->where);
9296           break;
9297
9298         case EXEC_POINTER_ASSIGN:
9299           {
9300             gfc_expr* e;
9301
9302             if (t == FAILURE)
9303               break;
9304
9305             /* This is both a variable definition and pointer assignment
9306                context, so check both of them.  For rank remapping, a final
9307                array ref may be present on the LHS and fool gfc_expr_attr
9308                used in gfc_check_vardef_context.  Remove it.  */
9309             e = remove_last_array_ref (code->expr1);
9310             t = gfc_check_vardef_context (e, true, false,
9311                                           _("pointer assignment"));
9312             if (t == SUCCESS)
9313               t = gfc_check_vardef_context (e, false, false,
9314                                             _("pointer assignment"));
9315             gfc_free_expr (e);
9316             if (t == FAILURE)
9317               break;
9318
9319             gfc_check_pointer_assign (code->expr1, code->expr2);
9320             break;
9321           }
9322
9323         case EXEC_ARITHMETIC_IF:
9324           if (t == SUCCESS
9325               && code->expr1->ts.type != BT_INTEGER
9326               && code->expr1->ts.type != BT_REAL)
9327             gfc_error ("Arithmetic IF statement at %L requires a numeric "
9328                        "expression", &code->expr1->where);
9329
9330           resolve_branch (code->label1, code);
9331           resolve_branch (code->label2, code);
9332           resolve_branch (code->label3, code);
9333           break;
9334
9335         case EXEC_IF:
9336           if (t == SUCCESS && code->expr1 != NULL
9337               && (code->expr1->ts.type != BT_LOGICAL
9338                   || code->expr1->rank != 0))
9339             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9340                        &code->expr1->where);
9341           break;
9342
9343         case EXEC_CALL:
9344         call:
9345           resolve_call (code);
9346           break;
9347
9348         case EXEC_COMPCALL:
9349         compcall:
9350           resolve_typebound_subroutine (code);
9351           break;
9352
9353         case EXEC_CALL_PPC:
9354           resolve_ppc_call (code);
9355           break;
9356
9357         case EXEC_SELECT:
9358           /* Select is complicated. Also, a SELECT construct could be
9359              a transformed computed GOTO.  */
9360           resolve_select (code);
9361           break;
9362
9363         case EXEC_SELECT_TYPE:
9364           resolve_select_type (code, ns);
9365           break;
9366
9367         case EXEC_BLOCK:
9368           resolve_block_construct (code);
9369           break;
9370
9371         case EXEC_DO:
9372           if (code->ext.iterator != NULL)
9373             {
9374               gfc_iterator *iter = code->ext.iterator;
9375               if (gfc_resolve_iterator (iter, true) != FAILURE)
9376                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
9377             }
9378           break;
9379
9380         case EXEC_DO_WHILE:
9381           if (code->expr1 == NULL)
9382             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
9383           if (t == SUCCESS
9384               && (code->expr1->rank != 0
9385                   || code->expr1->ts.type != BT_LOGICAL))
9386             gfc_error ("Exit condition of DO WHILE loop at %L must be "
9387                        "a scalar LOGICAL expression", &code->expr1->where);
9388           break;
9389
9390         case EXEC_ALLOCATE:
9391           if (t == SUCCESS)
9392             resolve_allocate_deallocate (code, "ALLOCATE");
9393
9394           break;
9395
9396         case EXEC_DEALLOCATE:
9397           if (t == SUCCESS)
9398             resolve_allocate_deallocate (code, "DEALLOCATE");
9399
9400           break;
9401
9402         case EXEC_OPEN:
9403           if (gfc_resolve_open (code->ext.open) == FAILURE)
9404             break;
9405
9406           resolve_branch (code->ext.open->err, code);
9407           break;
9408
9409         case EXEC_CLOSE:
9410           if (gfc_resolve_close (code->ext.close) == FAILURE)
9411             break;
9412
9413           resolve_branch (code->ext.close->err, code);
9414           break;
9415
9416         case EXEC_BACKSPACE:
9417         case EXEC_ENDFILE:
9418         case EXEC_REWIND:
9419         case EXEC_FLUSH:
9420           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
9421             break;
9422
9423           resolve_branch (code->ext.filepos->err, code);
9424           break;
9425
9426         case EXEC_INQUIRE:
9427           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9428               break;
9429
9430           resolve_branch (code->ext.inquire->err, code);
9431           break;
9432
9433         case EXEC_IOLENGTH:
9434           gcc_assert (code->ext.inquire != NULL);
9435           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9436             break;
9437
9438           resolve_branch (code->ext.inquire->err, code);
9439           break;
9440
9441         case EXEC_WAIT:
9442           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
9443             break;
9444
9445           resolve_branch (code->ext.wait->err, code);
9446           resolve_branch (code->ext.wait->end, code);
9447           resolve_branch (code->ext.wait->eor, code);
9448           break;
9449
9450         case EXEC_READ:
9451         case EXEC_WRITE:
9452           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
9453             break;
9454
9455           resolve_branch (code->ext.dt->err, code);
9456           resolve_branch (code->ext.dt->end, code);
9457           resolve_branch (code->ext.dt->eor, code);
9458           break;
9459
9460         case EXEC_TRANSFER:
9461           resolve_transfer (code);
9462           break;
9463
9464         case EXEC_DO_CONCURRENT:
9465         case EXEC_FORALL:
9466           resolve_forall_iterators (code->ext.forall_iterator);
9467
9468           if (code->expr1 != NULL
9469               && (code->expr1->ts.type != BT_LOGICAL || code->expr1->rank))
9470             gfc_error ("FORALL mask clause at %L requires a scalar LOGICAL "
9471                        "expression", &code->expr1->where);
9472           break;
9473
9474         case EXEC_OMP_ATOMIC:
9475         case EXEC_OMP_BARRIER:
9476         case EXEC_OMP_CRITICAL:
9477         case EXEC_OMP_FLUSH:
9478         case EXEC_OMP_DO:
9479         case EXEC_OMP_MASTER:
9480         case EXEC_OMP_ORDERED:
9481         case EXEC_OMP_SECTIONS:
9482         case EXEC_OMP_SINGLE:
9483         case EXEC_OMP_TASKWAIT:
9484         case EXEC_OMP_TASKYIELD:
9485         case EXEC_OMP_WORKSHARE:
9486           gfc_resolve_omp_directive (code, ns);
9487           break;
9488
9489         case EXEC_OMP_PARALLEL:
9490         case EXEC_OMP_PARALLEL_DO:
9491         case EXEC_OMP_PARALLEL_SECTIONS:
9492         case EXEC_OMP_PARALLEL_WORKSHARE:
9493         case EXEC_OMP_TASK:
9494           omp_workshare_save = omp_workshare_flag;
9495           omp_workshare_flag = 0;
9496           gfc_resolve_omp_directive (code, ns);
9497           omp_workshare_flag = omp_workshare_save;
9498           break;
9499
9500         default:
9501           gfc_internal_error ("resolve_code(): Bad statement code");
9502         }
9503     }
9504
9505   cs_base = frame.prev;
9506 }
9507
9508
9509 /* Resolve initial values and make sure they are compatible with
9510    the variable.  */
9511
9512 static void
9513 resolve_values (gfc_symbol *sym)
9514 {
9515   gfc_try t;
9516
9517   if (sym->value == NULL)
9518     return;
9519
9520   if (sym->value->expr_type == EXPR_STRUCTURE)
9521     t= resolve_structure_cons (sym->value, 1);
9522   else 
9523     t = gfc_resolve_expr (sym->value);
9524
9525   if (t == FAILURE)
9526     return;
9527
9528   gfc_check_assign_symbol (sym, sym->value);
9529 }
9530
9531
9532 /* Verify the binding labels for common blocks that are BIND(C).  The label
9533    for a BIND(C) common block must be identical in all scoping units in which
9534    the common block is declared.  Further, the binding label can not collide
9535    with any other global entity in the program.  */
9536
9537 static void
9538 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
9539 {
9540   if (comm_block_tree->n.common->is_bind_c == 1)
9541     {
9542       gfc_gsymbol *binding_label_gsym;
9543       gfc_gsymbol *comm_name_gsym;
9544
9545       /* See if a global symbol exists by the common block's name.  It may
9546          be NULL if the common block is use-associated.  */
9547       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
9548                                          comm_block_tree->n.common->name);
9549       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
9550         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
9551                    "with the global entity '%s' at %L",
9552                    comm_block_tree->n.common->binding_label,
9553                    comm_block_tree->n.common->name,
9554                    &(comm_block_tree->n.common->where),
9555                    comm_name_gsym->name, &(comm_name_gsym->where));
9556       else if (comm_name_gsym != NULL
9557                && strcmp (comm_name_gsym->name,
9558                           comm_block_tree->n.common->name) == 0)
9559         {
9560           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
9561              as expected.  */
9562           if (comm_name_gsym->binding_label == NULL)
9563             /* No binding label for common block stored yet; save this one.  */
9564             comm_name_gsym->binding_label =
9565               comm_block_tree->n.common->binding_label;
9566           else
9567             if (strcmp (comm_name_gsym->binding_label,
9568                         comm_block_tree->n.common->binding_label) != 0)
9569               {
9570                 /* Common block names match but binding labels do not.  */
9571                 gfc_error ("Binding label '%s' for common block '%s' at %L "
9572                            "does not match the binding label '%s' for common "
9573                            "block '%s' at %L",
9574                            comm_block_tree->n.common->binding_label,
9575                            comm_block_tree->n.common->name,
9576                            &(comm_block_tree->n.common->where),
9577                            comm_name_gsym->binding_label,
9578                            comm_name_gsym->name,
9579                            &(comm_name_gsym->where));
9580                 return;
9581               }
9582         }
9583
9584       /* There is no binding label (NAME="") so we have nothing further to
9585          check and nothing to add as a global symbol for the label.  */
9586       if (comm_block_tree->n.common->binding_label[0] == '\0' )
9587         return;
9588       
9589       binding_label_gsym =
9590         gfc_find_gsymbol (gfc_gsym_root,
9591                           comm_block_tree->n.common->binding_label);
9592       if (binding_label_gsym == NULL)
9593         {
9594           /* Need to make a global symbol for the binding label to prevent
9595              it from colliding with another.  */
9596           binding_label_gsym =
9597             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
9598           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
9599           binding_label_gsym->type = GSYM_COMMON;
9600         }
9601       else
9602         {
9603           /* If comm_name_gsym is NULL, the name common block is use
9604              associated and the name could be colliding.  */
9605           if (binding_label_gsym->type != GSYM_COMMON)
9606             gfc_error ("Binding label '%s' for common block '%s' at %L "
9607                        "collides with the global entity '%s' at %L",
9608                        comm_block_tree->n.common->binding_label,
9609                        comm_block_tree->n.common->name,
9610                        &(comm_block_tree->n.common->where),
9611                        binding_label_gsym->name,
9612                        &(binding_label_gsym->where));
9613           else if (comm_name_gsym != NULL
9614                    && (strcmp (binding_label_gsym->name,
9615                                comm_name_gsym->binding_label) != 0)
9616                    && (strcmp (binding_label_gsym->sym_name,
9617                                comm_name_gsym->name) != 0))
9618             gfc_error ("Binding label '%s' for common block '%s' at %L "
9619                        "collides with global entity '%s' at %L",
9620                        binding_label_gsym->name, binding_label_gsym->sym_name,
9621                        &(comm_block_tree->n.common->where),
9622                        comm_name_gsym->name, &(comm_name_gsym->where));
9623         }
9624     }
9625   
9626   return;
9627 }
9628
9629
9630 /* Verify any BIND(C) derived types in the namespace so we can report errors
9631    for them once, rather than for each variable declared of that type.  */
9632
9633 static void
9634 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
9635 {
9636   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
9637       && derived_sym->attr.is_bind_c == 1)
9638     verify_bind_c_derived_type (derived_sym);
9639   
9640   return;
9641 }
9642
9643
9644 /* Verify that any binding labels used in a given namespace do not collide 
9645    with the names or binding labels of any global symbols.  */
9646
9647 static void
9648 gfc_verify_binding_labels (gfc_symbol *sym)
9649 {
9650   int has_error = 0;
9651   
9652   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
9653       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
9654     {
9655       gfc_gsymbol *bind_c_sym;
9656
9657       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
9658       if (bind_c_sym != NULL 
9659           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
9660         {
9661           if (sym->attr.if_source == IFSRC_DECL 
9662               && (bind_c_sym->type != GSYM_SUBROUTINE 
9663                   && bind_c_sym->type != GSYM_FUNCTION) 
9664               && ((sym->attr.contained == 1 
9665                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
9666                   || (sym->attr.use_assoc == 1 
9667                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
9668             {
9669               /* Make sure global procedures don't collide with anything.  */
9670               gfc_error ("Binding label '%s' at %L collides with the global "
9671                          "entity '%s' at %L", sym->binding_label,
9672                          &(sym->declared_at), bind_c_sym->name,
9673                          &(bind_c_sym->where));
9674               has_error = 1;
9675             }
9676           else if (sym->attr.contained == 0 
9677                    && (sym->attr.if_source == IFSRC_IFBODY 
9678                        && sym->attr.flavor == FL_PROCEDURE) 
9679                    && (bind_c_sym->sym_name != NULL 
9680                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
9681             {
9682               /* Make sure procedures in interface bodies don't collide.  */
9683               gfc_error ("Binding label '%s' in interface body at %L collides "
9684                          "with the global entity '%s' at %L",
9685                          sym->binding_label,
9686                          &(sym->declared_at), bind_c_sym->name,
9687                          &(bind_c_sym->where));
9688               has_error = 1;
9689             }
9690           else if (sym->attr.contained == 0 
9691                    && sym->attr.if_source == IFSRC_UNKNOWN)
9692             if ((sym->attr.use_assoc && bind_c_sym->mod_name
9693                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
9694                 || sym->attr.use_assoc == 0)
9695               {
9696                 gfc_error ("Binding label '%s' at %L collides with global "
9697                            "entity '%s' at %L", sym->binding_label,
9698                            &(sym->declared_at), bind_c_sym->name,
9699                            &(bind_c_sym->where));
9700                 has_error = 1;
9701               }
9702
9703           if (has_error != 0)
9704             /* Clear the binding label to prevent checking multiple times.  */
9705             sym->binding_label[0] = '\0';
9706         }
9707       else if (bind_c_sym == NULL)
9708         {
9709           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
9710           bind_c_sym->where = sym->declared_at;
9711           bind_c_sym->sym_name = sym->name;
9712
9713           if (sym->attr.use_assoc == 1)
9714             bind_c_sym->mod_name = sym->module;
9715           else
9716             if (sym->ns->proc_name != NULL)
9717               bind_c_sym->mod_name = sym->ns->proc_name->name;
9718
9719           if (sym->attr.contained == 0)
9720             {
9721               if (sym->attr.subroutine)
9722                 bind_c_sym->type = GSYM_SUBROUTINE;
9723               else if (sym->attr.function)
9724                 bind_c_sym->type = GSYM_FUNCTION;
9725             }
9726         }
9727     }
9728   return;
9729 }
9730
9731
9732 /* Resolve an index expression.  */
9733
9734 static gfc_try
9735 resolve_index_expr (gfc_expr *e)
9736 {
9737   if (gfc_resolve_expr (e) == FAILURE)
9738     return FAILURE;
9739
9740   if (gfc_simplify_expr (e, 0) == FAILURE)
9741     return FAILURE;
9742
9743   if (gfc_specification_expr (e) == FAILURE)
9744     return FAILURE;
9745
9746   return SUCCESS;
9747 }
9748
9749
9750 /* Resolve a charlen structure.  */
9751
9752 static gfc_try
9753 resolve_charlen (gfc_charlen *cl)
9754 {
9755   int i, k;
9756
9757   if (cl->resolved)
9758     return SUCCESS;
9759
9760   cl->resolved = 1;
9761
9762   specification_expr = 1;
9763
9764   if (resolve_index_expr (cl->length) == FAILURE)
9765     {
9766       specification_expr = 0;
9767       return FAILURE;
9768     }
9769
9770   /* "If the character length parameter value evaluates to a negative
9771      value, the length of character entities declared is zero."  */
9772   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
9773     {
9774       if (gfc_option.warn_surprising)
9775         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
9776                          " the length has been set to zero",
9777                          &cl->length->where, i);
9778       gfc_replace_expr (cl->length,
9779                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
9780     }
9781
9782   /* Check that the character length is not too large.  */
9783   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
9784   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
9785       && cl->length->ts.type == BT_INTEGER
9786       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
9787     {
9788       gfc_error ("String length at %L is too large", &cl->length->where);
9789       return FAILURE;
9790     }
9791
9792   return SUCCESS;
9793 }
9794
9795
9796 /* Test for non-constant shape arrays.  */
9797
9798 static bool
9799 is_non_constant_shape_array (gfc_symbol *sym)
9800 {
9801   gfc_expr *e;
9802   int i;
9803   bool not_constant;
9804
9805   not_constant = false;
9806   if (sym->as != NULL)
9807     {
9808       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
9809          has not been simplified; parameter array references.  Do the
9810          simplification now.  */
9811       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
9812         {
9813           e = sym->as->lower[i];
9814           if (e && (resolve_index_expr (e) == FAILURE
9815                     || !gfc_is_constant_expr (e)))
9816             not_constant = true;
9817           e = sym->as->upper[i];
9818           if (e && (resolve_index_expr (e) == FAILURE
9819                     || !gfc_is_constant_expr (e)))
9820             not_constant = true;
9821         }
9822     }
9823   return not_constant;
9824 }
9825
9826 /* Given a symbol and an initialization expression, add code to initialize
9827    the symbol to the function entry.  */
9828 static void
9829 build_init_assign (gfc_symbol *sym, gfc_expr *init)
9830 {
9831   gfc_expr *lval;
9832   gfc_code *init_st;
9833   gfc_namespace *ns = sym->ns;
9834
9835   /* Search for the function namespace if this is a contained
9836      function without an explicit result.  */
9837   if (sym->attr.function && sym == sym->result
9838       && sym->name != sym->ns->proc_name->name)
9839     {
9840       ns = ns->contained;
9841       for (;ns; ns = ns->sibling)
9842         if (strcmp (ns->proc_name->name, sym->name) == 0)
9843           break;
9844     }
9845
9846   if (ns == NULL)
9847     {
9848       gfc_free_expr (init);
9849       return;
9850     }
9851
9852   /* Build an l-value expression for the result.  */
9853   lval = gfc_lval_expr_from_sym (sym);
9854
9855   /* Add the code at scope entry.  */
9856   init_st = gfc_get_code ();
9857   init_st->next = ns->code;
9858   ns->code = init_st;
9859
9860   /* Assign the default initializer to the l-value.  */
9861   init_st->loc = sym->declared_at;
9862   init_st->op = EXEC_INIT_ASSIGN;
9863   init_st->expr1 = lval;
9864   init_st->expr2 = init;
9865 }
9866
9867 /* Assign the default initializer to a derived type variable or result.  */
9868
9869 static void
9870 apply_default_init (gfc_symbol *sym)
9871 {
9872   gfc_expr *init = NULL;
9873
9874   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9875     return;
9876
9877   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
9878     init = gfc_default_initializer (&sym->ts);
9879
9880   if (init == NULL && sym->ts.type != BT_CLASS)
9881     return;
9882
9883   build_init_assign (sym, init);
9884   sym->attr.referenced = 1;
9885 }
9886
9887 /* Build an initializer for a local integer, real, complex, logical, or
9888    character variable, based on the command line flags finit-local-zero,
9889    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
9890    null if the symbol should not have a default initialization.  */
9891 static gfc_expr *
9892 build_default_init_expr (gfc_symbol *sym)
9893 {
9894   int char_len;
9895   gfc_expr *init_expr;
9896   int i;
9897
9898   /* These symbols should never have a default initialization.  */
9899   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
9900       || sym->attr.external
9901       || sym->attr.dummy
9902       || sym->attr.pointer
9903       || sym->attr.in_equivalence
9904       || sym->attr.in_common
9905       || sym->attr.data
9906       || sym->module
9907       || sym->attr.cray_pointee
9908       || sym->attr.cray_pointer)
9909     return NULL;
9910
9911   /* Now we'll try to build an initializer expression.  */
9912   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
9913                                      &sym->declared_at);
9914
9915   /* We will only initialize integers, reals, complex, logicals, and
9916      characters, and only if the corresponding command-line flags
9917      were set.  Otherwise, we free init_expr and return null.  */
9918   switch (sym->ts.type)
9919     {    
9920     case BT_INTEGER:
9921       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
9922         mpz_set_si (init_expr->value.integer, 
9923                          gfc_option.flag_init_integer_value);
9924       else
9925         {
9926           gfc_free_expr (init_expr);
9927           init_expr = NULL;
9928         }
9929       break;
9930
9931     case BT_REAL:
9932       switch (gfc_option.flag_init_real)
9933         {
9934         case GFC_INIT_REAL_SNAN:
9935           init_expr->is_snan = 1;
9936           /* Fall through.  */
9937         case GFC_INIT_REAL_NAN:
9938           mpfr_set_nan (init_expr->value.real);
9939           break;
9940
9941         case GFC_INIT_REAL_INF:
9942           mpfr_set_inf (init_expr->value.real, 1);
9943           break;
9944
9945         case GFC_INIT_REAL_NEG_INF:
9946           mpfr_set_inf (init_expr->value.real, -1);
9947           break;
9948
9949         case GFC_INIT_REAL_ZERO:
9950           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
9951           break;
9952
9953         default:
9954           gfc_free_expr (init_expr);
9955           init_expr = NULL;
9956           break;
9957         }
9958       break;
9959           
9960     case BT_COMPLEX:
9961       switch (gfc_option.flag_init_real)
9962         {
9963         case GFC_INIT_REAL_SNAN:
9964           init_expr->is_snan = 1;
9965           /* Fall through.  */
9966         case GFC_INIT_REAL_NAN:
9967           mpfr_set_nan (mpc_realref (init_expr->value.complex));
9968           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
9969           break;
9970
9971         case GFC_INIT_REAL_INF:
9972           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
9973           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
9974           break;
9975
9976         case GFC_INIT_REAL_NEG_INF:
9977           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
9978           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
9979           break;
9980
9981         case GFC_INIT_REAL_ZERO:
9982           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
9983           break;
9984
9985         default:
9986           gfc_free_expr (init_expr);
9987           init_expr = NULL;
9988           break;
9989         }
9990       break;
9991           
9992     case BT_LOGICAL:
9993       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
9994         init_expr->value.logical = 0;
9995       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
9996         init_expr->value.logical = 1;
9997       else
9998         {
9999           gfc_free_expr (init_expr);
10000           init_expr = NULL;
10001         }
10002       break;
10003           
10004     case BT_CHARACTER:
10005       /* For characters, the length must be constant in order to 
10006          create a default initializer.  */
10007       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
10008           && sym->ts.u.cl->length
10009           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
10010         {
10011           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
10012           init_expr->value.character.length = char_len;
10013           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
10014           for (i = 0; i < char_len; i++)
10015             init_expr->value.character.string[i]
10016               = (unsigned char) gfc_option.flag_init_character_value;
10017         }
10018       else
10019         {
10020           gfc_free_expr (init_expr);
10021           init_expr = NULL;
10022         }
10023       break;
10024           
10025     default:
10026      gfc_free_expr (init_expr);
10027      init_expr = NULL;
10028     }
10029   return init_expr;
10030 }
10031
10032 /* Add an initialization expression to a local variable.  */
10033 static void
10034 apply_default_init_local (gfc_symbol *sym)
10035 {
10036   gfc_expr *init = NULL;
10037
10038   /* The symbol should be a variable or a function return value.  */
10039   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
10040       || (sym->attr.function && sym->result != sym))
10041     return;
10042
10043   /* Try to build the initializer expression.  If we can't initialize
10044      this symbol, then init will be NULL.  */
10045   init = build_default_init_expr (sym);
10046   if (init == NULL)
10047     return;
10048
10049   /* For saved variables, we don't want to add an initializer at 
10050      function entry, so we just add a static initializer.  */
10051   if (sym->attr.save || sym->ns->save_all 
10052       || gfc_option.flag_max_stack_var_size == 0)
10053     {
10054       /* Don't clobber an existing initializer!  */
10055       gcc_assert (sym->value == NULL);
10056       sym->value = init;
10057       return;
10058     }
10059
10060   build_init_assign (sym, init);
10061 }
10062
10063
10064 /* Resolution of common features of flavors variable and procedure.  */
10065
10066 static gfc_try
10067 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
10068 {
10069   /* Avoid double diagnostics for function result symbols.  */
10070   if ((sym->result || sym->attr.result) && !sym->attr.dummy
10071       && (sym->ns != gfc_current_ns))
10072     return SUCCESS;
10073
10074   /* Constraints on deferred shape variable.  */
10075   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
10076     {
10077       if (sym->attr.allocatable)
10078         {
10079           if (sym->attr.dimension)
10080             {
10081               gfc_error ("Allocatable array '%s' at %L must have "
10082                          "a deferred shape", sym->name, &sym->declared_at);
10083               return FAILURE;
10084             }
10085           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
10086                                    "may not be ALLOCATABLE", sym->name,
10087                                    &sym->declared_at) == FAILURE)
10088             return FAILURE;
10089         }
10090
10091       if (sym->attr.pointer && sym->attr.dimension)
10092         {
10093           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
10094                      sym->name, &sym->declared_at);
10095           return FAILURE;
10096         }
10097     }
10098   else
10099     {
10100       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
10101           && sym->ts.type != BT_CLASS && !sym->assoc)
10102         {
10103           gfc_error ("Array '%s' at %L cannot have a deferred shape",
10104                      sym->name, &sym->declared_at);
10105           return FAILURE;
10106          }
10107     }
10108
10109   /* Constraints on polymorphic variables.  */
10110   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
10111     {
10112       /* F03:C502.  */
10113       if (sym->attr.class_ok
10114           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
10115         {
10116           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
10117                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
10118                      &sym->declared_at);
10119           return FAILURE;
10120         }
10121
10122       /* F03:C509.  */
10123       /* Assume that use associated symbols were checked in the module ns.
10124          Class-variables that are associate-names are also something special
10125          and excepted from the test.  */
10126       if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
10127         {
10128           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
10129                      "or pointer", sym->name, &sym->declared_at);
10130           return FAILURE;
10131         }
10132     }
10133     
10134   return SUCCESS;
10135 }
10136
10137
10138 /* Additional checks for symbols with flavor variable and derived
10139    type.  To be called from resolve_fl_variable.  */
10140
10141 static gfc_try
10142 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
10143 {
10144   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
10145
10146   /* Check to see if a derived type is blocked from being host
10147      associated by the presence of another class I symbol in the same
10148      namespace.  14.6.1.3 of the standard and the discussion on
10149      comp.lang.fortran.  */
10150   if (sym->ns != sym->ts.u.derived->ns
10151       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
10152     {
10153       gfc_symbol *s;
10154       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
10155       if (s && s->attr.flavor != FL_DERIVED)
10156         {
10157           gfc_error ("The type '%s' cannot be host associated at %L "
10158                      "because it is blocked by an incompatible object "
10159                      "of the same name declared at %L",
10160                      sym->ts.u.derived->name, &sym->declared_at,
10161                      &s->declared_at);
10162           return FAILURE;
10163         }
10164     }
10165
10166   /* 4th constraint in section 11.3: "If an object of a type for which
10167      component-initialization is specified (R429) appears in the
10168      specification-part of a module and does not have the ALLOCATABLE
10169      or POINTER attribute, the object shall have the SAVE attribute."
10170
10171      The check for initializers is performed with
10172      gfc_has_default_initializer because gfc_default_initializer generates
10173      a hidden default for allocatable components.  */
10174   if (!(sym->value || no_init_flag) && sym->ns->proc_name
10175       && sym->ns->proc_name->attr.flavor == FL_MODULE
10176       && !sym->ns->save_all && !sym->attr.save
10177       && !sym->attr.pointer && !sym->attr.allocatable
10178       && gfc_has_default_initializer (sym->ts.u.derived)
10179       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
10180                          "module variable '%s' at %L, needed due to "
10181                          "the default initialization", sym->name,
10182                          &sym->declared_at) == FAILURE)
10183     return FAILURE;
10184
10185   /* Assign default initializer.  */
10186   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
10187       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
10188     {
10189       sym->value = gfc_default_initializer (&sym->ts);
10190     }
10191
10192   return SUCCESS;
10193 }
10194
10195
10196 /* Resolve symbols with flavor variable.  */
10197
10198 static gfc_try
10199 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
10200 {
10201   int no_init_flag, automatic_flag;
10202   gfc_expr *e;
10203   const char *auto_save_msg;
10204
10205   auto_save_msg = "Automatic object '%s' at %L cannot have the "
10206                   "SAVE attribute";
10207
10208   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10209     return FAILURE;
10210
10211   /* Set this flag to check that variables are parameters of all entries.
10212      This check is effected by the call to gfc_resolve_expr through
10213      is_non_constant_shape_array.  */
10214   specification_expr = 1;
10215
10216   if (sym->ns->proc_name
10217       && (sym->ns->proc_name->attr.flavor == FL_MODULE
10218           || sym->ns->proc_name->attr.is_main_program)
10219       && !sym->attr.use_assoc
10220       && !sym->attr.allocatable
10221       && !sym->attr.pointer
10222       && is_non_constant_shape_array (sym))
10223     {
10224       /* The shape of a main program or module array needs to be
10225          constant.  */
10226       gfc_error ("The module or main program array '%s' at %L must "
10227                  "have constant shape", sym->name, &sym->declared_at);
10228       specification_expr = 0;
10229       return FAILURE;
10230     }
10231
10232   /* Constraints on deferred type parameter.  */
10233   if (sym->ts.deferred && !(sym->attr.pointer || sym->attr.allocatable))
10234     {
10235       gfc_error ("Entity '%s' at %L has a deferred type parameter and "
10236                  "requires either the pointer or allocatable attribute",
10237                      sym->name, &sym->declared_at);
10238       return FAILURE;
10239     }
10240
10241   if (sym->ts.type == BT_CHARACTER)
10242     {
10243       /* Make sure that character string variables with assumed length are
10244          dummy arguments.  */
10245       e = sym->ts.u.cl->length;
10246       if (e == NULL && !sym->attr.dummy && !sym->attr.result
10247           && !sym->ts.deferred)
10248         {
10249           gfc_error ("Entity with assumed character length at %L must be a "
10250                      "dummy argument or a PARAMETER", &sym->declared_at);
10251           return FAILURE;
10252         }
10253
10254       if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
10255         {
10256           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10257           return FAILURE;
10258         }
10259
10260       if (!gfc_is_constant_expr (e)
10261           && !(e->expr_type == EXPR_VARIABLE
10262                && e->symtree->n.sym->attr.flavor == FL_PARAMETER))
10263         {
10264           if (!sym->attr.use_assoc && sym->ns->proc_name
10265               && (sym->ns->proc_name->attr.flavor == FL_MODULE
10266                   || sym->ns->proc_name->attr.is_main_program))
10267             {
10268               gfc_error ("'%s' at %L must have constant character length "
10269                         "in this context", sym->name, &sym->declared_at);
10270               return FAILURE;
10271             }
10272           if (sym->attr.in_common)
10273             {
10274               gfc_error ("COMMON variable '%s' at %L must have constant "
10275                          "character length", sym->name, &sym->declared_at);
10276               return FAILURE;
10277             }
10278         }
10279     }
10280
10281   if (sym->value == NULL && sym->attr.referenced)
10282     apply_default_init_local (sym); /* Try to apply a default initialization.  */
10283
10284   /* Determine if the symbol may not have an initializer.  */
10285   no_init_flag = automatic_flag = 0;
10286   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
10287       || sym->attr.intrinsic || sym->attr.result)
10288     no_init_flag = 1;
10289   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
10290            && is_non_constant_shape_array (sym))
10291     {
10292       no_init_flag = automatic_flag = 1;
10293
10294       /* Also, they must not have the SAVE attribute.
10295          SAVE_IMPLICIT is checked below.  */
10296       if (sym->as && sym->attr.codimension)
10297         {
10298           int corank = sym->as->corank;
10299           sym->as->corank = 0;
10300           no_init_flag = automatic_flag = is_non_constant_shape_array (sym);
10301           sym->as->corank = corank;
10302         }
10303       if (automatic_flag && sym->attr.save == SAVE_EXPLICIT)
10304         {
10305           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10306           return FAILURE;
10307         }
10308     }
10309
10310   /* Ensure that any initializer is simplified.  */
10311   if (sym->value)
10312     gfc_simplify_expr (sym->value, 1);
10313
10314   /* Reject illegal initializers.  */
10315   if (!sym->mark && sym->value)
10316     {
10317       if (sym->attr.allocatable || (sym->ts.type == BT_CLASS
10318                                     && CLASS_DATA (sym)->attr.allocatable))
10319         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
10320                    sym->name, &sym->declared_at);
10321       else if (sym->attr.external)
10322         gfc_error ("External '%s' at %L cannot have an initializer",
10323                    sym->name, &sym->declared_at);
10324       else if (sym->attr.dummy
10325         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
10326         gfc_error ("Dummy '%s' at %L cannot have an initializer",
10327                    sym->name, &sym->declared_at);
10328       else if (sym->attr.intrinsic)
10329         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
10330                    sym->name, &sym->declared_at);
10331       else if (sym->attr.result)
10332         gfc_error ("Function result '%s' at %L cannot have an initializer",
10333                    sym->name, &sym->declared_at);
10334       else if (automatic_flag)
10335         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
10336                    sym->name, &sym->declared_at);
10337       else
10338         goto no_init_error;
10339       return FAILURE;
10340     }
10341
10342 no_init_error:
10343   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
10344     return resolve_fl_variable_derived (sym, no_init_flag);
10345
10346   return SUCCESS;
10347 }
10348
10349
10350 /* Resolve a procedure.  */
10351
10352 static gfc_try
10353 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
10354 {
10355   gfc_formal_arglist *arg;
10356
10357   if (sym->attr.function
10358       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10359     return FAILURE;
10360
10361   if (sym->ts.type == BT_CHARACTER)
10362     {
10363       gfc_charlen *cl = sym->ts.u.cl;
10364
10365       if (cl && cl->length && gfc_is_constant_expr (cl->length)
10366              && resolve_charlen (cl) == FAILURE)
10367         return FAILURE;
10368
10369       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
10370           && sym->attr.proc == PROC_ST_FUNCTION)
10371         {
10372           gfc_error ("Character-valued statement function '%s' at %L must "
10373                      "have constant length", sym->name, &sym->declared_at);
10374           return FAILURE;
10375         }
10376     }
10377
10378   /* Ensure that derived type for are not of a private type.  Internal
10379      module procedures are excluded by 2.2.3.3 - i.e., they are not
10380      externally accessible and can access all the objects accessible in
10381      the host.  */
10382   if (!(sym->ns->parent
10383         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
10384       && gfc_check_symbol_access (sym))
10385     {
10386       gfc_interface *iface;
10387
10388       for (arg = sym->formal; arg; arg = arg->next)
10389         {
10390           if (arg->sym
10391               && arg->sym->ts.type == BT_DERIVED
10392               && !arg->sym->ts.u.derived->attr.use_assoc
10393               && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10394               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
10395                                  "PRIVATE type and cannot be a dummy argument"
10396                                  " of '%s', which is PUBLIC at %L",
10397                                  arg->sym->name, sym->name, &sym->declared_at)
10398                  == FAILURE)
10399             {
10400               /* Stop this message from recurring.  */
10401               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10402               return FAILURE;
10403             }
10404         }
10405
10406       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10407          PRIVATE to the containing module.  */
10408       for (iface = sym->generic; iface; iface = iface->next)
10409         {
10410           for (arg = iface->sym->formal; arg; arg = arg->next)
10411             {
10412               if (arg->sym
10413                   && arg->sym->ts.type == BT_DERIVED
10414                   && !arg->sym->ts.u.derived->attr.use_assoc
10415                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10416                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10417                                      "'%s' in PUBLIC interface '%s' at %L "
10418                                      "takes dummy arguments of '%s' which is "
10419                                      "PRIVATE", iface->sym->name, sym->name,
10420                                      &iface->sym->declared_at,
10421                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10422                 {
10423                   /* Stop this message from recurring.  */
10424                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10425                   return FAILURE;
10426                 }
10427              }
10428         }
10429
10430       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10431          PRIVATE to the containing module.  */
10432       for (iface = sym->generic; iface; iface = iface->next)
10433         {
10434           for (arg = iface->sym->formal; arg; arg = arg->next)
10435             {
10436               if (arg->sym
10437                   && arg->sym->ts.type == BT_DERIVED
10438                   && !arg->sym->ts.u.derived->attr.use_assoc
10439                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10440                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10441                                      "'%s' in PUBLIC interface '%s' at %L "
10442                                      "takes dummy arguments of '%s' which is "
10443                                      "PRIVATE", iface->sym->name, sym->name,
10444                                      &iface->sym->declared_at,
10445                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10446                 {
10447                   /* Stop this message from recurring.  */
10448                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10449                   return FAILURE;
10450                 }
10451              }
10452         }
10453     }
10454
10455   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
10456       && !sym->attr.proc_pointer)
10457     {
10458       gfc_error ("Function '%s' at %L cannot have an initializer",
10459                  sym->name, &sym->declared_at);
10460       return FAILURE;
10461     }
10462
10463   /* An external symbol may not have an initializer because it is taken to be
10464      a procedure. Exception: Procedure Pointers.  */
10465   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
10466     {
10467       gfc_error ("External object '%s' at %L may not have an initializer",
10468                  sym->name, &sym->declared_at);
10469       return FAILURE;
10470     }
10471
10472   /* An elemental function is required to return a scalar 12.7.1  */
10473   if (sym->attr.elemental && sym->attr.function && sym->as)
10474     {
10475       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
10476                  "result", sym->name, &sym->declared_at);
10477       /* Reset so that the error only occurs once.  */
10478       sym->attr.elemental = 0;
10479       return FAILURE;
10480     }
10481
10482   if (sym->attr.proc == PROC_ST_FUNCTION
10483       && (sym->attr.allocatable || sym->attr.pointer))
10484     {
10485       gfc_error ("Statement function '%s' at %L may not have pointer or "
10486                  "allocatable attribute", sym->name, &sym->declared_at);
10487       return FAILURE;
10488     }
10489
10490   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
10491      char-len-param shall not be array-valued, pointer-valued, recursive
10492      or pure.  ....snip... A character value of * may only be used in the
10493      following ways: (i) Dummy arg of procedure - dummy associates with
10494      actual length; (ii) To declare a named constant; or (iii) External
10495      function - but length must be declared in calling scoping unit.  */
10496   if (sym->attr.function
10497       && sym->ts.type == BT_CHARACTER
10498       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
10499     {
10500       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
10501           || (sym->attr.recursive) || (sym->attr.pure))
10502         {
10503           if (sym->as && sym->as->rank)
10504             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10505                        "array-valued", sym->name, &sym->declared_at);
10506
10507           if (sym->attr.pointer)
10508             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10509                        "pointer-valued", sym->name, &sym->declared_at);
10510
10511           if (sym->attr.pure)
10512             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10513                        "pure", sym->name, &sym->declared_at);
10514
10515           if (sym->attr.recursive)
10516             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10517                        "recursive", sym->name, &sym->declared_at);
10518
10519           return FAILURE;
10520         }
10521
10522       /* Appendix B.2 of the standard.  Contained functions give an
10523          error anyway.  Fixed-form is likely to be F77/legacy. Deferred
10524          character length is an F2003 feature.  */
10525       if (!sym->attr.contained
10526             && gfc_current_form != FORM_FIXED
10527             && !sym->ts.deferred)
10528         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
10529                         "CHARACTER(*) function '%s' at %L",
10530                         sym->name, &sym->declared_at);
10531     }
10532
10533   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
10534     {
10535       gfc_formal_arglist *curr_arg;
10536       int has_non_interop_arg = 0;
10537
10538       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10539                              sym->common_block) == FAILURE)
10540         {
10541           /* Clear these to prevent looking at them again if there was an
10542              error.  */
10543           sym->attr.is_bind_c = 0;
10544           sym->attr.is_c_interop = 0;
10545           sym->ts.is_c_interop = 0;
10546         }
10547       else
10548         {
10549           /* So far, no errors have been found.  */
10550           sym->attr.is_c_interop = 1;
10551           sym->ts.is_c_interop = 1;
10552         }
10553       
10554       curr_arg = sym->formal;
10555       while (curr_arg != NULL)
10556         {
10557           /* Skip implicitly typed dummy args here.  */
10558           if (curr_arg->sym->attr.implicit_type == 0)
10559             if (gfc_verify_c_interop_param (curr_arg->sym) == FAILURE)
10560               /* If something is found to fail, record the fact so we
10561                  can mark the symbol for the procedure as not being
10562                  BIND(C) to try and prevent multiple errors being
10563                  reported.  */
10564               has_non_interop_arg = 1;
10565           
10566           curr_arg = curr_arg->next;
10567         }
10568
10569       /* See if any of the arguments were not interoperable and if so, clear
10570          the procedure symbol to prevent duplicate error messages.  */
10571       if (has_non_interop_arg != 0)
10572         {
10573           sym->attr.is_c_interop = 0;
10574           sym->ts.is_c_interop = 0;
10575           sym->attr.is_bind_c = 0;
10576         }
10577     }
10578   
10579   if (!sym->attr.proc_pointer)
10580     {
10581       if (sym->attr.save == SAVE_EXPLICIT)
10582         {
10583           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
10584                      "in '%s' at %L", sym->name, &sym->declared_at);
10585           return FAILURE;
10586         }
10587       if (sym->attr.intent)
10588         {
10589           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
10590                      "in '%s' at %L", sym->name, &sym->declared_at);
10591           return FAILURE;
10592         }
10593       if (sym->attr.subroutine && sym->attr.result)
10594         {
10595           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
10596                      "in '%s' at %L", sym->name, &sym->declared_at);
10597           return FAILURE;
10598         }
10599       if (sym->attr.external && sym->attr.function
10600           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
10601               || sym->attr.contained))
10602         {
10603           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
10604                      "in '%s' at %L", sym->name, &sym->declared_at);
10605           return FAILURE;
10606         }
10607       if (strcmp ("ppr@", sym->name) == 0)
10608         {
10609           gfc_error ("Procedure pointer result '%s' at %L "
10610                      "is missing the pointer attribute",
10611                      sym->ns->proc_name->name, &sym->declared_at);
10612           return FAILURE;
10613         }
10614     }
10615
10616   return SUCCESS;
10617 }
10618
10619
10620 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
10621    been defined and we now know their defined arguments, check that they fulfill
10622    the requirements of the standard for procedures used as finalizers.  */
10623
10624 static gfc_try
10625 gfc_resolve_finalizers (gfc_symbol* derived)
10626 {
10627   gfc_finalizer* list;
10628   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
10629   gfc_try result = SUCCESS;
10630   bool seen_scalar = false;
10631
10632   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
10633     return SUCCESS;
10634
10635   /* Walk over the list of finalizer-procedures, check them, and if any one
10636      does not fit in with the standard's definition, print an error and remove
10637      it from the list.  */
10638   prev_link = &derived->f2k_derived->finalizers;
10639   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
10640     {
10641       gfc_symbol* arg;
10642       gfc_finalizer* i;
10643       int my_rank;
10644
10645       /* Skip this finalizer if we already resolved it.  */
10646       if (list->proc_tree)
10647         {
10648           prev_link = &(list->next);
10649           continue;
10650         }
10651
10652       /* Check this exists and is a SUBROUTINE.  */
10653       if (!list->proc_sym->attr.subroutine)
10654         {
10655           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
10656                      list->proc_sym->name, &list->where);
10657           goto error;
10658         }
10659
10660       /* We should have exactly one argument.  */
10661       if (!list->proc_sym->formal || list->proc_sym->formal->next)
10662         {
10663           gfc_error ("FINAL procedure at %L must have exactly one argument",
10664                      &list->where);
10665           goto error;
10666         }
10667       arg = list->proc_sym->formal->sym;
10668
10669       /* This argument must be of our type.  */
10670       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
10671         {
10672           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
10673                      &arg->declared_at, derived->name);
10674           goto error;
10675         }
10676
10677       /* It must neither be a pointer nor allocatable nor optional.  */
10678       if (arg->attr.pointer)
10679         {
10680           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
10681                      &arg->declared_at);
10682           goto error;
10683         }
10684       if (arg->attr.allocatable)
10685         {
10686           gfc_error ("Argument of FINAL procedure at %L must not be"
10687                      " ALLOCATABLE", &arg->declared_at);
10688           goto error;
10689         }
10690       if (arg->attr.optional)
10691         {
10692           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
10693                      &arg->declared_at);
10694           goto error;
10695         }
10696
10697       /* It must not be INTENT(OUT).  */
10698       if (arg->attr.intent == INTENT_OUT)
10699         {
10700           gfc_error ("Argument of FINAL procedure at %L must not be"
10701                      " INTENT(OUT)", &arg->declared_at);
10702           goto error;
10703         }
10704
10705       /* Warn if the procedure is non-scalar and not assumed shape.  */
10706       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
10707           && arg->as->type != AS_ASSUMED_SHAPE)
10708         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
10709                      " shape argument", &arg->declared_at);
10710
10711       /* Check that it does not match in kind and rank with a FINAL procedure
10712          defined earlier.  To really loop over the *earlier* declarations,
10713          we need to walk the tail of the list as new ones were pushed at the
10714          front.  */
10715       /* TODO: Handle kind parameters once they are implemented.  */
10716       my_rank = (arg->as ? arg->as->rank : 0);
10717       for (i = list->next; i; i = i->next)
10718         {
10719           /* Argument list might be empty; that is an error signalled earlier,
10720              but we nevertheless continued resolving.  */
10721           if (i->proc_sym->formal)
10722             {
10723               gfc_symbol* i_arg = i->proc_sym->formal->sym;
10724               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
10725               if (i_rank == my_rank)
10726                 {
10727                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
10728                              " rank (%d) as '%s'",
10729                              list->proc_sym->name, &list->where, my_rank, 
10730                              i->proc_sym->name);
10731                   goto error;
10732                 }
10733             }
10734         }
10735
10736         /* Is this the/a scalar finalizer procedure?  */
10737         if (!arg->as || arg->as->rank == 0)
10738           seen_scalar = true;
10739
10740         /* Find the symtree for this procedure.  */
10741         gcc_assert (!list->proc_tree);
10742         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
10743
10744         prev_link = &list->next;
10745         continue;
10746
10747         /* Remove wrong nodes immediately from the list so we don't risk any
10748            troubles in the future when they might fail later expectations.  */
10749 error:
10750         result = FAILURE;
10751         i = list;
10752         *prev_link = list->next;
10753         gfc_free_finalizer (i);
10754     }
10755
10756   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
10757      were nodes in the list, must have been for arrays.  It is surely a good
10758      idea to have a scalar version there if there's something to finalize.  */
10759   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
10760     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
10761                  " defined at %L, suggest also scalar one",
10762                  derived->name, &derived->declared_at);
10763
10764   /* TODO:  Remove this error when finalization is finished.  */
10765   gfc_error ("Finalization at %L is not yet implemented",
10766              &derived->declared_at);
10767
10768   return result;
10769 }
10770
10771
10772 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10773
10774 static gfc_try
10775 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10776                              const char* generic_name, locus where)
10777 {
10778   gfc_symbol* sym1;
10779   gfc_symbol* sym2;
10780
10781   gcc_assert (t1->specific && t2->specific);
10782   gcc_assert (!t1->specific->is_generic);
10783   gcc_assert (!t2->specific->is_generic);
10784
10785   sym1 = t1->specific->u.specific->n.sym;
10786   sym2 = t2->specific->u.specific->n.sym;
10787
10788   if (sym1 == sym2)
10789     return SUCCESS;
10790
10791   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10792   if (sym1->attr.subroutine != sym2->attr.subroutine
10793       || sym1->attr.function != sym2->attr.function)
10794     {
10795       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10796                  " GENERIC '%s' at %L",
10797                  sym1->name, sym2->name, generic_name, &where);
10798       return FAILURE;
10799     }
10800
10801   /* Compare the interfaces.  */
10802   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10803     {
10804       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10805                  sym1->name, sym2->name, generic_name, &where);
10806       return FAILURE;
10807     }
10808
10809   return SUCCESS;
10810 }
10811
10812
10813 /* Worker function for resolving a generic procedure binding; this is used to
10814    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10815
10816    The difference between those cases is finding possible inherited bindings
10817    that are overridden, as one has to look for them in tb_sym_root,
10818    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10819    the super-type and set p->overridden correctly.  */
10820
10821 static gfc_try
10822 resolve_tb_generic_targets (gfc_symbol* super_type,
10823                             gfc_typebound_proc* p, const char* name)
10824 {
10825   gfc_tbp_generic* target;
10826   gfc_symtree* first_target;
10827   gfc_symtree* inherited;
10828
10829   gcc_assert (p && p->is_generic);
10830
10831   /* Try to find the specific bindings for the symtrees in our target-list.  */
10832   gcc_assert (p->u.generic);
10833   for (target = p->u.generic; target; target = target->next)
10834     if (!target->specific)
10835       {
10836         gfc_typebound_proc* overridden_tbp;
10837         gfc_tbp_generic* g;
10838         const char* target_name;
10839
10840         target_name = target->specific_st->name;
10841
10842         /* Defined for this type directly.  */
10843         if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
10844           {
10845             target->specific = target->specific_st->n.tb;
10846             goto specific_found;
10847           }
10848
10849         /* Look for an inherited specific binding.  */
10850         if (super_type)
10851           {
10852             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10853                                                  true, NULL);
10854
10855             if (inherited)
10856               {
10857                 gcc_assert (inherited->n.tb);
10858                 target->specific = inherited->n.tb;
10859                 goto specific_found;
10860               }
10861           }
10862
10863         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10864                    " at %L", target_name, name, &p->where);
10865         return FAILURE;
10866
10867         /* Once we've found the specific binding, check it is not ambiguous with
10868            other specifics already found or inherited for the same GENERIC.  */
10869 specific_found:
10870         gcc_assert (target->specific);
10871
10872         /* This must really be a specific binding!  */
10873         if (target->specific->is_generic)
10874           {
10875             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
10876                        " '%s' is GENERIC, too", name, &p->where, target_name);
10877             return FAILURE;
10878           }
10879
10880         /* Check those already resolved on this type directly.  */
10881         for (g = p->u.generic; g; g = g->next)
10882           if (g != target && g->specific
10883               && check_generic_tbp_ambiguity (target, g, name, p->where)
10884                   == FAILURE)
10885             return FAILURE;
10886
10887         /* Check for ambiguity with inherited specific targets.  */
10888         for (overridden_tbp = p->overridden; overridden_tbp;
10889              overridden_tbp = overridden_tbp->overridden)
10890           if (overridden_tbp->is_generic)
10891             {
10892               for (g = overridden_tbp->u.generic; g; g = g->next)
10893                 {
10894                   gcc_assert (g->specific);
10895                   if (check_generic_tbp_ambiguity (target, g,
10896                                                    name, p->where) == FAILURE)
10897                     return FAILURE;
10898                 }
10899             }
10900       }
10901
10902   /* If we attempt to "overwrite" a specific binding, this is an error.  */
10903   if (p->overridden && !p->overridden->is_generic)
10904     {
10905       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
10906                  " the same name", name, &p->where);
10907       return FAILURE;
10908     }
10909
10910   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
10911      all must have the same attributes here.  */
10912   first_target = p->u.generic->specific->u.specific;
10913   gcc_assert (first_target);
10914   p->subroutine = first_target->n.sym->attr.subroutine;
10915   p->function = first_target->n.sym->attr.function;
10916
10917   return SUCCESS;
10918 }
10919
10920
10921 /* Resolve a GENERIC procedure binding for a derived type.  */
10922
10923 static gfc_try
10924 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
10925 {
10926   gfc_symbol* super_type;
10927
10928   /* Find the overridden binding if any.  */
10929   st->n.tb->overridden = NULL;
10930   super_type = gfc_get_derived_super_type (derived);
10931   if (super_type)
10932     {
10933       gfc_symtree* overridden;
10934       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
10935                                             true, NULL);
10936
10937       if (overridden && overridden->n.tb)
10938         st->n.tb->overridden = overridden->n.tb;
10939     }
10940
10941   /* Resolve using worker function.  */
10942   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
10943 }
10944
10945
10946 /* Retrieve the target-procedure of an operator binding and do some checks in
10947    common for intrinsic and user-defined type-bound operators.  */
10948
10949 static gfc_symbol*
10950 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
10951 {
10952   gfc_symbol* target_proc;
10953
10954   gcc_assert (target->specific && !target->specific->is_generic);
10955   target_proc = target->specific->u.specific->n.sym;
10956   gcc_assert (target_proc);
10957
10958   /* All operator bindings must have a passed-object dummy argument.  */
10959   if (target->specific->nopass)
10960     {
10961       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
10962       return NULL;
10963     }
10964
10965   return target_proc;
10966 }
10967
10968
10969 /* Resolve a type-bound intrinsic operator.  */
10970
10971 static gfc_try
10972 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
10973                                 gfc_typebound_proc* p)
10974 {
10975   gfc_symbol* super_type;
10976   gfc_tbp_generic* target;
10977   
10978   /* If there's already an error here, do nothing (but don't fail again).  */
10979   if (p->error)
10980     return SUCCESS;
10981
10982   /* Operators should always be GENERIC bindings.  */
10983   gcc_assert (p->is_generic);
10984
10985   /* Look for an overridden binding.  */
10986   super_type = gfc_get_derived_super_type (derived);
10987   if (super_type && super_type->f2k_derived)
10988     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
10989                                                      op, true, NULL);
10990   else
10991     p->overridden = NULL;
10992
10993   /* Resolve general GENERIC properties using worker function.  */
10994   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
10995     goto error;
10996
10997   /* Check the targets to be procedures of correct interface.  */
10998   for (target = p->u.generic; target; target = target->next)
10999     {
11000       gfc_symbol* target_proc;
11001
11002       target_proc = get_checked_tb_operator_target (target, p->where);
11003       if (!target_proc)
11004         goto error;
11005
11006       if (!gfc_check_operator_interface (target_proc, op, p->where))
11007         goto error;
11008     }
11009
11010   return SUCCESS;
11011
11012 error:
11013   p->error = 1;
11014   return FAILURE;
11015 }
11016
11017
11018 /* Resolve a type-bound user operator (tree-walker callback).  */
11019
11020 static gfc_symbol* resolve_bindings_derived;
11021 static gfc_try resolve_bindings_result;
11022
11023 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
11024
11025 static void
11026 resolve_typebound_user_op (gfc_symtree* stree)
11027 {
11028   gfc_symbol* super_type;
11029   gfc_tbp_generic* target;
11030
11031   gcc_assert (stree && stree->n.tb);
11032
11033   if (stree->n.tb->error)
11034     return;
11035
11036   /* Operators should always be GENERIC bindings.  */
11037   gcc_assert (stree->n.tb->is_generic);
11038
11039   /* Find overridden procedure, if any.  */
11040   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11041   if (super_type && super_type->f2k_derived)
11042     {
11043       gfc_symtree* overridden;
11044       overridden = gfc_find_typebound_user_op (super_type, NULL,
11045                                                stree->name, true, NULL);
11046
11047       if (overridden && overridden->n.tb)
11048         stree->n.tb->overridden = overridden->n.tb;
11049     }
11050   else
11051     stree->n.tb->overridden = NULL;
11052
11053   /* Resolve basically using worker function.  */
11054   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
11055         == FAILURE)
11056     goto error;
11057
11058   /* Check the targets to be functions of correct interface.  */
11059   for (target = stree->n.tb->u.generic; target; target = target->next)
11060     {
11061       gfc_symbol* target_proc;
11062
11063       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
11064       if (!target_proc)
11065         goto error;
11066
11067       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
11068         goto error;
11069     }
11070
11071   return;
11072
11073 error:
11074   resolve_bindings_result = FAILURE;
11075   stree->n.tb->error = 1;
11076 }
11077
11078
11079 /* Resolve the type-bound procedures for a derived type.  */
11080
11081 static void
11082 resolve_typebound_procedure (gfc_symtree* stree)
11083 {
11084   gfc_symbol* proc;
11085   locus where;
11086   gfc_symbol* me_arg;
11087   gfc_symbol* super_type;
11088   gfc_component* comp;
11089
11090   gcc_assert (stree);
11091
11092   /* Undefined specific symbol from GENERIC target definition.  */
11093   if (!stree->n.tb)
11094     return;
11095
11096   if (stree->n.tb->error)
11097     return;
11098
11099   /* If this is a GENERIC binding, use that routine.  */
11100   if (stree->n.tb->is_generic)
11101     {
11102       if (resolve_typebound_generic (resolve_bindings_derived, stree)
11103             == FAILURE)
11104         goto error;
11105       return;
11106     }
11107
11108   /* Get the target-procedure to check it.  */
11109   gcc_assert (!stree->n.tb->is_generic);
11110   gcc_assert (stree->n.tb->u.specific);
11111   proc = stree->n.tb->u.specific->n.sym;
11112   where = stree->n.tb->where;
11113
11114   /* Default access should already be resolved from the parser.  */
11115   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
11116
11117   /* It should be a module procedure or an external procedure with explicit
11118      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
11119   if ((!proc->attr.subroutine && !proc->attr.function)
11120       || (proc->attr.proc != PROC_MODULE
11121           && proc->attr.if_source != IFSRC_IFBODY)
11122       || (proc->attr.abstract && !stree->n.tb->deferred))
11123     {
11124       gfc_error ("'%s' must be a module procedure or an external procedure with"
11125                  " an explicit interface at %L", proc->name, &where);
11126       goto error;
11127     }
11128   stree->n.tb->subroutine = proc->attr.subroutine;
11129   stree->n.tb->function = proc->attr.function;
11130
11131   /* Find the super-type of the current derived type.  We could do this once and
11132      store in a global if speed is needed, but as long as not I believe this is
11133      more readable and clearer.  */
11134   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11135
11136   /* If PASS, resolve and check arguments if not already resolved / loaded
11137      from a .mod file.  */
11138   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
11139     {
11140       if (stree->n.tb->pass_arg)
11141         {
11142           gfc_formal_arglist* i;
11143
11144           /* If an explicit passing argument name is given, walk the arg-list
11145              and look for it.  */
11146
11147           me_arg = NULL;
11148           stree->n.tb->pass_arg_num = 1;
11149           for (i = proc->formal; i; i = i->next)
11150             {
11151               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
11152                 {
11153                   me_arg = i->sym;
11154                   break;
11155                 }
11156               ++stree->n.tb->pass_arg_num;
11157             }
11158
11159           if (!me_arg)
11160             {
11161               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
11162                          " argument '%s'",
11163                          proc->name, stree->n.tb->pass_arg, &where,
11164                          stree->n.tb->pass_arg);
11165               goto error;
11166             }
11167         }
11168       else
11169         {
11170           /* Otherwise, take the first one; there should in fact be at least
11171              one.  */
11172           stree->n.tb->pass_arg_num = 1;
11173           if (!proc->formal)
11174             {
11175               gfc_error ("Procedure '%s' with PASS at %L must have at"
11176                          " least one argument", proc->name, &where);
11177               goto error;
11178             }
11179           me_arg = proc->formal->sym;
11180         }
11181
11182       /* Now check that the argument-type matches and the passed-object
11183          dummy argument is generally fine.  */
11184
11185       gcc_assert (me_arg);
11186
11187       if (me_arg->ts.type != BT_CLASS)
11188         {
11189           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11190                      " at %L", proc->name, &where);
11191           goto error;
11192         }
11193
11194       if (CLASS_DATA (me_arg)->ts.u.derived
11195           != resolve_bindings_derived)
11196         {
11197           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11198                      " the derived-type '%s'", me_arg->name, proc->name,
11199                      me_arg->name, &where, resolve_bindings_derived->name);
11200           goto error;
11201         }
11202   
11203       gcc_assert (me_arg->ts.type == BT_CLASS);
11204       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
11205         {
11206           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
11207                      " scalar", proc->name, &where);
11208           goto error;
11209         }
11210       if (CLASS_DATA (me_arg)->attr.allocatable)
11211         {
11212           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11213                      " be ALLOCATABLE", proc->name, &where);
11214           goto error;
11215         }
11216       if (CLASS_DATA (me_arg)->attr.class_pointer)
11217         {
11218           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11219                      " be POINTER", proc->name, &where);
11220           goto error;
11221         }
11222     }
11223
11224   /* If we are extending some type, check that we don't override a procedure
11225      flagged NON_OVERRIDABLE.  */
11226   stree->n.tb->overridden = NULL;
11227   if (super_type)
11228     {
11229       gfc_symtree* overridden;
11230       overridden = gfc_find_typebound_proc (super_type, NULL,
11231                                             stree->name, true, NULL);
11232
11233       if (overridden)
11234         {
11235           if (overridden->n.tb)
11236             stree->n.tb->overridden = overridden->n.tb;
11237
11238           if (gfc_check_typebound_override (stree, overridden) == FAILURE)
11239             goto error;
11240         }
11241     }
11242
11243   /* See if there's a name collision with a component directly in this type.  */
11244   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
11245     if (!strcmp (comp->name, stree->name))
11246       {
11247         gfc_error ("Procedure '%s' at %L has the same name as a component of"
11248                    " '%s'",
11249                    stree->name, &where, resolve_bindings_derived->name);
11250         goto error;
11251       }
11252
11253   /* Try to find a name collision with an inherited component.  */
11254   if (super_type && gfc_find_component (super_type, stree->name, true, true))
11255     {
11256       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
11257                  " component of '%s'",
11258                  stree->name, &where, resolve_bindings_derived->name);
11259       goto error;
11260     }
11261
11262   stree->n.tb->error = 0;
11263   return;
11264
11265 error:
11266   resolve_bindings_result = FAILURE;
11267   stree->n.tb->error = 1;
11268 }
11269
11270
11271 static gfc_try
11272 resolve_typebound_procedures (gfc_symbol* derived)
11273 {
11274   int op;
11275   gfc_symbol* super_type;
11276
11277   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
11278     return SUCCESS;
11279   
11280   super_type = gfc_get_derived_super_type (derived);
11281   if (super_type)
11282     resolve_typebound_procedures (super_type);
11283
11284   resolve_bindings_derived = derived;
11285   resolve_bindings_result = SUCCESS;
11286
11287   /* Make sure the vtab has been generated.  */
11288   gfc_find_derived_vtab (derived);
11289
11290   if (derived->f2k_derived->tb_sym_root)
11291     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
11292                           &resolve_typebound_procedure);
11293
11294   if (derived->f2k_derived->tb_uop_root)
11295     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
11296                           &resolve_typebound_user_op);
11297
11298   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
11299     {
11300       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
11301       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
11302                                                p) == FAILURE)
11303         resolve_bindings_result = FAILURE;
11304     }
11305
11306   return resolve_bindings_result;
11307 }
11308
11309
11310 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
11311    to give all identical derived types the same backend_decl.  */
11312 static void
11313 add_dt_to_dt_list (gfc_symbol *derived)
11314 {
11315   gfc_dt_list *dt_list;
11316
11317   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
11318     if (derived == dt_list->derived)
11319       return;
11320
11321   dt_list = gfc_get_dt_list ();
11322   dt_list->next = gfc_derived_types;
11323   dt_list->derived = derived;
11324   gfc_derived_types = dt_list;
11325 }
11326
11327
11328 /* Ensure that a derived-type is really not abstract, meaning that every
11329    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
11330
11331 static gfc_try
11332 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
11333 {
11334   if (!st)
11335     return SUCCESS;
11336
11337   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
11338     return FAILURE;
11339   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
11340     return FAILURE;
11341
11342   if (st->n.tb && st->n.tb->deferred)
11343     {
11344       gfc_symtree* overriding;
11345       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
11346       if (!overriding)
11347         return FAILURE;
11348       gcc_assert (overriding->n.tb);
11349       if (overriding->n.tb->deferred)
11350         {
11351           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
11352                      " '%s' is DEFERRED and not overridden",
11353                      sub->name, &sub->declared_at, st->name);
11354           return FAILURE;
11355         }
11356     }
11357
11358   return SUCCESS;
11359 }
11360
11361 static gfc_try
11362 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
11363 {
11364   /* The algorithm used here is to recursively travel up the ancestry of sub
11365      and for each ancestor-type, check all bindings.  If any of them is
11366      DEFERRED, look it up starting from sub and see if the found (overriding)
11367      binding is not DEFERRED.
11368      This is not the most efficient way to do this, but it should be ok and is
11369      clearer than something sophisticated.  */
11370
11371   gcc_assert (ancestor && !sub->attr.abstract);
11372   
11373   if (!ancestor->attr.abstract)
11374     return SUCCESS;
11375
11376   /* Walk bindings of this ancestor.  */
11377   if (ancestor->f2k_derived)
11378     {
11379       gfc_try t;
11380       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
11381       if (t == FAILURE)
11382         return FAILURE;
11383     }
11384
11385   /* Find next ancestor type and recurse on it.  */
11386   ancestor = gfc_get_derived_super_type (ancestor);
11387   if (ancestor)
11388     return ensure_not_abstract (sub, ancestor);
11389
11390   return SUCCESS;
11391 }
11392
11393
11394 /* Resolve the components of a derived type. This does not have to wait until
11395    resolution stage, but can be done as soon as the dt declaration has been
11396    parsed.  */
11397
11398 static gfc_try
11399 resolve_fl_derived0 (gfc_symbol *sym)
11400 {
11401   gfc_symbol* super_type;
11402   gfc_component *c;
11403
11404   super_type = gfc_get_derived_super_type (sym);
11405
11406   /* F2008, C432. */
11407   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
11408     {
11409       gfc_error ("As extending type '%s' at %L has a coarray component, "
11410                  "parent type '%s' shall also have one", sym->name,
11411                  &sym->declared_at, super_type->name);
11412       return FAILURE;
11413     }
11414
11415   /* Ensure the extended type gets resolved before we do.  */
11416   if (super_type && resolve_fl_derived0 (super_type) == FAILURE)
11417     return FAILURE;
11418
11419   /* An ABSTRACT type must be extensible.  */
11420   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
11421     {
11422       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
11423                  sym->name, &sym->declared_at);
11424       return FAILURE;
11425     }
11426
11427   for (c = sym->components; c != NULL; c = c->next)
11428     {
11429       /* F2008, C442.  */
11430       if (c->attr.codimension /* FIXME: c->as check due to PR 43412.  */
11431           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
11432         {
11433           gfc_error ("Coarray component '%s' at %L must be allocatable with "
11434                      "deferred shape", c->name, &c->loc);
11435           return FAILURE;
11436         }
11437
11438       /* F2008, C443.  */
11439       if (c->attr.codimension && c->ts.type == BT_DERIVED
11440           && c->ts.u.derived->ts.is_iso_c)
11441         {
11442           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11443                      "shall not be a coarray", c->name, &c->loc);
11444           return FAILURE;
11445         }
11446
11447       /* F2008, C444.  */
11448       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
11449           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
11450               || c->attr.allocatable))
11451         {
11452           gfc_error ("Component '%s' at %L with coarray component "
11453                      "shall be a nonpointer, nonallocatable scalar",
11454                      c->name, &c->loc);
11455           return FAILURE;
11456         }
11457
11458       /* F2008, C448.  */
11459       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
11460         {
11461           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
11462                      "is not an array pointer", c->name, &c->loc);
11463           return FAILURE;
11464         }
11465
11466       if (c->attr.proc_pointer && c->ts.interface)
11467         {
11468           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
11469             gfc_error ("Interface '%s', used by procedure pointer component "
11470                        "'%s' at %L, is declared in a later PROCEDURE statement",
11471                        c->ts.interface->name, c->name, &c->loc);
11472
11473           /* Get the attributes from the interface (now resolved).  */
11474           if (c->ts.interface->attr.if_source
11475               || c->ts.interface->attr.intrinsic)
11476             {
11477               gfc_symbol *ifc = c->ts.interface;
11478
11479               if (ifc->formal && !ifc->formal_ns)
11480                 resolve_symbol (ifc);
11481
11482               if (ifc->attr.intrinsic)
11483                 resolve_intrinsic (ifc, &ifc->declared_at);
11484
11485               if (ifc->result)
11486                 {
11487                   c->ts = ifc->result->ts;
11488                   c->attr.allocatable = ifc->result->attr.allocatable;
11489                   c->attr.pointer = ifc->result->attr.pointer;
11490                   c->attr.dimension = ifc->result->attr.dimension;
11491                   c->as = gfc_copy_array_spec (ifc->result->as);
11492                 }
11493               else
11494                 {   
11495                   c->ts = ifc->ts;
11496                   c->attr.allocatable = ifc->attr.allocatable;
11497                   c->attr.pointer = ifc->attr.pointer;
11498                   c->attr.dimension = ifc->attr.dimension;
11499                   c->as = gfc_copy_array_spec (ifc->as);
11500                 }
11501               c->ts.interface = ifc;
11502               c->attr.function = ifc->attr.function;
11503               c->attr.subroutine = ifc->attr.subroutine;
11504               gfc_copy_formal_args_ppc (c, ifc);
11505
11506               c->attr.pure = ifc->attr.pure;
11507               c->attr.elemental = ifc->attr.elemental;
11508               c->attr.recursive = ifc->attr.recursive;
11509               c->attr.always_explicit = ifc->attr.always_explicit;
11510               c->attr.ext_attr |= ifc->attr.ext_attr;
11511               /* Replace symbols in array spec.  */
11512               if (c->as)
11513                 {
11514                   int i;
11515                   for (i = 0; i < c->as->rank; i++)
11516                     {
11517                       gfc_expr_replace_comp (c->as->lower[i], c);
11518                       gfc_expr_replace_comp (c->as->upper[i], c);
11519                     }
11520                 }
11521               /* Copy char length.  */
11522               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11523                 {
11524                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11525                   gfc_expr_replace_comp (cl->length, c);
11526                   if (cl->length && !cl->resolved
11527                         && gfc_resolve_expr (cl->length) == FAILURE)
11528                     return FAILURE;
11529                   c->ts.u.cl = cl;
11530                 }
11531             }
11532           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
11533             {
11534               gfc_error ("Interface '%s' of procedure pointer component "
11535                          "'%s' at %L must be explicit", c->ts.interface->name,
11536                          c->name, &c->loc);
11537               return FAILURE;
11538             }
11539         }
11540       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
11541         {
11542           /* Since PPCs are not implicitly typed, a PPC without an explicit
11543              interface must be a subroutine.  */
11544           gfc_add_subroutine (&c->attr, c->name, &c->loc);
11545         }
11546
11547       /* Procedure pointer components: Check PASS arg.  */
11548       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
11549           && !sym->attr.vtype)
11550         {
11551           gfc_symbol* me_arg;
11552
11553           if (c->tb->pass_arg)
11554             {
11555               gfc_formal_arglist* i;
11556
11557               /* If an explicit passing argument name is given, walk the arg-list
11558                 and look for it.  */
11559
11560               me_arg = NULL;
11561               c->tb->pass_arg_num = 1;
11562               for (i = c->formal; i; i = i->next)
11563                 {
11564                   if (!strcmp (i->sym->name, c->tb->pass_arg))
11565                     {
11566                       me_arg = i->sym;
11567                       break;
11568                     }
11569                   c->tb->pass_arg_num++;
11570                 }
11571
11572               if (!me_arg)
11573                 {
11574                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
11575                              "at %L has no argument '%s'", c->name,
11576                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
11577                   c->tb->error = 1;
11578                   return FAILURE;
11579                 }
11580             }
11581           else
11582             {
11583               /* Otherwise, take the first one; there should in fact be at least
11584                 one.  */
11585               c->tb->pass_arg_num = 1;
11586               if (!c->formal)
11587                 {
11588                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
11589                              "must have at least one argument",
11590                              c->name, &c->loc);
11591                   c->tb->error = 1;
11592                   return FAILURE;
11593                 }
11594               me_arg = c->formal->sym;
11595             }
11596
11597           /* Now check that the argument-type matches.  */
11598           gcc_assert (me_arg);
11599           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
11600               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
11601               || (me_arg->ts.type == BT_CLASS
11602                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
11603             {
11604               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11605                          " the derived type '%s'", me_arg->name, c->name,
11606                          me_arg->name, &c->loc, sym->name);
11607               c->tb->error = 1;
11608               return FAILURE;
11609             }
11610
11611           /* Check for C453.  */
11612           if (me_arg->attr.dimension)
11613             {
11614               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11615                          "must be scalar", me_arg->name, c->name, me_arg->name,
11616                          &c->loc);
11617               c->tb->error = 1;
11618               return FAILURE;
11619             }
11620
11621           if (me_arg->attr.pointer)
11622             {
11623               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11624                          "may not have the POINTER attribute", me_arg->name,
11625                          c->name, me_arg->name, &c->loc);
11626               c->tb->error = 1;
11627               return FAILURE;
11628             }
11629
11630           if (me_arg->attr.allocatable)
11631             {
11632               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11633                          "may not be ALLOCATABLE", me_arg->name, c->name,
11634                          me_arg->name, &c->loc);
11635               c->tb->error = 1;
11636               return FAILURE;
11637             }
11638
11639           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11640             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11641                        " at %L", c->name, &c->loc);
11642
11643         }
11644
11645       /* Check type-spec if this is not the parent-type component.  */
11646       if ((!sym->attr.extension || c != sym->components) && !sym->attr.vtype
11647           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11648         return FAILURE;
11649
11650       /* If this type is an extension, set the accessibility of the parent
11651          component.  */
11652       if (super_type && c == sym->components
11653           && strcmp (super_type->name, c->name) == 0)
11654         c->attr.access = super_type->attr.access;
11655       
11656       /* If this type is an extension, see if this component has the same name
11657          as an inherited type-bound procedure.  */
11658       if (super_type && !sym->attr.is_class
11659           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11660         {
11661           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11662                      " inherited type-bound procedure",
11663                      c->name, sym->name, &c->loc);
11664           return FAILURE;
11665         }
11666
11667       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer
11668             && !c->ts.deferred)
11669         {
11670          if (c->ts.u.cl->length == NULL
11671              || (resolve_charlen (c->ts.u.cl) == FAILURE)
11672              || !gfc_is_constant_expr (c->ts.u.cl->length))
11673            {
11674              gfc_error ("Character length of component '%s' needs to "
11675                         "be a constant specification expression at %L",
11676                         c->name,
11677                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
11678              return FAILURE;
11679            }
11680         }
11681
11682       if (c->ts.type == BT_CHARACTER && c->ts.deferred
11683           && !c->attr.pointer && !c->attr.allocatable)
11684         {
11685           gfc_error ("Character component '%s' of '%s' at %L with deferred "
11686                      "length must be a POINTER or ALLOCATABLE",
11687                      c->name, sym->name, &c->loc);
11688           return FAILURE;
11689         }
11690
11691       if (c->ts.type == BT_DERIVED
11692           && sym->component_access != ACCESS_PRIVATE
11693           && gfc_check_symbol_access (sym)
11694           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11695           && !c->ts.u.derived->attr.use_assoc
11696           && !gfc_check_symbol_access (c->ts.u.derived)
11697           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11698                              "is a PRIVATE type and cannot be a component of "
11699                              "'%s', which is PUBLIC at %L", c->name,
11700                              sym->name, &sym->declared_at) == FAILURE)
11701         return FAILURE;
11702
11703       if ((sym->attr.sequence || sym->attr.is_bind_c) && c->ts.type == BT_CLASS)
11704         {
11705           gfc_error ("Polymorphic component %s at %L in SEQUENCE or BIND(C) "
11706                      "type %s", c->name, &c->loc, sym->name);
11707           return FAILURE;
11708         }
11709
11710       if (sym->attr.sequence)
11711         {
11712           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
11713             {
11714               gfc_error ("Component %s of SEQUENCE type declared at %L does "
11715                          "not have the SEQUENCE attribute",
11716                          c->ts.u.derived->name, &sym->declared_at);
11717               return FAILURE;
11718             }
11719         }
11720
11721       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && !sym->attr.vtype
11722           && c->attr.pointer && c->ts.u.derived->components == NULL
11723           && !c->ts.u.derived->attr.zero_comp)
11724         {
11725           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11726                      "that has not been declared", c->name, sym->name,
11727                      &c->loc);
11728           return FAILURE;
11729         }
11730
11731       if (c->ts.type == BT_CLASS && c->attr.class_ok
11732           && CLASS_DATA (c)->attr.class_pointer
11733           && CLASS_DATA (c)->ts.u.derived->components == NULL
11734           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
11735         {
11736           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11737                      "that has not been declared", c->name, sym->name,
11738                      &c->loc);
11739           return FAILURE;
11740         }
11741
11742       /* C437.  */
11743       if (c->ts.type == BT_CLASS && c->attr.flavor != FL_PROCEDURE
11744           && (!c->attr.class_ok
11745               || !(CLASS_DATA (c)->attr.class_pointer
11746                    || CLASS_DATA (c)->attr.allocatable)))
11747         {
11748           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
11749                      "or pointer", c->name, &c->loc);
11750           return FAILURE;
11751         }
11752
11753       /* Ensure that all the derived type components are put on the
11754          derived type list; even in formal namespaces, where derived type
11755          pointer components might not have been declared.  */
11756       if (c->ts.type == BT_DERIVED
11757             && c->ts.u.derived
11758             && c->ts.u.derived->components
11759             && c->attr.pointer
11760             && sym != c->ts.u.derived)
11761         add_dt_to_dt_list (c->ts.u.derived);
11762
11763       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
11764                                            || c->attr.proc_pointer
11765                                            || c->attr.allocatable)) == FAILURE)
11766         return FAILURE;
11767     }
11768
11769   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11770      all DEFERRED bindings are overridden.  */
11771   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11772       && !sym->attr.is_class
11773       && ensure_not_abstract (sym, super_type) == FAILURE)
11774     return FAILURE;
11775
11776   /* Add derived type to the derived type list.  */
11777   add_dt_to_dt_list (sym);
11778
11779   return SUCCESS;
11780 }
11781
11782
11783 /* The following procedure does the full resolution of a derived type,
11784    including resolution of all type-bound procedures (if present). In contrast
11785    to 'resolve_fl_derived0' this can only be done after the module has been
11786    parsed completely.  */
11787
11788 static gfc_try
11789 resolve_fl_derived (gfc_symbol *sym)
11790 {
11791   if (sym->attr.is_class && sym->ts.u.derived == NULL)
11792     {
11793       /* Fix up incomplete CLASS symbols.  */
11794       gfc_component *data = gfc_find_component (sym, "_data", true, true);
11795       gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true);
11796       if (vptr->ts.u.derived == NULL)
11797         {
11798           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
11799           gcc_assert (vtab);
11800           vptr->ts.u.derived = vtab->ts.u.derived;
11801         }
11802     }
11803   
11804   if (resolve_fl_derived0 (sym) == FAILURE)
11805     return FAILURE;
11806   
11807   /* Resolve the type-bound procedures.  */
11808   if (resolve_typebound_procedures (sym) == FAILURE)
11809     return FAILURE;
11810
11811   /* Resolve the finalizer procedures.  */
11812   if (gfc_resolve_finalizers (sym) == FAILURE)
11813     return FAILURE;
11814   
11815   return SUCCESS;
11816 }
11817
11818
11819 static gfc_try
11820 resolve_fl_namelist (gfc_symbol *sym)
11821 {
11822   gfc_namelist *nl;
11823   gfc_symbol *nlsym;
11824
11825   for (nl = sym->namelist; nl; nl = nl->next)
11826     {
11827       /* Check again, the check in match only works if NAMELIST comes
11828          after the decl.  */
11829       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SIZE)
11830         {
11831           gfc_error ("Assumed size array '%s' in namelist '%s' at %L is not "
11832                      "allowed", nl->sym->name, sym->name, &sym->declared_at);
11833           return FAILURE;
11834         }
11835
11836       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
11837           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: NAMELIST array "
11838                              "object '%s' with assumed shape in namelist "
11839                              "'%s' at %L", nl->sym->name, sym->name,
11840                              &sym->declared_at) == FAILURE)
11841         return FAILURE;
11842
11843       if (is_non_constant_shape_array (nl->sym)
11844           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST array "
11845                              "object '%s' with nonconstant shape in namelist "
11846                              "'%s' at %L", nl->sym->name, sym->name,
11847                              &sym->declared_at) == FAILURE)
11848         return FAILURE;
11849
11850       if (nl->sym->ts.type == BT_CHARACTER
11851           && (nl->sym->ts.u.cl->length == NULL
11852               || !gfc_is_constant_expr (nl->sym->ts.u.cl->length))
11853           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
11854                              "'%s' with nonconstant character length in "
11855                              "namelist '%s' at %L", nl->sym->name, sym->name,
11856                              &sym->declared_at) == FAILURE)
11857         return FAILURE;
11858
11859       /* FIXME: Once UDDTIO is implemented, the following can be
11860          removed.  */
11861       if (nl->sym->ts.type == BT_CLASS)
11862         {
11863           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L is "
11864                      "polymorphic and requires a defined input/output "
11865                      "procedure", nl->sym->name, sym->name, &sym->declared_at);
11866           return FAILURE;
11867         }
11868
11869       if (nl->sym->ts.type == BT_DERIVED
11870           && (nl->sym->ts.u.derived->attr.alloc_comp
11871               || nl->sym->ts.u.derived->attr.pointer_comp))
11872         {
11873           if (gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
11874                               "'%s' in namelist '%s' at %L with ALLOCATABLE "
11875                               "or POINTER components", nl->sym->name,
11876                               sym->name, &sym->declared_at) == FAILURE)
11877             return FAILURE;
11878
11879          /* FIXME: Once UDDTIO is implemented, the following can be
11880             removed.  */
11881           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L has "
11882                      "ALLOCATABLE or POINTER components and thus requires "
11883                      "a defined input/output procedure", nl->sym->name,
11884                      sym->name, &sym->declared_at);
11885           return FAILURE;
11886         }
11887     }
11888
11889   /* Reject PRIVATE objects in a PUBLIC namelist.  */
11890   if (gfc_check_symbol_access (sym))
11891     {
11892       for (nl = sym->namelist; nl; nl = nl->next)
11893         {
11894           if (!nl->sym->attr.use_assoc
11895               && !is_sym_host_assoc (nl->sym, sym->ns)
11896               && !gfc_check_symbol_access (nl->sym))
11897             {
11898               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
11899                          "cannot be member of PUBLIC namelist '%s' at %L",
11900                          nl->sym->name, sym->name, &sym->declared_at);
11901               return FAILURE;
11902             }
11903
11904           /* Types with private components that came here by USE-association.  */
11905           if (nl->sym->ts.type == BT_DERIVED
11906               && derived_inaccessible (nl->sym->ts.u.derived))
11907             {
11908               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
11909                          "components and cannot be member of namelist '%s' at %L",
11910                          nl->sym->name, sym->name, &sym->declared_at);
11911               return FAILURE;
11912             }
11913
11914           /* Types with private components that are defined in the same module.  */
11915           if (nl->sym->ts.type == BT_DERIVED
11916               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
11917               && nl->sym->ts.u.derived->attr.private_comp)
11918             {
11919               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
11920                          "cannot be a member of PUBLIC namelist '%s' at %L",
11921                          nl->sym->name, sym->name, &sym->declared_at);
11922               return FAILURE;
11923             }
11924         }
11925     }
11926
11927
11928   /* 14.1.2 A module or internal procedure represent local entities
11929      of the same type as a namelist member and so are not allowed.  */
11930   for (nl = sym->namelist; nl; nl = nl->next)
11931     {
11932       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
11933         continue;
11934
11935       if (nl->sym->attr.function && nl->sym == nl->sym->result)
11936         if ((nl->sym == sym->ns->proc_name)
11937                ||
11938             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
11939           continue;
11940
11941       nlsym = NULL;
11942       if (nl->sym && nl->sym->name)
11943         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
11944       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
11945         {
11946           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
11947                      "attribute in '%s' at %L", nlsym->name,
11948                      &sym->declared_at);
11949           return FAILURE;
11950         }
11951     }
11952
11953   return SUCCESS;
11954 }
11955
11956
11957 static gfc_try
11958 resolve_fl_parameter (gfc_symbol *sym)
11959 {
11960   /* A parameter array's shape needs to be constant.  */
11961   if (sym->as != NULL 
11962       && (sym->as->type == AS_DEFERRED
11963           || is_non_constant_shape_array (sym)))
11964     {
11965       gfc_error ("Parameter array '%s' at %L cannot be automatic "
11966                  "or of deferred shape", sym->name, &sym->declared_at);
11967       return FAILURE;
11968     }
11969
11970   /* Make sure a parameter that has been implicitly typed still
11971      matches the implicit type, since PARAMETER statements can precede
11972      IMPLICIT statements.  */
11973   if (sym->attr.implicit_type
11974       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
11975                                                              sym->ns)))
11976     {
11977       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
11978                  "later IMPLICIT type", sym->name, &sym->declared_at);
11979       return FAILURE;
11980     }
11981
11982   /* Make sure the types of derived parameters are consistent.  This
11983      type checking is deferred until resolution because the type may
11984      refer to a derived type from the host.  */
11985   if (sym->ts.type == BT_DERIVED
11986       && !gfc_compare_types (&sym->ts, &sym->value->ts))
11987     {
11988       gfc_error ("Incompatible derived type in PARAMETER at %L",
11989                  &sym->value->where);
11990       return FAILURE;
11991     }
11992   return SUCCESS;
11993 }
11994
11995
11996 /* Do anything necessary to resolve a symbol.  Right now, we just
11997    assume that an otherwise unknown symbol is a variable.  This sort
11998    of thing commonly happens for symbols in module.  */
11999
12000 static void
12001 resolve_symbol (gfc_symbol *sym)
12002 {
12003   int check_constant, mp_flag;
12004   gfc_symtree *symtree;
12005   gfc_symtree *this_symtree;
12006   gfc_namespace *ns;
12007   gfc_component *c;
12008
12009   if (sym->attr.flavor == FL_UNKNOWN)
12010     {
12011
12012     /* If we find that a flavorless symbol is an interface in one of the
12013        parent namespaces, find its symtree in this namespace, free the
12014        symbol and set the symtree to point to the interface symbol.  */
12015       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
12016         {
12017           symtree = gfc_find_symtree (ns->sym_root, sym->name);
12018           if (symtree && (symtree->n.sym->generic ||
12019                           (symtree->n.sym->attr.flavor == FL_PROCEDURE
12020                            && sym->ns->construct_entities)))
12021             {
12022               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
12023                                                sym->name);
12024               gfc_release_symbol (sym);
12025               symtree->n.sym->refs++;
12026               this_symtree->n.sym = symtree->n.sym;
12027               return;
12028             }
12029         }
12030
12031       /* Otherwise give it a flavor according to such attributes as
12032          it has.  */
12033       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
12034         sym->attr.flavor = FL_VARIABLE;
12035       else
12036         {
12037           sym->attr.flavor = FL_PROCEDURE;
12038           if (sym->attr.dimension)
12039             sym->attr.function = 1;
12040         }
12041     }
12042
12043   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
12044     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
12045
12046   if (sym->attr.procedure && sym->ts.interface
12047       && sym->attr.if_source != IFSRC_DECL
12048       && resolve_procedure_interface (sym) == FAILURE)
12049     return;
12050
12051   if (sym->attr.is_protected && !sym->attr.proc_pointer
12052       && (sym->attr.procedure || sym->attr.external))
12053     {
12054       if (sym->attr.external)
12055         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
12056                    "at %L", &sym->declared_at);
12057       else
12058         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
12059                    "at %L", &sym->declared_at);
12060
12061       return;
12062     }
12063
12064
12065   /* F2008, C530. */
12066   if (sym->attr.contiguous
12067       && (!sym->attr.dimension || (sym->as->type != AS_ASSUMED_SHAPE
12068                                    && !sym->attr.pointer)))
12069     {
12070       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
12071                   "array pointer or an assumed-shape array", sym->name,
12072                   &sym->declared_at);
12073       return;
12074     }
12075
12076   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
12077     return;
12078
12079   /* Symbols that are module procedures with results (functions) have
12080      the types and array specification copied for type checking in
12081      procedures that call them, as well as for saving to a module
12082      file.  These symbols can't stand the scrutiny that their results
12083      can.  */
12084   mp_flag = (sym->result != NULL && sym->result != sym);
12085
12086   /* Make sure that the intrinsic is consistent with its internal 
12087      representation. This needs to be done before assigning a default 
12088      type to avoid spurious warnings.  */
12089   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
12090       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
12091     return;
12092
12093   /* Resolve associate names.  */
12094   if (sym->assoc)
12095     resolve_assoc_var (sym, true);
12096
12097   /* Assign default type to symbols that need one and don't have one.  */
12098   if (sym->ts.type == BT_UNKNOWN)
12099     {
12100       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
12101         gfc_set_default_type (sym, 1, NULL);
12102
12103       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
12104           && !sym->attr.function && !sym->attr.subroutine
12105           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
12106         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
12107
12108       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12109         {
12110           /* The specific case of an external procedure should emit an error
12111              in the case that there is no implicit type.  */
12112           if (!mp_flag)
12113             gfc_set_default_type (sym, sym->attr.external, NULL);
12114           else
12115             {
12116               /* Result may be in another namespace.  */
12117               resolve_symbol (sym->result);
12118
12119               if (!sym->result->attr.proc_pointer)
12120                 {
12121                   sym->ts = sym->result->ts;
12122                   sym->as = gfc_copy_array_spec (sym->result->as);
12123                   sym->attr.dimension = sym->result->attr.dimension;
12124                   sym->attr.pointer = sym->result->attr.pointer;
12125                   sym->attr.allocatable = sym->result->attr.allocatable;
12126                   sym->attr.contiguous = sym->result->attr.contiguous;
12127                 }
12128             }
12129         }
12130     }
12131   else if (mp_flag && sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12132     gfc_resolve_array_spec (sym->result->as, false);
12133
12134   /* Assumed size arrays and assumed shape arrays must be dummy
12135      arguments.  Array-spec's of implied-shape should have been resolved to
12136      AS_EXPLICIT already.  */
12137
12138   if (sym->as)
12139     {
12140       gcc_assert (sym->as->type != AS_IMPLIED_SHAPE);
12141       if (((sym->as->type == AS_ASSUMED_SIZE && !sym->as->cp_was_assumed)
12142            || sym->as->type == AS_ASSUMED_SHAPE)
12143           && sym->attr.dummy == 0)
12144         {
12145           if (sym->as->type == AS_ASSUMED_SIZE)
12146             gfc_error ("Assumed size array at %L must be a dummy argument",
12147                        &sym->declared_at);
12148           else
12149             gfc_error ("Assumed shape array at %L must be a dummy argument",
12150                        &sym->declared_at);
12151           return;
12152         }
12153     }
12154
12155   /* Make sure symbols with known intent or optional are really dummy
12156      variable.  Because of ENTRY statement, this has to be deferred
12157      until resolution time.  */
12158
12159   if (!sym->attr.dummy
12160       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
12161     {
12162       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
12163       return;
12164     }
12165
12166   if (sym->attr.value && !sym->attr.dummy)
12167     {
12168       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
12169                  "it is not a dummy argument", sym->name, &sym->declared_at);
12170       return;
12171     }
12172
12173   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
12174     {
12175       gfc_charlen *cl = sym->ts.u.cl;
12176       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
12177         {
12178           gfc_error ("Character dummy variable '%s' at %L with VALUE "
12179                      "attribute must have constant length",
12180                      sym->name, &sym->declared_at);
12181           return;
12182         }
12183
12184       if (sym->ts.is_c_interop
12185           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
12186         {
12187           gfc_error ("C interoperable character dummy variable '%s' at %L "
12188                      "with VALUE attribute must have length one",
12189                      sym->name, &sym->declared_at);
12190           return;
12191         }
12192     }
12193
12194   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
12195      do this for something that was implicitly typed because that is handled
12196      in gfc_set_default_type.  Handle dummy arguments and procedure
12197      definitions separately.  Also, anything that is use associated is not
12198      handled here but instead is handled in the module it is declared in.
12199      Finally, derived type definitions are allowed to be BIND(C) since that
12200      only implies that they're interoperable, and they are checked fully for
12201      interoperability when a variable is declared of that type.  */
12202   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
12203       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
12204       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
12205     {
12206       gfc_try t = SUCCESS;
12207       
12208       /* First, make sure the variable is declared at the
12209          module-level scope (J3/04-007, Section 15.3).  */
12210       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
12211           sym->attr.in_common == 0)
12212         {
12213           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
12214                      "is neither a COMMON block nor declared at the "
12215                      "module level scope", sym->name, &(sym->declared_at));
12216           t = FAILURE;
12217         }
12218       else if (sym->common_head != NULL)
12219         {
12220           t = verify_com_block_vars_c_interop (sym->common_head);
12221         }
12222       else
12223         {
12224           /* If type() declaration, we need to verify that the components
12225              of the given type are all C interoperable, etc.  */
12226           if (sym->ts.type == BT_DERIVED &&
12227               sym->ts.u.derived->attr.is_c_interop != 1)
12228             {
12229               /* Make sure the user marked the derived type as BIND(C).  If
12230                  not, call the verify routine.  This could print an error
12231                  for the derived type more than once if multiple variables
12232                  of that type are declared.  */
12233               if (sym->ts.u.derived->attr.is_bind_c != 1)
12234                 verify_bind_c_derived_type (sym->ts.u.derived);
12235               t = FAILURE;
12236             }
12237           
12238           /* Verify the variable itself as C interoperable if it
12239              is BIND(C).  It is not possible for this to succeed if
12240              the verify_bind_c_derived_type failed, so don't have to handle
12241              any error returned by verify_bind_c_derived_type.  */
12242           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
12243                                  sym->common_block);
12244         }
12245
12246       if (t == FAILURE)
12247         {
12248           /* clear the is_bind_c flag to prevent reporting errors more than
12249              once if something failed.  */
12250           sym->attr.is_bind_c = 0;
12251           return;
12252         }
12253     }
12254
12255   /* If a derived type symbol has reached this point, without its
12256      type being declared, we have an error.  Notice that most
12257      conditions that produce undefined derived types have already
12258      been dealt with.  However, the likes of:
12259      implicit type(t) (t) ..... call foo (t) will get us here if
12260      the type is not declared in the scope of the implicit
12261      statement. Change the type to BT_UNKNOWN, both because it is so
12262      and to prevent an ICE.  */
12263   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
12264       && !sym->ts.u.derived->attr.zero_comp)
12265     {
12266       gfc_error ("The derived type '%s' at %L is of type '%s', "
12267                  "which has not been defined", sym->name,
12268                   &sym->declared_at, sym->ts.u.derived->name);
12269       sym->ts.type = BT_UNKNOWN;
12270       return;
12271     }
12272
12273   /* Make sure that the derived type has been resolved and that the
12274      derived type is visible in the symbol's namespace, if it is a
12275      module function and is not PRIVATE.  */
12276   if (sym->ts.type == BT_DERIVED
12277         && sym->ts.u.derived->attr.use_assoc
12278         && sym->ns->proc_name
12279         && sym->ns->proc_name->attr.flavor == FL_MODULE)
12280     {
12281       gfc_symbol *ds;
12282
12283       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
12284         return;
12285
12286       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
12287       if (!ds && sym->attr.function && gfc_check_symbol_access (sym))
12288         {
12289           symtree = gfc_new_symtree (&sym->ns->sym_root,
12290                                      sym->ts.u.derived->name);
12291           symtree->n.sym = sym->ts.u.derived;
12292           sym->ts.u.derived->refs++;
12293         }
12294     }
12295
12296   /* Unless the derived-type declaration is use associated, Fortran 95
12297      does not allow public entries of private derived types.
12298      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
12299      161 in 95-006r3.  */
12300   if (sym->ts.type == BT_DERIVED
12301       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
12302       && !sym->ts.u.derived->attr.use_assoc
12303       && gfc_check_symbol_access (sym)
12304       && !gfc_check_symbol_access (sym->ts.u.derived)
12305       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
12306                          "of PRIVATE derived type '%s'",
12307                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
12308                          : "variable", sym->name, &sym->declared_at,
12309                          sym->ts.u.derived->name) == FAILURE)
12310     return;
12311
12312   /* F2008, C1302.  */
12313   if (sym->ts.type == BT_DERIVED
12314       && ((sym->ts.u.derived->from_intmod == INTMOD_ISO_FORTRAN_ENV
12315            && sym->ts.u.derived->intmod_sym_id == ISOFORTRAN_LOCK_TYPE)
12316           || sym->ts.u.derived->attr.lock_comp)
12317       && !sym->attr.codimension && !sym->ts.u.derived->attr.coarray_comp)
12318     {
12319       gfc_error ("Variable %s at %L of type LOCK_TYPE or with subcomponent of "
12320                  "type LOCK_TYPE must be a coarray", sym->name,
12321                  &sym->declared_at);
12322       return;
12323     }
12324
12325   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
12326      default initialization is defined (5.1.2.4.4).  */
12327   if (sym->ts.type == BT_DERIVED
12328       && sym->attr.dummy
12329       && sym->attr.intent == INTENT_OUT
12330       && sym->as
12331       && sym->as->type == AS_ASSUMED_SIZE)
12332     {
12333       for (c = sym->ts.u.derived->components; c; c = c->next)
12334         {
12335           if (c->initializer)
12336             {
12337               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
12338                          "ASSUMED SIZE and so cannot have a default initializer",
12339                          sym->name, &sym->declared_at);
12340               return;
12341             }
12342         }
12343     }
12344
12345   /* F2008, C542.  */
12346   if (sym->ts.type == BT_DERIVED && sym->attr.dummy
12347       && sym->attr.intent == INTENT_OUT && sym->attr.lock_comp)
12348     {
12349       gfc_error ("Dummy argument '%s' at %L of LOCK_TYPE shall not be "
12350                  "INTENT(OUT)", sym->name, &sym->declared_at);
12351       return;
12352     }
12353
12354   /* F2008, C525.  */
12355   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12356        || sym->attr.codimension)
12357       && (sym->attr.result || sym->result == sym))
12358     {
12359       gfc_error ("Function result '%s' at %L shall not be a coarray or have "
12360                  "a coarray component", sym->name, &sym->declared_at);
12361       return;
12362     }
12363
12364   /* F2008, C524.  */
12365   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
12366       && sym->ts.u.derived->ts.is_iso_c)
12367     {
12368       gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12369                  "shall not be a coarray", sym->name, &sym->declared_at);
12370       return;
12371     }
12372
12373   /* F2008, C525.  */
12374   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp
12375       && (sym->attr.codimension || sym->attr.pointer || sym->attr.dimension
12376           || sym->attr.allocatable))
12377     {
12378       gfc_error ("Variable '%s' at %L with coarray component "
12379                  "shall be a nonpointer, nonallocatable scalar",
12380                  sym->name, &sym->declared_at);
12381       return;
12382     }
12383
12384   /* F2008, C526.  The function-result case was handled above.  */
12385   if (sym->attr.codimension
12386       && !(sym->attr.allocatable || sym->attr.dummy || sym->attr.save
12387            || sym->ns->save_all
12388            || sym->ns->proc_name->attr.flavor == FL_MODULE
12389            || sym->ns->proc_name->attr.is_main_program
12390            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
12391     {
12392       gfc_error ("Variable '%s' at %L is a coarray and is not ALLOCATABLE, SAVE "
12393                  "nor a dummy argument", sym->name, &sym->declared_at);
12394       return;
12395     }
12396   /* F2008, C528.  */  /* FIXME: sym->as check due to PR 43412.  */
12397   else if (sym->attr.codimension && !sym->attr.allocatable
12398       && sym->as && sym->as->cotype == AS_DEFERRED)
12399     {
12400       gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
12401                  "deferred shape", sym->name, &sym->declared_at);
12402       return;
12403     }
12404   else if (sym->attr.codimension && sym->attr.allocatable
12405       && (sym->as->type != AS_DEFERRED || sym->as->cotype != AS_DEFERRED))
12406     {
12407       gfc_error ("Allocatable coarray variable '%s' at %L must have "
12408                  "deferred shape", sym->name, &sym->declared_at);
12409       return;
12410     }
12411
12412   /* F2008, C541.  */
12413   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12414        || (sym->attr.codimension && sym->attr.allocatable))
12415       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
12416     {
12417       gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
12418                  "allocatable coarray or have coarray components",
12419                  sym->name, &sym->declared_at);
12420       return;
12421     }
12422
12423   if (sym->attr.codimension && sym->attr.dummy
12424       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
12425     {
12426       gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
12427                  "procedure '%s'", sym->name, &sym->declared_at,
12428                  sym->ns->proc_name->name);
12429       return;
12430     }
12431
12432   switch (sym->attr.flavor)
12433     {
12434     case FL_VARIABLE:
12435       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
12436         return;
12437       break;
12438
12439     case FL_PROCEDURE:
12440       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
12441         return;
12442       break;
12443
12444     case FL_NAMELIST:
12445       if (resolve_fl_namelist (sym) == FAILURE)
12446         return;
12447       break;
12448
12449     case FL_PARAMETER:
12450       if (resolve_fl_parameter (sym) == FAILURE)
12451         return;
12452       break;
12453
12454     default:
12455       break;
12456     }
12457
12458   /* Resolve array specifier. Check as well some constraints
12459      on COMMON blocks.  */
12460
12461   check_constant = sym->attr.in_common && !sym->attr.pointer;
12462
12463   /* Set the formal_arg_flag so that check_conflict will not throw
12464      an error for host associated variables in the specification
12465      expression for an array_valued function.  */
12466   if (sym->attr.function && sym->as)
12467     formal_arg_flag = 1;
12468
12469   gfc_resolve_array_spec (sym->as, check_constant);
12470
12471   formal_arg_flag = 0;
12472
12473   /* Resolve formal namespaces.  */
12474   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
12475       && !sym->attr.contained && !sym->attr.intrinsic)
12476     gfc_resolve (sym->formal_ns);
12477
12478   /* Make sure the formal namespace is present.  */
12479   if (sym->formal && !sym->formal_ns)
12480     {
12481       gfc_formal_arglist *formal = sym->formal;
12482       while (formal && !formal->sym)
12483         formal = formal->next;
12484
12485       if (formal)
12486         {
12487           sym->formal_ns = formal->sym->ns;
12488           sym->formal_ns->refs++;
12489         }
12490     }
12491
12492   /* Check threadprivate restrictions.  */
12493   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
12494       && (!sym->attr.in_common
12495           && sym->module == NULL
12496           && (sym->ns->proc_name == NULL
12497               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
12498     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
12499
12500   /* If we have come this far we can apply default-initializers, as
12501      described in 14.7.5, to those variables that have not already
12502      been assigned one.  */
12503   if (sym->ts.type == BT_DERIVED
12504       && sym->ns == gfc_current_ns
12505       && !sym->value
12506       && !sym->attr.allocatable
12507       && !sym->attr.alloc_comp)
12508     {
12509       symbol_attribute *a = &sym->attr;
12510
12511       if ((!a->save && !a->dummy && !a->pointer
12512            && !a->in_common && !a->use_assoc
12513            && (a->referenced || a->result)
12514            && !(a->function && sym != sym->result))
12515           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
12516         apply_default_init (sym);
12517     }
12518
12519   if (sym->ts.type == BT_CLASS && sym->ns == gfc_current_ns
12520       && sym->attr.dummy && sym->attr.intent == INTENT_OUT
12521       && !CLASS_DATA (sym)->attr.class_pointer
12522       && !CLASS_DATA (sym)->attr.allocatable)
12523     apply_default_init (sym);
12524
12525   /* If this symbol has a type-spec, check it.  */
12526   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
12527       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
12528     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
12529           == FAILURE)
12530       return;
12531 }
12532
12533
12534 /************* Resolve DATA statements *************/
12535
12536 static struct
12537 {
12538   gfc_data_value *vnode;
12539   mpz_t left;
12540 }
12541 values;
12542
12543
12544 /* Advance the values structure to point to the next value in the data list.  */
12545
12546 static gfc_try
12547 next_data_value (void)
12548 {
12549   while (mpz_cmp_ui (values.left, 0) == 0)
12550     {
12551
12552       if (values.vnode->next == NULL)
12553         return FAILURE;
12554
12555       values.vnode = values.vnode->next;
12556       mpz_set (values.left, values.vnode->repeat);
12557     }
12558
12559   return SUCCESS;
12560 }
12561
12562
12563 static gfc_try
12564 check_data_variable (gfc_data_variable *var, locus *where)
12565 {
12566   gfc_expr *e;
12567   mpz_t size;
12568   mpz_t offset;
12569   gfc_try t;
12570   ar_type mark = AR_UNKNOWN;
12571   int i;
12572   mpz_t section_index[GFC_MAX_DIMENSIONS];
12573   gfc_ref *ref;
12574   gfc_array_ref *ar;
12575   gfc_symbol *sym;
12576   int has_pointer;
12577
12578   if (gfc_resolve_expr (var->expr) == FAILURE)
12579     return FAILURE;
12580
12581   ar = NULL;
12582   mpz_init_set_si (offset, 0);
12583   e = var->expr;
12584
12585   if (e->expr_type != EXPR_VARIABLE)
12586     gfc_internal_error ("check_data_variable(): Bad expression");
12587
12588   sym = e->symtree->n.sym;
12589
12590   if (sym->ns->is_block_data && !sym->attr.in_common)
12591     {
12592       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
12593                  sym->name, &sym->declared_at);
12594     }
12595
12596   if (e->ref == NULL && sym->as)
12597     {
12598       gfc_error ("DATA array '%s' at %L must be specified in a previous"
12599                  " declaration", sym->name, where);
12600       return FAILURE;
12601     }
12602
12603   has_pointer = sym->attr.pointer;
12604
12605   if (gfc_is_coindexed (e))
12606     {
12607       gfc_error ("DATA element '%s' at %L cannot have a coindex", sym->name,
12608                  where);
12609       return FAILURE;
12610     }
12611
12612   for (ref = e->ref; ref; ref = ref->next)
12613     {
12614       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
12615         has_pointer = 1;
12616
12617       if (has_pointer
12618             && ref->type == REF_ARRAY
12619             && ref->u.ar.type != AR_FULL)
12620           {
12621             gfc_error ("DATA element '%s' at %L is a pointer and so must "
12622                         "be a full array", sym->name, where);
12623             return FAILURE;
12624           }
12625     }
12626
12627   if (e->rank == 0 || has_pointer)
12628     {
12629       mpz_init_set_ui (size, 1);
12630       ref = NULL;
12631     }
12632   else
12633     {
12634       ref = e->ref;
12635
12636       /* Find the array section reference.  */
12637       for (ref = e->ref; ref; ref = ref->next)
12638         {
12639           if (ref->type != REF_ARRAY)
12640             continue;
12641           if (ref->u.ar.type == AR_ELEMENT)
12642             continue;
12643           break;
12644         }
12645       gcc_assert (ref);
12646
12647       /* Set marks according to the reference pattern.  */
12648       switch (ref->u.ar.type)
12649         {
12650         case AR_FULL:
12651           mark = AR_FULL;
12652           break;
12653
12654         case AR_SECTION:
12655           ar = &ref->u.ar;
12656           /* Get the start position of array section.  */
12657           gfc_get_section_index (ar, section_index, &offset);
12658           mark = AR_SECTION;
12659           break;
12660
12661         default:
12662           gcc_unreachable ();
12663         }
12664
12665       if (gfc_array_size (e, &size) == FAILURE)
12666         {
12667           gfc_error ("Nonconstant array section at %L in DATA statement",
12668                      &e->where);
12669           mpz_clear (offset);
12670           return FAILURE;
12671         }
12672     }
12673
12674   t = SUCCESS;
12675
12676   while (mpz_cmp_ui (size, 0) > 0)
12677     {
12678       if (next_data_value () == FAILURE)
12679         {
12680           gfc_error ("DATA statement at %L has more variables than values",
12681                      where);
12682           t = FAILURE;
12683           break;
12684         }
12685
12686       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
12687       if (t == FAILURE)
12688         break;
12689
12690       /* If we have more than one element left in the repeat count,
12691          and we have more than one element left in the target variable,
12692          then create a range assignment.  */
12693       /* FIXME: Only done for full arrays for now, since array sections
12694          seem tricky.  */
12695       if (mark == AR_FULL && ref && ref->next == NULL
12696           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
12697         {
12698           mpz_t range;
12699
12700           if (mpz_cmp (size, values.left) >= 0)
12701             {
12702               mpz_init_set (range, values.left);
12703               mpz_sub (size, size, values.left);
12704               mpz_set_ui (values.left, 0);
12705             }
12706           else
12707             {
12708               mpz_init_set (range, size);
12709               mpz_sub (values.left, values.left, size);
12710               mpz_set_ui (size, 0);
12711             }
12712
12713           t = gfc_assign_data_value (var->expr, values.vnode->expr,
12714                                      offset, &range);
12715
12716           mpz_add (offset, offset, range);
12717           mpz_clear (range);
12718
12719           if (t == FAILURE)
12720             break;
12721         }
12722
12723       /* Assign initial value to symbol.  */
12724       else
12725         {
12726           mpz_sub_ui (values.left, values.left, 1);
12727           mpz_sub_ui (size, size, 1);
12728
12729           t = gfc_assign_data_value (var->expr, values.vnode->expr,
12730                                      offset, NULL);
12731           if (t == FAILURE)
12732             break;
12733
12734           if (mark == AR_FULL)
12735             mpz_add_ui (offset, offset, 1);
12736
12737           /* Modify the array section indexes and recalculate the offset
12738              for next element.  */
12739           else if (mark == AR_SECTION)
12740             gfc_advance_section (section_index, ar, &offset);
12741         }
12742     }
12743
12744   if (mark == AR_SECTION)
12745     {
12746       for (i = 0; i < ar->dimen; i++)
12747         mpz_clear (section_index[i]);
12748     }
12749
12750   mpz_clear (size);
12751   mpz_clear (offset);
12752
12753   return t;
12754 }
12755
12756
12757 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
12758
12759 /* Iterate over a list of elements in a DATA statement.  */
12760
12761 static gfc_try
12762 traverse_data_list (gfc_data_variable *var, locus *where)
12763 {
12764   mpz_t trip;
12765   iterator_stack frame;
12766   gfc_expr *e, *start, *end, *step;
12767   gfc_try retval = SUCCESS;
12768
12769   mpz_init (frame.value);
12770   mpz_init (trip);
12771
12772   start = gfc_copy_expr (var->iter.start);
12773   end = gfc_copy_expr (var->iter.end);
12774   step = gfc_copy_expr (var->iter.step);
12775
12776   if (gfc_simplify_expr (start, 1) == FAILURE
12777       || start->expr_type != EXPR_CONSTANT)
12778     {
12779       gfc_error ("start of implied-do loop at %L could not be "
12780                  "simplified to a constant value", &start->where);
12781       retval = FAILURE;
12782       goto cleanup;
12783     }
12784   if (gfc_simplify_expr (end, 1) == FAILURE
12785       || end->expr_type != EXPR_CONSTANT)
12786     {
12787       gfc_error ("end of implied-do loop at %L could not be "
12788                  "simplified to a constant value", &start->where);
12789       retval = FAILURE;
12790       goto cleanup;
12791     }
12792   if (gfc_simplify_expr (step, 1) == FAILURE
12793       || step->expr_type != EXPR_CONSTANT)
12794     {
12795       gfc_error ("step of implied-do loop at %L could not be "
12796                  "simplified to a constant value", &start->where);
12797       retval = FAILURE;
12798       goto cleanup;
12799     }
12800
12801   mpz_set (trip, end->value.integer);
12802   mpz_sub (trip, trip, start->value.integer);
12803   mpz_add (trip, trip, step->value.integer);
12804
12805   mpz_div (trip, trip, step->value.integer);
12806
12807   mpz_set (frame.value, start->value.integer);
12808
12809   frame.prev = iter_stack;
12810   frame.variable = var->iter.var->symtree;
12811   iter_stack = &frame;
12812
12813   while (mpz_cmp_ui (trip, 0) > 0)
12814     {
12815       if (traverse_data_var (var->list, where) == FAILURE)
12816         {
12817           retval = FAILURE;
12818           goto cleanup;
12819         }
12820
12821       e = gfc_copy_expr (var->expr);
12822       if (gfc_simplify_expr (e, 1) == FAILURE)
12823         {
12824           gfc_free_expr (e);
12825           retval = FAILURE;
12826           goto cleanup;
12827         }
12828
12829       mpz_add (frame.value, frame.value, step->value.integer);
12830
12831       mpz_sub_ui (trip, trip, 1);
12832     }
12833
12834 cleanup:
12835   mpz_clear (frame.value);
12836   mpz_clear (trip);
12837
12838   gfc_free_expr (start);
12839   gfc_free_expr (end);
12840   gfc_free_expr (step);
12841
12842   iter_stack = frame.prev;
12843   return retval;
12844 }
12845
12846
12847 /* Type resolve variables in the variable list of a DATA statement.  */
12848
12849 static gfc_try
12850 traverse_data_var (gfc_data_variable *var, locus *where)
12851 {
12852   gfc_try t;
12853
12854   for (; var; var = var->next)
12855     {
12856       if (var->expr == NULL)
12857         t = traverse_data_list (var, where);
12858       else
12859         t = check_data_variable (var, where);
12860
12861       if (t == FAILURE)
12862         return FAILURE;
12863     }
12864
12865   return SUCCESS;
12866 }
12867
12868
12869 /* Resolve the expressions and iterators associated with a data statement.
12870    This is separate from the assignment checking because data lists should
12871    only be resolved once.  */
12872
12873 static gfc_try
12874 resolve_data_variables (gfc_data_variable *d)
12875 {
12876   for (; d; d = d->next)
12877     {
12878       if (d->list == NULL)
12879         {
12880           if (gfc_resolve_expr (d->expr) == FAILURE)
12881             return FAILURE;
12882         }
12883       else
12884         {
12885           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
12886             return FAILURE;
12887
12888           if (resolve_data_variables (d->list) == FAILURE)
12889             return FAILURE;
12890         }
12891     }
12892
12893   return SUCCESS;
12894 }
12895
12896
12897 /* Resolve a single DATA statement.  We implement this by storing a pointer to
12898    the value list into static variables, and then recursively traversing the
12899    variables list, expanding iterators and such.  */
12900
12901 static void
12902 resolve_data (gfc_data *d)
12903 {
12904
12905   if (resolve_data_variables (d->var) == FAILURE)
12906     return;
12907
12908   values.vnode = d->value;
12909   if (d->value == NULL)
12910     mpz_set_ui (values.left, 0);
12911   else
12912     mpz_set (values.left, d->value->repeat);
12913
12914   if (traverse_data_var (d->var, &d->where) == FAILURE)
12915     return;
12916
12917   /* At this point, we better not have any values left.  */
12918
12919   if (next_data_value () == SUCCESS)
12920     gfc_error ("DATA statement at %L has more values than variables",
12921                &d->where);
12922 }
12923
12924
12925 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
12926    accessed by host or use association, is a dummy argument to a pure function,
12927    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
12928    is storage associated with any such variable, shall not be used in the
12929    following contexts: (clients of this function).  */
12930
12931 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
12932    procedure.  Returns zero if assignment is OK, nonzero if there is a
12933    problem.  */
12934 int
12935 gfc_impure_variable (gfc_symbol *sym)
12936 {
12937   gfc_symbol *proc;
12938   gfc_namespace *ns;
12939
12940   if (sym->attr.use_assoc || sym->attr.in_common)
12941     return 1;
12942
12943   /* Check if the symbol's ns is inside the pure procedure.  */
12944   for (ns = gfc_current_ns; ns; ns = ns->parent)
12945     {
12946       if (ns == sym->ns)
12947         break;
12948       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
12949         return 1;
12950     }
12951
12952   proc = sym->ns->proc_name;
12953   if (sym->attr.dummy && gfc_pure (proc)
12954         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
12955                 ||
12956              proc->attr.function))
12957     return 1;
12958
12959   /* TODO: Sort out what can be storage associated, if anything, and include
12960      it here.  In principle equivalences should be scanned but it does not
12961      seem to be possible to storage associate an impure variable this way.  */
12962   return 0;
12963 }
12964
12965
12966 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
12967    current namespace is inside a pure procedure.  */
12968
12969 int
12970 gfc_pure (gfc_symbol *sym)
12971 {
12972   symbol_attribute attr;
12973   gfc_namespace *ns;
12974
12975   if (sym == NULL)
12976     {
12977       /* Check if the current namespace or one of its parents
12978         belongs to a pure procedure.  */
12979       for (ns = gfc_current_ns; ns; ns = ns->parent)
12980         {
12981           sym = ns->proc_name;
12982           if (sym == NULL)
12983             return 0;
12984           attr = sym->attr;
12985           if (attr.flavor == FL_PROCEDURE && attr.pure)
12986             return 1;
12987         }
12988       return 0;
12989     }
12990
12991   attr = sym->attr;
12992
12993   return attr.flavor == FL_PROCEDURE && attr.pure;
12994 }
12995
12996
12997 /* Test whether a symbol is implicitly pure or not.  For a NULL pointer,
12998    checks if the current namespace is implicitly pure.  Note that this
12999    function returns false for a PURE procedure.  */
13000
13001 int
13002 gfc_implicit_pure (gfc_symbol *sym)
13003 {
13004   symbol_attribute attr;
13005
13006   if (sym == NULL)
13007     {
13008       /* Check if the current namespace is implicit_pure.  */
13009       sym = gfc_current_ns->proc_name;
13010       if (sym == NULL)
13011         return 0;
13012       attr = sym->attr;
13013       if (attr.flavor == FL_PROCEDURE
13014             && attr.implicit_pure && !attr.pure)
13015         return 1;
13016       return 0;
13017     }
13018
13019   attr = sym->attr;
13020
13021   return attr.flavor == FL_PROCEDURE && attr.implicit_pure && !attr.pure;
13022 }
13023
13024
13025 /* Test whether the current procedure is elemental or not.  */
13026
13027 int
13028 gfc_elemental (gfc_symbol *sym)
13029 {
13030   symbol_attribute attr;
13031
13032   if (sym == NULL)
13033     sym = gfc_current_ns->proc_name;
13034   if (sym == NULL)
13035     return 0;
13036   attr = sym->attr;
13037
13038   return attr.flavor == FL_PROCEDURE && attr.elemental;
13039 }
13040
13041
13042 /* Warn about unused labels.  */
13043
13044 static void
13045 warn_unused_fortran_label (gfc_st_label *label)
13046 {
13047   if (label == NULL)
13048     return;
13049
13050   warn_unused_fortran_label (label->left);
13051
13052   if (label->defined == ST_LABEL_UNKNOWN)
13053     return;
13054
13055   switch (label->referenced)
13056     {
13057     case ST_LABEL_UNKNOWN:
13058       gfc_warning ("Label %d at %L defined but not used", label->value,
13059                    &label->where);
13060       break;
13061
13062     case ST_LABEL_BAD_TARGET:
13063       gfc_warning ("Label %d at %L defined but cannot be used",
13064                    label->value, &label->where);
13065       break;
13066
13067     default:
13068       break;
13069     }
13070
13071   warn_unused_fortran_label (label->right);
13072 }
13073
13074
13075 /* Returns the sequence type of a symbol or sequence.  */
13076
13077 static seq_type
13078 sequence_type (gfc_typespec ts)
13079 {
13080   seq_type result;
13081   gfc_component *c;
13082
13083   switch (ts.type)
13084   {
13085     case BT_DERIVED:
13086
13087       if (ts.u.derived->components == NULL)
13088         return SEQ_NONDEFAULT;
13089
13090       result = sequence_type (ts.u.derived->components->ts);
13091       for (c = ts.u.derived->components->next; c; c = c->next)
13092         if (sequence_type (c->ts) != result)
13093           return SEQ_MIXED;
13094
13095       return result;
13096
13097     case BT_CHARACTER:
13098       if (ts.kind != gfc_default_character_kind)
13099           return SEQ_NONDEFAULT;
13100
13101       return SEQ_CHARACTER;
13102
13103     case BT_INTEGER:
13104       if (ts.kind != gfc_default_integer_kind)
13105           return SEQ_NONDEFAULT;
13106
13107       return SEQ_NUMERIC;
13108
13109     case BT_REAL:
13110       if (!(ts.kind == gfc_default_real_kind
13111             || ts.kind == gfc_default_double_kind))
13112           return SEQ_NONDEFAULT;
13113
13114       return SEQ_NUMERIC;
13115
13116     case BT_COMPLEX:
13117       if (ts.kind != gfc_default_complex_kind)
13118           return SEQ_NONDEFAULT;
13119
13120       return SEQ_NUMERIC;
13121
13122     case BT_LOGICAL:
13123       if (ts.kind != gfc_default_logical_kind)
13124           return SEQ_NONDEFAULT;
13125
13126       return SEQ_NUMERIC;
13127
13128     default:
13129       return SEQ_NONDEFAULT;
13130   }
13131 }
13132
13133
13134 /* Resolve derived type EQUIVALENCE object.  */
13135
13136 static gfc_try
13137 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
13138 {
13139   gfc_component *c = derived->components;
13140
13141   if (!derived)
13142     return SUCCESS;
13143
13144   /* Shall not be an object of nonsequence derived type.  */
13145   if (!derived->attr.sequence)
13146     {
13147       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
13148                  "attribute to be an EQUIVALENCE object", sym->name,
13149                  &e->where);
13150       return FAILURE;
13151     }
13152
13153   /* Shall not have allocatable components.  */
13154   if (derived->attr.alloc_comp)
13155     {
13156       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
13157                  "components to be an EQUIVALENCE object",sym->name,
13158                  &e->where);
13159       return FAILURE;
13160     }
13161
13162   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
13163     {
13164       gfc_error ("Derived type variable '%s' at %L with default "
13165                  "initialization cannot be in EQUIVALENCE with a variable "
13166                  "in COMMON", sym->name, &e->where);
13167       return FAILURE;
13168     }
13169
13170   for (; c ; c = c->next)
13171     {
13172       if (c->ts.type == BT_DERIVED
13173           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
13174         return FAILURE;
13175
13176       /* Shall not be an object of sequence derived type containing a pointer
13177          in the structure.  */
13178       if (c->attr.pointer)
13179         {
13180           gfc_error ("Derived type variable '%s' at %L with pointer "
13181                      "component(s) cannot be an EQUIVALENCE object",
13182                      sym->name, &e->where);
13183           return FAILURE;
13184         }
13185     }
13186   return SUCCESS;
13187 }
13188
13189
13190 /* Resolve equivalence object. 
13191    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
13192    an allocatable array, an object of nonsequence derived type, an object of
13193    sequence derived type containing a pointer at any level of component
13194    selection, an automatic object, a function name, an entry name, a result
13195    name, a named constant, a structure component, or a subobject of any of
13196    the preceding objects.  A substring shall not have length zero.  A
13197    derived type shall not have components with default initialization nor
13198    shall two objects of an equivalence group be initialized.
13199    Either all or none of the objects shall have an protected attribute.
13200    The simple constraints are done in symbol.c(check_conflict) and the rest
13201    are implemented here.  */
13202
13203 static void
13204 resolve_equivalence (gfc_equiv *eq)
13205 {
13206   gfc_symbol *sym;
13207   gfc_symbol *first_sym;
13208   gfc_expr *e;
13209   gfc_ref *r;
13210   locus *last_where = NULL;
13211   seq_type eq_type, last_eq_type;
13212   gfc_typespec *last_ts;
13213   int object, cnt_protected;
13214   const char *msg;
13215
13216   last_ts = &eq->expr->symtree->n.sym->ts;
13217
13218   first_sym = eq->expr->symtree->n.sym;
13219
13220   cnt_protected = 0;
13221
13222   for (object = 1; eq; eq = eq->eq, object++)
13223     {
13224       e = eq->expr;
13225
13226       e->ts = e->symtree->n.sym->ts;
13227       /* match_varspec might not know yet if it is seeing
13228          array reference or substring reference, as it doesn't
13229          know the types.  */
13230       if (e->ref && e->ref->type == REF_ARRAY)
13231         {
13232           gfc_ref *ref = e->ref;
13233           sym = e->symtree->n.sym;
13234
13235           if (sym->attr.dimension)
13236             {
13237               ref->u.ar.as = sym->as;
13238               ref = ref->next;
13239             }
13240
13241           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
13242           if (e->ts.type == BT_CHARACTER
13243               && ref
13244               && ref->type == REF_ARRAY
13245               && ref->u.ar.dimen == 1
13246               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
13247               && ref->u.ar.stride[0] == NULL)
13248             {
13249               gfc_expr *start = ref->u.ar.start[0];
13250               gfc_expr *end = ref->u.ar.end[0];
13251               void *mem = NULL;
13252
13253               /* Optimize away the (:) reference.  */
13254               if (start == NULL && end == NULL)
13255                 {
13256                   if (e->ref == ref)
13257                     e->ref = ref->next;
13258                   else
13259                     e->ref->next = ref->next;
13260                   mem = ref;
13261                 }
13262               else
13263                 {
13264                   ref->type = REF_SUBSTRING;
13265                   if (start == NULL)
13266                     start = gfc_get_int_expr (gfc_default_integer_kind,
13267                                               NULL, 1);
13268                   ref->u.ss.start = start;
13269                   if (end == NULL && e->ts.u.cl)
13270                     end = gfc_copy_expr (e->ts.u.cl->length);
13271                   ref->u.ss.end = end;
13272                   ref->u.ss.length = e->ts.u.cl;
13273                   e->ts.u.cl = NULL;
13274                 }
13275               ref = ref->next;
13276               free (mem);
13277             }
13278
13279           /* Any further ref is an error.  */
13280           if (ref)
13281             {
13282               gcc_assert (ref->type == REF_ARRAY);
13283               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
13284                          &ref->u.ar.where);
13285               continue;
13286             }
13287         }
13288
13289       if (gfc_resolve_expr (e) == FAILURE)
13290         continue;
13291
13292       sym = e->symtree->n.sym;
13293
13294       if (sym->attr.is_protected)
13295         cnt_protected++;
13296       if (cnt_protected > 0 && cnt_protected != object)
13297         {
13298               gfc_error ("Either all or none of the objects in the "
13299                          "EQUIVALENCE set at %L shall have the "
13300                          "PROTECTED attribute",
13301                          &e->where);
13302               break;
13303         }
13304
13305       /* Shall not equivalence common block variables in a PURE procedure.  */
13306       if (sym->ns->proc_name
13307           && sym->ns->proc_name->attr.pure
13308           && sym->attr.in_common)
13309         {
13310           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
13311                      "object in the pure procedure '%s'",
13312                      sym->name, &e->where, sym->ns->proc_name->name);
13313           break;
13314         }
13315
13316       /* Shall not be a named constant.  */
13317       if (e->expr_type == EXPR_CONSTANT)
13318         {
13319           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
13320                      "object", sym->name, &e->where);
13321           continue;
13322         }
13323
13324       if (e->ts.type == BT_DERIVED
13325           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
13326         continue;
13327
13328       /* Check that the types correspond correctly:
13329          Note 5.28:
13330          A numeric sequence structure may be equivalenced to another sequence
13331          structure, an object of default integer type, default real type, double
13332          precision real type, default logical type such that components of the
13333          structure ultimately only become associated to objects of the same
13334          kind. A character sequence structure may be equivalenced to an object
13335          of default character kind or another character sequence structure.
13336          Other objects may be equivalenced only to objects of the same type and
13337          kind parameters.  */
13338
13339       /* Identical types are unconditionally OK.  */
13340       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
13341         goto identical_types;
13342
13343       last_eq_type = sequence_type (*last_ts);
13344       eq_type = sequence_type (sym->ts);
13345
13346       /* Since the pair of objects is not of the same type, mixed or
13347          non-default sequences can be rejected.  */
13348
13349       msg = "Sequence %s with mixed components in EQUIVALENCE "
13350             "statement at %L with different type objects";
13351       if ((object ==2
13352            && last_eq_type == SEQ_MIXED
13353            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
13354               == FAILURE)
13355           || (eq_type == SEQ_MIXED
13356               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13357                                  &e->where) == FAILURE))
13358         continue;
13359
13360       msg = "Non-default type object or sequence %s in EQUIVALENCE "
13361             "statement at %L with objects of different type";
13362       if ((object ==2
13363            && last_eq_type == SEQ_NONDEFAULT
13364            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
13365                               last_where) == FAILURE)
13366           || (eq_type == SEQ_NONDEFAULT
13367               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13368                                  &e->where) == FAILURE))
13369         continue;
13370
13371       msg ="Non-CHARACTER object '%s' in default CHARACTER "
13372            "EQUIVALENCE statement at %L";
13373       if (last_eq_type == SEQ_CHARACTER
13374           && eq_type != SEQ_CHARACTER
13375           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13376                              &e->where) == FAILURE)
13377                 continue;
13378
13379       msg ="Non-NUMERIC object '%s' in default NUMERIC "
13380            "EQUIVALENCE statement at %L";
13381       if (last_eq_type == SEQ_NUMERIC
13382           && eq_type != SEQ_NUMERIC
13383           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13384                              &e->where) == FAILURE)
13385                 continue;
13386
13387   identical_types:
13388       last_ts =&sym->ts;
13389       last_where = &e->where;
13390
13391       if (!e->ref)
13392         continue;
13393
13394       /* Shall not be an automatic array.  */
13395       if (e->ref->type == REF_ARRAY
13396           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
13397         {
13398           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
13399                      "an EQUIVALENCE object", sym->name, &e->where);
13400           continue;
13401         }
13402
13403       r = e->ref;
13404       while (r)
13405         {
13406           /* Shall not be a structure component.  */
13407           if (r->type == REF_COMPONENT)
13408             {
13409               gfc_error ("Structure component '%s' at %L cannot be an "
13410                          "EQUIVALENCE object",
13411                          r->u.c.component->name, &e->where);
13412               break;
13413             }
13414
13415           /* A substring shall not have length zero.  */
13416           if (r->type == REF_SUBSTRING)
13417             {
13418               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
13419                 {
13420                   gfc_error ("Substring at %L has length zero",
13421                              &r->u.ss.start->where);
13422                   break;
13423                 }
13424             }
13425           r = r->next;
13426         }
13427     }
13428 }
13429
13430
13431 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
13432
13433 static void
13434 resolve_fntype (gfc_namespace *ns)
13435 {
13436   gfc_entry_list *el;
13437   gfc_symbol *sym;
13438
13439   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
13440     return;
13441
13442   /* If there are any entries, ns->proc_name is the entry master
13443      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
13444   if (ns->entries)
13445     sym = ns->entries->sym;
13446   else
13447     sym = ns->proc_name;
13448   if (sym->result == sym
13449       && sym->ts.type == BT_UNKNOWN
13450       && gfc_set_default_type (sym, 0, NULL) == FAILURE
13451       && !sym->attr.untyped)
13452     {
13453       gfc_error ("Function '%s' at %L has no IMPLICIT type",
13454                  sym->name, &sym->declared_at);
13455       sym->attr.untyped = 1;
13456     }
13457
13458   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
13459       && !sym->attr.contained
13460       && !gfc_check_symbol_access (sym->ts.u.derived)
13461       && gfc_check_symbol_access (sym))
13462     {
13463       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
13464                       "%L of PRIVATE type '%s'", sym->name,
13465                       &sym->declared_at, sym->ts.u.derived->name);
13466     }
13467
13468     if (ns->entries)
13469     for (el = ns->entries->next; el; el = el->next)
13470       {
13471         if (el->sym->result == el->sym
13472             && el->sym->ts.type == BT_UNKNOWN
13473             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
13474             && !el->sym->attr.untyped)
13475           {
13476             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
13477                        el->sym->name, &el->sym->declared_at);
13478             el->sym->attr.untyped = 1;
13479           }
13480       }
13481 }
13482
13483
13484 /* 12.3.2.1.1 Defined operators.  */
13485
13486 static gfc_try
13487 check_uop_procedure (gfc_symbol *sym, locus where)
13488 {
13489   gfc_formal_arglist *formal;
13490
13491   if (!sym->attr.function)
13492     {
13493       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
13494                  sym->name, &where);
13495       return FAILURE;
13496     }
13497
13498   if (sym->ts.type == BT_CHARACTER
13499       && !(sym->ts.u.cl && sym->ts.u.cl->length)
13500       && !(sym->result && sym->result->ts.u.cl
13501            && sym->result->ts.u.cl->length))
13502     {
13503       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
13504                  "character length", sym->name, &where);
13505       return FAILURE;
13506     }
13507
13508   formal = sym->formal;
13509   if (!formal || !formal->sym)
13510     {
13511       gfc_error ("User operator procedure '%s' at %L must have at least "
13512                  "one argument", sym->name, &where);
13513       return FAILURE;
13514     }
13515
13516   if (formal->sym->attr.intent != INTENT_IN)
13517     {
13518       gfc_error ("First argument of operator interface at %L must be "
13519                  "INTENT(IN)", &where);
13520       return FAILURE;
13521     }
13522
13523   if (formal->sym->attr.optional)
13524     {
13525       gfc_error ("First argument of operator interface at %L cannot be "
13526                  "optional", &where);
13527       return FAILURE;
13528     }
13529
13530   formal = formal->next;
13531   if (!formal || !formal->sym)
13532     return SUCCESS;
13533
13534   if (formal->sym->attr.intent != INTENT_IN)
13535     {
13536       gfc_error ("Second argument of operator interface at %L must be "
13537                  "INTENT(IN)", &where);
13538       return FAILURE;
13539     }
13540
13541   if (formal->sym->attr.optional)
13542     {
13543       gfc_error ("Second argument of operator interface at %L cannot be "
13544                  "optional", &where);
13545       return FAILURE;
13546     }
13547
13548   if (formal->next)
13549     {
13550       gfc_error ("Operator interface at %L must have, at most, two "
13551                  "arguments", &where);
13552       return FAILURE;
13553     }
13554
13555   return SUCCESS;
13556 }
13557
13558 static void
13559 gfc_resolve_uops (gfc_symtree *symtree)
13560 {
13561   gfc_interface *itr;
13562
13563   if (symtree == NULL)
13564     return;
13565
13566   gfc_resolve_uops (symtree->left);
13567   gfc_resolve_uops (symtree->right);
13568
13569   for (itr = symtree->n.uop->op; itr; itr = itr->next)
13570     check_uop_procedure (itr->sym, itr->sym->declared_at);
13571 }
13572
13573
13574 /* Examine all of the expressions associated with a program unit,
13575    assign types to all intermediate expressions, make sure that all
13576    assignments are to compatible types and figure out which names
13577    refer to which functions or subroutines.  It doesn't check code
13578    block, which is handled by resolve_code.  */
13579
13580 static void
13581 resolve_types (gfc_namespace *ns)
13582 {
13583   gfc_namespace *n;
13584   gfc_charlen *cl;
13585   gfc_data *d;
13586   gfc_equiv *eq;
13587   gfc_namespace* old_ns = gfc_current_ns;
13588
13589   /* Check that all IMPLICIT types are ok.  */
13590   if (!ns->seen_implicit_none)
13591     {
13592       unsigned letter;
13593       for (letter = 0; letter != GFC_LETTERS; ++letter)
13594         if (ns->set_flag[letter]
13595             && resolve_typespec_used (&ns->default_type[letter],
13596                                       &ns->implicit_loc[letter],
13597                                       NULL) == FAILURE)
13598           return;
13599     }
13600
13601   gfc_current_ns = ns;
13602
13603   resolve_entries (ns);
13604
13605   resolve_common_vars (ns->blank_common.head, false);
13606   resolve_common_blocks (ns->common_root);
13607
13608   resolve_contained_functions (ns);
13609
13610   if (ns->proc_name && ns->proc_name->attr.flavor == FL_PROCEDURE
13611       && ns->proc_name->attr.if_source == IFSRC_IFBODY)
13612     resolve_formal_arglist (ns->proc_name);
13613
13614   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
13615
13616   for (cl = ns->cl_list; cl; cl = cl->next)
13617     resolve_charlen (cl);
13618
13619   gfc_traverse_ns (ns, resolve_symbol);
13620
13621   resolve_fntype (ns);
13622
13623   for (n = ns->contained; n; n = n->sibling)
13624     {
13625       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
13626         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
13627                    "also be PURE", n->proc_name->name,
13628                    &n->proc_name->declared_at);
13629
13630       resolve_types (n);
13631     }
13632
13633   forall_flag = 0;
13634   do_concurrent_flag = 0;
13635   gfc_check_interfaces (ns);
13636
13637   gfc_traverse_ns (ns, resolve_values);
13638
13639   if (ns->save_all)
13640     gfc_save_all (ns);
13641
13642   iter_stack = NULL;
13643   for (d = ns->data; d; d = d->next)
13644     resolve_data (d);
13645
13646   iter_stack = NULL;
13647   gfc_traverse_ns (ns, gfc_formalize_init_value);
13648
13649   gfc_traverse_ns (ns, gfc_verify_binding_labels);
13650
13651   if (ns->common_root != NULL)
13652     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
13653
13654   for (eq = ns->equiv; eq; eq = eq->next)
13655     resolve_equivalence (eq);
13656
13657   /* Warn about unused labels.  */
13658   if (warn_unused_label)
13659     warn_unused_fortran_label (ns->st_labels);
13660
13661   gfc_resolve_uops (ns->uop_root);
13662
13663   gfc_current_ns = old_ns;
13664 }
13665
13666
13667 /* Call resolve_code recursively.  */
13668
13669 static void
13670 resolve_codes (gfc_namespace *ns)
13671 {
13672   gfc_namespace *n;
13673   bitmap_obstack old_obstack;
13674
13675   if (ns->resolved == 1)
13676     return;
13677
13678   for (n = ns->contained; n; n = n->sibling)
13679     resolve_codes (n);
13680
13681   gfc_current_ns = ns;
13682
13683   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
13684   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
13685     cs_base = NULL;
13686
13687   /* Set to an out of range value.  */
13688   current_entry_id = -1;
13689
13690   old_obstack = labels_obstack;
13691   bitmap_obstack_initialize (&labels_obstack);
13692
13693   resolve_code (ns->code, ns);
13694
13695   bitmap_obstack_release (&labels_obstack);
13696   labels_obstack = old_obstack;
13697 }
13698
13699
13700 /* This function is called after a complete program unit has been compiled.
13701    Its purpose is to examine all of the expressions associated with a program
13702    unit, assign types to all intermediate expressions, make sure that all
13703    assignments are to compatible types and figure out which names refer to
13704    which functions or subroutines.  */
13705
13706 void
13707 gfc_resolve (gfc_namespace *ns)
13708 {
13709   gfc_namespace *old_ns;
13710   code_stack *old_cs_base;
13711
13712   if (ns->resolved)
13713     return;
13714
13715   ns->resolved = -1;
13716   old_ns = gfc_current_ns;
13717   old_cs_base = cs_base;
13718
13719   resolve_types (ns);
13720   resolve_codes (ns);
13721
13722   gfc_current_ns = old_ns;
13723   cs_base = old_cs_base;
13724   ns->resolved = 1;
13725
13726   gfc_run_passes (ns);
13727 }