OSDN Git Service

cec45cab44d661936269528b193cc42a172ca5a8
[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 block.  */
62
63 static int forall_flag;
64
65 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
66
67 static int omp_workshare_flag;
68
69 /* Nonzero if we are processing a formal arglist. The corresponding function
70    resets the flag each time that it is read.  */
71 static int formal_arg_flag = 0;
72
73 /* True if we are resolving a specification expression.  */
74 static int specification_expr = 0;
75
76 /* The id of the last entry seen.  */
77 static int current_entry_id;
78
79 /* We use bitmaps to determine if a branch target is valid.  */
80 static bitmap_obstack labels_obstack;
81
82 /* True when simplifying a EXPR_VARIABLE argument to an inquiry function.  */
83 static bool inquiry_argument = false;
84
85 int
86 gfc_is_formal_arg (void)
87 {
88   return formal_arg_flag;
89 }
90
91 /* Is the symbol host associated?  */
92 static bool
93 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
94 {
95   for (ns = ns->parent; ns; ns = ns->parent)
96     {      
97       if (sym->ns == ns)
98         return true;
99     }
100
101   return false;
102 }
103
104 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
105    an ABSTRACT derived-type.  If where is not NULL, an error message with that
106    locus is printed, optionally using name.  */
107
108 static gfc_try
109 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
110 {
111   if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
112     {
113       if (where)
114         {
115           if (name)
116             gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
117                        name, where, ts->u.derived->name);
118           else
119             gfc_error ("ABSTRACT type '%s' used at %L",
120                        ts->u.derived->name, where);
121         }
122
123       return FAILURE;
124     }
125
126   return SUCCESS;
127 }
128
129
130 static void resolve_symbol (gfc_symbol *sym);
131 static gfc_try resolve_intrinsic (gfc_symbol *sym, locus *loc);
132
133
134 /* Resolve the interface for a PROCEDURE declaration or procedure pointer.  */
135
136 static gfc_try
137 resolve_procedure_interface (gfc_symbol *sym)
138 {
139   if (sym->ts.interface == sym)
140     {
141       gfc_error ("PROCEDURE '%s' at %L may not be used as its own interface",
142                  sym->name, &sym->declared_at);
143       return FAILURE;
144     }
145   if (sym->ts.interface->attr.procedure)
146     {
147       gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared "
148                  "in a later PROCEDURE statement", sym->ts.interface->name,
149                  sym->name, &sym->declared_at);
150       return FAILURE;
151     }
152
153   /* Get the attributes from the interface (now resolved).  */
154   if (sym->ts.interface->attr.if_source || sym->ts.interface->attr.intrinsic)
155     {
156       gfc_symbol *ifc = sym->ts.interface;
157       resolve_symbol (ifc);
158
159       if (ifc->attr.intrinsic)
160         resolve_intrinsic (ifc, &ifc->declared_at);
161
162       if (ifc->result)
163         {
164           sym->ts = ifc->result->ts;
165           sym->result = sym;
166         }
167       else   
168         sym->ts = ifc->ts;
169       sym->ts.interface = ifc;
170       sym->attr.function = ifc->attr.function;
171       sym->attr.subroutine = ifc->attr.subroutine;
172       gfc_copy_formal_args (sym, ifc);
173
174       sym->attr.allocatable = ifc->attr.allocatable;
175       sym->attr.pointer = ifc->attr.pointer;
176       sym->attr.pure = ifc->attr.pure;
177       sym->attr.elemental = ifc->attr.elemental;
178       sym->attr.dimension = ifc->attr.dimension;
179       sym->attr.contiguous = ifc->attr.contiguous;
180       sym->attr.recursive = ifc->attr.recursive;
181       sym->attr.always_explicit = ifc->attr.always_explicit;
182       sym->attr.ext_attr |= ifc->attr.ext_attr;
183       sym->attr.is_bind_c = ifc->attr.is_bind_c;
184       /* Copy array spec.  */
185       sym->as = gfc_copy_array_spec (ifc->as);
186       if (sym->as)
187         {
188           int i;
189           for (i = 0; i < sym->as->rank; i++)
190             {
191               gfc_expr_replace_symbols (sym->as->lower[i], sym);
192               gfc_expr_replace_symbols (sym->as->upper[i], sym);
193             }
194         }
195       /* Copy char length.  */
196       if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
197         {
198           sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
199           gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
200           if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
201               && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
202             return FAILURE;
203         }
204     }
205   else if (sym->ts.interface->name[0] != '\0')
206     {
207       gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
208                  sym->ts.interface->name, sym->name, &sym->declared_at);
209       return FAILURE;
210     }
211
212   return SUCCESS;
213 }
214
215
216 /* Resolve types of formal argument lists.  These have to be done early so that
217    the formal argument lists of module procedures can be copied to the
218    containing module before the individual procedures are resolved
219    individually.  We also resolve argument lists of procedures in interface
220    blocks because they are self-contained scoping units.
221
222    Since a dummy argument cannot be a non-dummy procedure, the only
223    resort left for untyped names are the IMPLICIT types.  */
224
225 static void
226 resolve_formal_arglist (gfc_symbol *proc)
227 {
228   gfc_formal_arglist *f;
229   gfc_symbol *sym;
230   int i;
231
232   if (proc->result != NULL)
233     sym = proc->result;
234   else
235     sym = proc;
236
237   if (gfc_elemental (proc)
238       || sym->attr.pointer || sym->attr.allocatable
239       || (sym->as && sym->as->rank > 0))
240     {
241       proc->attr.always_explicit = 1;
242       sym->attr.always_explicit = 1;
243     }
244
245   formal_arg_flag = 1;
246
247   for (f = proc->formal; f; f = f->next)
248     {
249       sym = f->sym;
250
251       if (sym == NULL)
252         {
253           /* Alternate return placeholder.  */
254           if (gfc_elemental (proc))
255             gfc_error ("Alternate return specifier in elemental subroutine "
256                        "'%s' at %L is not allowed", proc->name,
257                        &proc->declared_at);
258           if (proc->attr.function)
259             gfc_error ("Alternate return specifier in function "
260                        "'%s' at %L is not allowed", proc->name,
261                        &proc->declared_at);
262           continue;
263         }
264       else if (sym->attr.procedure && sym->ts.interface
265                && sym->attr.if_source != IFSRC_DECL)
266         resolve_procedure_interface (sym);
267
268       if (sym->attr.if_source != IFSRC_UNKNOWN)
269         resolve_formal_arglist (sym);
270
271       if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
272         {
273           if (gfc_pure (proc) && !gfc_pure (sym))
274             {
275               gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
276                          "also be PURE", sym->name, &sym->declared_at);
277               continue;
278             }
279
280           if (proc->attr.implicit_pure && !gfc_pure(sym))
281             proc->attr.implicit_pure = 0;
282
283           if (gfc_elemental (proc))
284             {
285               gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
286                          "procedure", &sym->declared_at);
287               continue;
288             }
289
290           if (sym->attr.function
291                 && sym->ts.type == BT_UNKNOWN
292                 && sym->attr.intrinsic)
293             {
294               gfc_intrinsic_sym *isym;
295               isym = gfc_find_function (sym->name);
296               if (isym == NULL || !isym->specific)
297                 {
298                   gfc_error ("Unable to find a specific INTRINSIC procedure "
299                              "for the reference '%s' at %L", sym->name,
300                              &sym->declared_at);
301                 }
302               sym->ts = isym->ts;
303             }
304
305           continue;
306         }
307
308       if (sym->ts.type == BT_UNKNOWN && !proc->attr.intrinsic
309           && (!sym->attr.function || sym->result == sym))
310         gfc_set_default_type (sym, 1, sym->ns);
311
312       gfc_resolve_array_spec (sym->as, 0);
313
314       /* We can't tell if an array with dimension (:) is assumed or deferred
315          shape until we know if it has the pointer or allocatable attributes.
316       */
317       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
318           && !(sym->attr.pointer || sym->attr.allocatable)
319           && sym->attr.flavor != FL_PROCEDURE)
320         {
321           sym->as->type = AS_ASSUMED_SHAPE;
322           for (i = 0; i < sym->as->rank; i++)
323             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
324                                                   NULL, 1);
325         }
326
327       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
328           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
329           || sym->attr.optional)
330         {
331           proc->attr.always_explicit = 1;
332           if (proc->result)
333             proc->result->attr.always_explicit = 1;
334         }
335
336       /* If the flavor is unknown at this point, it has to be a variable.
337          A procedure specification would have already set the type.  */
338
339       if (sym->attr.flavor == FL_UNKNOWN)
340         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
341
342       if (gfc_pure (proc) && !sym->attr.pointer
343           && sym->attr.flavor != FL_PROCEDURE)
344         {
345           if (proc->attr.function && sym->attr.intent != INTENT_IN)
346             {
347               if (sym->attr.value)
348                 gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s' "
349                                 "of pure function '%s' at %L with VALUE "
350                                 "attribute but without INTENT(IN)", sym->name,
351                                 proc->name, &sym->declared_at);
352               else
353                 gfc_error ("Argument '%s' of pure function '%s' at %L must be "
354                            "INTENT(IN) or VALUE", sym->name, proc->name,
355                            &sym->declared_at);
356             }
357
358           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
359             {
360               if (sym->attr.value)
361                 gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s' "
362                                 "of pure subroutine '%s' at %L with VALUE "
363                                 "attribute but without INTENT", sym->name,
364                                 proc->name, &sym->declared_at);
365               else
366                 gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
367                        "have its INTENT specified or have the VALUE "
368                        "attribute", sym->name, proc->name, &sym->declared_at);
369             }
370         }
371
372       if (proc->attr.implicit_pure && !sym->attr.pointer
373           && sym->attr.flavor != FL_PROCEDURE)
374         {
375           if (proc->attr.function && sym->attr.intent != INTENT_IN)
376             proc->attr.implicit_pure = 0;
377
378           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
379             proc->attr.implicit_pure = 0;
380         }
381
382       if (gfc_elemental (proc))
383         {
384           /* F2008, C1289.  */
385           if (sym->attr.codimension)
386             {
387               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
388                          "procedure", sym->name, &sym->declared_at);
389               continue;
390             }
391
392           if (sym->as != NULL)
393             {
394               gfc_error ("Argument '%s' of elemental procedure at %L must "
395                          "be scalar", sym->name, &sym->declared_at);
396               continue;
397             }
398
399           if (sym->attr.allocatable)
400             {
401               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
402                          "have the ALLOCATABLE attribute", sym->name,
403                          &sym->declared_at);
404               continue;
405             }
406
407           if (sym->attr.pointer)
408             {
409               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
410                          "have the POINTER attribute", sym->name,
411                          &sym->declared_at);
412               continue;
413             }
414
415           if (sym->attr.flavor == FL_PROCEDURE)
416             {
417               gfc_error ("Dummy procedure '%s' not allowed in elemental "
418                          "procedure '%s' at %L", sym->name, proc->name,
419                          &sym->declared_at);
420               continue;
421             }
422
423           if (sym->attr.intent == INTENT_UNKNOWN)
424             {
425               gfc_error ("Argument '%s' of elemental procedure '%s' at %L must "
426                          "have its INTENT specified", sym->name, proc->name,
427                          &sym->declared_at);
428               continue;
429             }
430         }
431
432       /* Each dummy shall be specified to be scalar.  */
433       if (proc->attr.proc == PROC_ST_FUNCTION)
434         {
435           if (sym->as != NULL)
436             {
437               gfc_error ("Argument '%s' of statement function at %L must "
438                          "be scalar", sym->name, &sym->declared_at);
439               continue;
440             }
441
442           if (sym->ts.type == BT_CHARACTER)
443             {
444               gfc_charlen *cl = sym->ts.u.cl;
445               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
446                 {
447                   gfc_error ("Character-valued argument '%s' of statement "
448                              "function at %L must have constant length",
449                              sym->name, &sym->declared_at);
450                   continue;
451                 }
452             }
453         }
454     }
455   formal_arg_flag = 0;
456 }
457
458
459 /* Work function called when searching for symbols that have argument lists
460    associated with them.  */
461
462 static void
463 find_arglists (gfc_symbol *sym)
464 {
465   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
466     return;
467
468   resolve_formal_arglist (sym);
469 }
470
471
472 /* Given a namespace, resolve all formal argument lists within the namespace.
473  */
474
475 static void
476 resolve_formal_arglists (gfc_namespace *ns)
477 {
478   if (ns == NULL)
479     return;
480
481   gfc_traverse_ns (ns, find_arglists);
482 }
483
484
485 static void
486 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
487 {
488   gfc_try t;
489
490   /* If this namespace is not a function or an entry master function,
491      ignore it.  */
492   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
493       || sym->attr.entry_master)
494     return;
495
496   /* Try to find out of what the return type is.  */
497   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
498     {
499       t = gfc_set_default_type (sym->result, 0, ns);
500
501       if (t == FAILURE && !sym->result->attr.untyped)
502         {
503           if (sym->result == sym)
504             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
505                        sym->name, &sym->declared_at);
506           else if (!sym->result->attr.proc_pointer)
507             gfc_error ("Result '%s' of contained function '%s' at %L has "
508                        "no IMPLICIT type", sym->result->name, sym->name,
509                        &sym->result->declared_at);
510           sym->result->attr.untyped = 1;
511         }
512     }
513
514   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
515      type, lists the only ways a character length value of * can be used:
516      dummy arguments of procedures, named constants, and function results
517      in external functions.  Internal function results and results of module
518      procedures are not on this list, ergo, not permitted.  */
519
520   if (sym->result->ts.type == BT_CHARACTER)
521     {
522       gfc_charlen *cl = sym->result->ts.u.cl;
523       if ((!cl || !cl->length) && !sym->result->ts.deferred)
524         {
525           /* See if this is a module-procedure and adapt error message
526              accordingly.  */
527           bool module_proc;
528           gcc_assert (ns->parent && ns->parent->proc_name);
529           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
530
531           gfc_error ("Character-valued %s '%s' at %L must not be"
532                      " assumed length",
533                      module_proc ? _("module procedure")
534                                  : _("internal function"),
535                      sym->name, &sym->declared_at);
536         }
537     }
538 }
539
540
541 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
542    introduce duplicates.  */
543
544 static void
545 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
546 {
547   gfc_formal_arglist *f, *new_arglist;
548   gfc_symbol *new_sym;
549
550   for (; new_args != NULL; new_args = new_args->next)
551     {
552       new_sym = new_args->sym;
553       /* See if this arg is already in the formal argument list.  */
554       for (f = proc->formal; f; f = f->next)
555         {
556           if (new_sym == f->sym)
557             break;
558         }
559
560       if (f)
561         continue;
562
563       /* Add a new argument.  Argument order is not important.  */
564       new_arglist = gfc_get_formal_arglist ();
565       new_arglist->sym = new_sym;
566       new_arglist->next = proc->formal;
567       proc->formal  = new_arglist;
568     }
569 }
570
571
572 /* Flag the arguments that are not present in all entries.  */
573
574 static void
575 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
576 {
577   gfc_formal_arglist *f, *head;
578   head = new_args;
579
580   for (f = proc->formal; f; f = f->next)
581     {
582       if (f->sym == NULL)
583         continue;
584
585       for (new_args = head; new_args; new_args = new_args->next)
586         {
587           if (new_args->sym == f->sym)
588             break;
589         }
590
591       if (new_args)
592         continue;
593
594       f->sym->attr.not_always_present = 1;
595     }
596 }
597
598
599 /* Resolve alternate entry points.  If a symbol has multiple entry points we
600    create a new master symbol for the main routine, and turn the existing
601    symbol into an entry point.  */
602
603 static void
604 resolve_entries (gfc_namespace *ns)
605 {
606   gfc_namespace *old_ns;
607   gfc_code *c;
608   gfc_symbol *proc;
609   gfc_entry_list *el;
610   char name[GFC_MAX_SYMBOL_LEN + 1];
611   static int master_count = 0;
612
613   if (ns->proc_name == NULL)
614     return;
615
616   /* No need to do anything if this procedure doesn't have alternate entry
617      points.  */
618   if (!ns->entries)
619     return;
620
621   /* We may already have resolved alternate entry points.  */
622   if (ns->proc_name->attr.entry_master)
623     return;
624
625   /* If this isn't a procedure something has gone horribly wrong.  */
626   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
627
628   /* Remember the current namespace.  */
629   old_ns = gfc_current_ns;
630
631   gfc_current_ns = ns;
632
633   /* Add the main entry point to the list of entry points.  */
634   el = gfc_get_entry_list ();
635   el->sym = ns->proc_name;
636   el->id = 0;
637   el->next = ns->entries;
638   ns->entries = el;
639   ns->proc_name->attr.entry = 1;
640
641   /* If it is a module function, it needs to be in the right namespace
642      so that gfc_get_fake_result_decl can gather up the results. The
643      need for this arose in get_proc_name, where these beasts were
644      left in their own namespace, to keep prior references linked to
645      the entry declaration.*/
646   if (ns->proc_name->attr.function
647       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
648     el->sym->ns = ns;
649
650   /* Do the same for entries where the master is not a module
651      procedure.  These are retained in the module namespace because
652      of the module procedure declaration.  */
653   for (el = el->next; el; el = el->next)
654     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
655           && el->sym->attr.mod_proc)
656       el->sym->ns = ns;
657   el = ns->entries;
658
659   /* Add an entry statement for it.  */
660   c = gfc_get_code ();
661   c->op = EXEC_ENTRY;
662   c->ext.entry = el;
663   c->next = ns->code;
664   ns->code = c;
665
666   /* Create a new symbol for the master function.  */
667   /* Give the internal function a unique name (within this file).
668      Also include the function name so the user has some hope of figuring
669      out what is going on.  */
670   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
671             master_count++, ns->proc_name->name);
672   gfc_get_ha_symbol (name, &proc);
673   gcc_assert (proc != NULL);
674
675   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
676   if (ns->proc_name->attr.subroutine)
677     gfc_add_subroutine (&proc->attr, proc->name, NULL);
678   else
679     {
680       gfc_symbol *sym;
681       gfc_typespec *ts, *fts;
682       gfc_array_spec *as, *fas;
683       gfc_add_function (&proc->attr, proc->name, NULL);
684       proc->result = proc;
685       fas = ns->entries->sym->as;
686       fas = fas ? fas : ns->entries->sym->result->as;
687       fts = &ns->entries->sym->result->ts;
688       if (fts->type == BT_UNKNOWN)
689         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
690       for (el = ns->entries->next; el; el = el->next)
691         {
692           ts = &el->sym->result->ts;
693           as = el->sym->as;
694           as = as ? as : el->sym->result->as;
695           if (ts->type == BT_UNKNOWN)
696             ts = gfc_get_default_type (el->sym->result->name, NULL);
697
698           if (! gfc_compare_types (ts, fts)
699               || (el->sym->result->attr.dimension
700                   != ns->entries->sym->result->attr.dimension)
701               || (el->sym->result->attr.pointer
702                   != ns->entries->sym->result->attr.pointer))
703             break;
704           else if (as && fas && ns->entries->sym->result != el->sym->result
705                       && gfc_compare_array_spec (as, fas) == 0)
706             gfc_error ("Function %s at %L has entries with mismatched "
707                        "array specifications", ns->entries->sym->name,
708                        &ns->entries->sym->declared_at);
709           /* The characteristics need to match and thus both need to have
710              the same string length, i.e. both len=*, or both len=4.
711              Having both len=<variable> is also possible, but difficult to
712              check at compile time.  */
713           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
714                    && (((ts->u.cl->length && !fts->u.cl->length)
715                         ||(!ts->u.cl->length && fts->u.cl->length))
716                        || (ts->u.cl->length
717                            && ts->u.cl->length->expr_type
718                               != fts->u.cl->length->expr_type)
719                        || (ts->u.cl->length
720                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
721                            && mpz_cmp (ts->u.cl->length->value.integer,
722                                        fts->u.cl->length->value.integer) != 0)))
723             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
724                             "entries returning variables of different "
725                             "string lengths", ns->entries->sym->name,
726                             &ns->entries->sym->declared_at);
727         }
728
729       if (el == NULL)
730         {
731           sym = ns->entries->sym->result;
732           /* All result types the same.  */
733           proc->ts = *fts;
734           if (sym->attr.dimension)
735             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
736           if (sym->attr.pointer)
737             gfc_add_pointer (&proc->attr, NULL);
738         }
739       else
740         {
741           /* Otherwise the result will be passed through a union by
742              reference.  */
743           proc->attr.mixed_entry_master = 1;
744           for (el = ns->entries; el; el = el->next)
745             {
746               sym = el->sym->result;
747               if (sym->attr.dimension)
748                 {
749                   if (el == ns->entries)
750                     gfc_error ("FUNCTION result %s can't be an array in "
751                                "FUNCTION %s at %L", sym->name,
752                                ns->entries->sym->name, &sym->declared_at);
753                   else
754                     gfc_error ("ENTRY result %s can't be an array in "
755                                "FUNCTION %s at %L", sym->name,
756                                ns->entries->sym->name, &sym->declared_at);
757                 }
758               else if (sym->attr.pointer)
759                 {
760                   if (el == ns->entries)
761                     gfc_error ("FUNCTION result %s can't be a POINTER in "
762                                "FUNCTION %s at %L", sym->name,
763                                ns->entries->sym->name, &sym->declared_at);
764                   else
765                     gfc_error ("ENTRY result %s can't be a POINTER in "
766                                "FUNCTION %s at %L", sym->name,
767                                ns->entries->sym->name, &sym->declared_at);
768                 }
769               else
770                 {
771                   ts = &sym->ts;
772                   if (ts->type == BT_UNKNOWN)
773                     ts = gfc_get_default_type (sym->name, NULL);
774                   switch (ts->type)
775                     {
776                     case BT_INTEGER:
777                       if (ts->kind == gfc_default_integer_kind)
778                         sym = NULL;
779                       break;
780                     case BT_REAL:
781                       if (ts->kind == gfc_default_real_kind
782                           || ts->kind == gfc_default_double_kind)
783                         sym = NULL;
784                       break;
785                     case BT_COMPLEX:
786                       if (ts->kind == gfc_default_complex_kind)
787                         sym = NULL;
788                       break;
789                     case BT_LOGICAL:
790                       if (ts->kind == gfc_default_logical_kind)
791                         sym = NULL;
792                       break;
793                     case BT_UNKNOWN:
794                       /* We will issue error elsewhere.  */
795                       sym = NULL;
796                       break;
797                     default:
798                       break;
799                     }
800                   if (sym)
801                     {
802                       if (el == ns->entries)
803                         gfc_error ("FUNCTION result %s can't be of type %s "
804                                    "in FUNCTION %s at %L", sym->name,
805                                    gfc_typename (ts), ns->entries->sym->name,
806                                    &sym->declared_at);
807                       else
808                         gfc_error ("ENTRY result %s can't be of type %s "
809                                    "in FUNCTION %s at %L", sym->name,
810                                    gfc_typename (ts), ns->entries->sym->name,
811                                    &sym->declared_at);
812                     }
813                 }
814             }
815         }
816     }
817   proc->attr.access = ACCESS_PRIVATE;
818   proc->attr.entry_master = 1;
819
820   /* Merge all the entry point arguments.  */
821   for (el = ns->entries; el; el = el->next)
822     merge_argument_lists (proc, el->sym->formal);
823
824   /* Check the master formal arguments for any that are not
825      present in all entry points.  */
826   for (el = ns->entries; el; el = el->next)
827     check_argument_lists (proc, el->sym->formal);
828
829   /* Use the master function for the function body.  */
830   ns->proc_name = proc;
831
832   /* Finalize the new symbols.  */
833   gfc_commit_symbols ();
834
835   /* Restore the original namespace.  */
836   gfc_current_ns = old_ns;
837 }
838
839
840 /* Resolve common variables.  */
841 static void
842 resolve_common_vars (gfc_symbol *sym, bool named_common)
843 {
844   gfc_symbol *csym = sym;
845
846   for (; csym; csym = csym->common_next)
847     {
848       if (csym->value || csym->attr.data)
849         {
850           if (!csym->ns->is_block_data)
851             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
852                             "but only in BLOCK DATA initialization is "
853                             "allowed", csym->name, &csym->declared_at);
854           else if (!named_common)
855             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
856                             "in a blank COMMON but initialization is only "
857                             "allowed in named common blocks", csym->name,
858                             &csym->declared_at);
859         }
860
861       if (csym->ts.type != BT_DERIVED)
862         continue;
863
864       if (!(csym->ts.u.derived->attr.sequence
865             || csym->ts.u.derived->attr.is_bind_c))
866         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
867                        "has neither the SEQUENCE nor the BIND(C) "
868                        "attribute", csym->name, &csym->declared_at);
869       if (csym->ts.u.derived->attr.alloc_comp)
870         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
871                        "has an ultimate component that is "
872                        "allocatable", csym->name, &csym->declared_at);
873       if (gfc_has_default_initializer (csym->ts.u.derived))
874         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
875                        "may not have default initializer", csym->name,
876                        &csym->declared_at);
877
878       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
879         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
880     }
881 }
882
883 /* Resolve common blocks.  */
884 static void
885 resolve_common_blocks (gfc_symtree *common_root)
886 {
887   gfc_symbol *sym;
888
889   if (common_root == NULL)
890     return;
891
892   if (common_root->left)
893     resolve_common_blocks (common_root->left);
894   if (common_root->right)
895     resolve_common_blocks (common_root->right);
896
897   resolve_common_vars (common_root->n.common->head, true);
898
899   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
900   if (sym == NULL)
901     return;
902
903   if (sym->attr.flavor == FL_PARAMETER)
904     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
905                sym->name, &common_root->n.common->where, &sym->declared_at);
906
907   if (sym->attr.intrinsic)
908     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
909                sym->name, &common_root->n.common->where);
910   else if (sym->attr.result
911            || gfc_is_function_return_value (sym, gfc_current_ns))
912     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
913                     "that is also a function result", sym->name,
914                     &common_root->n.common->where);
915   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
916            && sym->attr.proc != PROC_ST_FUNCTION)
917     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
918                     "that is also a global procedure", sym->name,
919                     &common_root->n.common->where);
920 }
921
922
923 /* Resolve contained function types.  Because contained functions can call one
924    another, they have to be worked out before any of the contained procedures
925    can be resolved.
926
927    The good news is that if a function doesn't already have a type, the only
928    way it can get one is through an IMPLICIT type or a RESULT variable, because
929    by definition contained functions are contained namespace they're contained
930    in, not in a sibling or parent namespace.  */
931
932 static void
933 resolve_contained_functions (gfc_namespace *ns)
934 {
935   gfc_namespace *child;
936   gfc_entry_list *el;
937
938   resolve_formal_arglists (ns);
939
940   for (child = ns->contained; child; child = child->sibling)
941     {
942       /* Resolve alternate entry points first.  */
943       resolve_entries (child);
944
945       /* Then check function return types.  */
946       resolve_contained_fntype (child->proc_name, child);
947       for (el = child->entries; el; el = el->next)
948         resolve_contained_fntype (el->sym, child);
949     }
950 }
951
952
953 /* Resolve all of the elements of a structure constructor and make sure that
954    the types are correct. The 'init' flag indicates that the given
955    constructor is an initializer.  */
956
957 static gfc_try
958 resolve_structure_cons (gfc_expr *expr, int init)
959 {
960   gfc_constructor *cons;
961   gfc_component *comp;
962   gfc_try t;
963   symbol_attribute a;
964
965   t = SUCCESS;
966
967   if (expr->ts.type == BT_DERIVED)
968     resolve_symbol (expr->ts.u.derived);
969
970   cons = gfc_constructor_first (expr->value.constructor);
971   /* A constructor may have references if it is the result of substituting a
972      parameter variable.  In this case we just pull out the component we
973      want.  */
974   if (expr->ref)
975     comp = expr->ref->u.c.sym->components;
976   else
977     comp = expr->ts.u.derived->components;
978
979   /* See if the user is trying to invoke a structure constructor for one of
980      the iso_c_binding derived types.  */
981   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
982       && expr->ts.u.derived->ts.is_iso_c && cons
983       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
984     {
985       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
986                  expr->ts.u.derived->name, &(expr->where));
987       return FAILURE;
988     }
989
990   /* Return if structure constructor is c_null_(fun)prt.  */
991   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
992       && expr->ts.u.derived->ts.is_iso_c && cons
993       && cons->expr && cons->expr->expr_type == EXPR_NULL)
994     return SUCCESS;
995
996   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
997     {
998       int rank;
999
1000       if (!cons->expr)
1001         continue;
1002
1003       if (gfc_resolve_expr (cons->expr) == FAILURE)
1004         {
1005           t = FAILURE;
1006           continue;
1007         }
1008
1009       rank = comp->as ? comp->as->rank : 0;
1010       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
1011           && (comp->attr.allocatable || cons->expr->rank))
1012         {
1013           gfc_error ("The rank of the element in the derived type "
1014                      "constructor at %L does not match that of the "
1015                      "component (%d/%d)", &cons->expr->where,
1016                      cons->expr->rank, rank);
1017           t = FAILURE;
1018         }
1019
1020       /* If we don't have the right type, try to convert it.  */
1021
1022       if (!comp->attr.proc_pointer &&
1023           !gfc_compare_types (&cons->expr->ts, &comp->ts))
1024         {
1025           t = FAILURE;
1026           if (strcmp (comp->name, "_extends") == 0)
1027             {
1028               /* Can afford to be brutal with the _extends initializer.
1029                  The derived type can get lost because it is PRIVATE
1030                  but it is not usage constrained by the standard.  */
1031               cons->expr->ts = comp->ts;
1032               t = SUCCESS;
1033             }
1034           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
1035             gfc_error ("The element in the derived type constructor at %L, "
1036                        "for pointer component '%s', is %s but should be %s",
1037                        &cons->expr->where, comp->name,
1038                        gfc_basic_typename (cons->expr->ts.type),
1039                        gfc_basic_typename (comp->ts.type));
1040           else
1041             t = gfc_convert_type (cons->expr, &comp->ts, 1);
1042         }
1043
1044       /* For strings, the length of the constructor should be the same as
1045          the one of the structure, ensure this if the lengths are known at
1046          compile time and when we are dealing with PARAMETER or structure
1047          constructors.  */
1048       if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1049           && comp->ts.u.cl->length
1050           && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1051           && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1052           && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1053           && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1054                       comp->ts.u.cl->length->value.integer) != 0)
1055         {
1056           if (cons->expr->expr_type == EXPR_VARIABLE
1057               && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1058             {
1059               /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1060                  to make use of the gfc_resolve_character_array_constructor
1061                  machinery.  The expression is later simplified away to
1062                  an array of string literals.  */
1063               gfc_expr *para = cons->expr;
1064               cons->expr = gfc_get_expr ();
1065               cons->expr->ts = para->ts;
1066               cons->expr->where = para->where;
1067               cons->expr->expr_type = EXPR_ARRAY;
1068               cons->expr->rank = para->rank;
1069               cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1070               gfc_constructor_append_expr (&cons->expr->value.constructor,
1071                                            para, &cons->expr->where);
1072             }
1073           if (cons->expr->expr_type == EXPR_ARRAY)
1074             {
1075               gfc_constructor *p;
1076               p = gfc_constructor_first (cons->expr->value.constructor);
1077               if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1078                 {
1079                   gfc_charlen *cl, *cl2;
1080
1081                   cl2 = NULL;
1082                   for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1083                     {
1084                       if (cl == cons->expr->ts.u.cl)
1085                         break;
1086                       cl2 = cl;
1087                     }
1088
1089                   gcc_assert (cl);
1090
1091                   if (cl2)
1092                     cl2->next = cl->next;
1093
1094                   gfc_free_expr (cl->length);
1095                   free (cl);
1096                 }
1097
1098               cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1099               cons->expr->ts.u.cl->length_from_typespec = true;
1100               cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1101               gfc_resolve_character_array_constructor (cons->expr);
1102             }
1103         }
1104
1105       if (cons->expr->expr_type == EXPR_NULL
1106           && !(comp->attr.pointer || comp->attr.allocatable
1107                || comp->attr.proc_pointer
1108                || (comp->ts.type == BT_CLASS
1109                    && (CLASS_DATA (comp)->attr.class_pointer
1110                        || CLASS_DATA (comp)->attr.allocatable))))
1111         {
1112           t = FAILURE;
1113           gfc_error ("The NULL in the derived type constructor at %L is "
1114                      "being applied to component '%s', which is neither "
1115                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
1116                      comp->name);
1117         }
1118
1119       if (!comp->attr.pointer || comp->attr.proc_pointer
1120           || cons->expr->expr_type == EXPR_NULL)
1121         continue;
1122
1123       a = gfc_expr_attr (cons->expr);
1124
1125       if (!a.pointer && !a.target)
1126         {
1127           t = FAILURE;
1128           gfc_error ("The element in the derived type constructor at %L, "
1129                      "for pointer component '%s' should be a POINTER or "
1130                      "a TARGET", &cons->expr->where, comp->name);
1131         }
1132
1133       if (init)
1134         {
1135           /* F08:C461. Additional checks for pointer initialization.  */
1136           if (a.allocatable)
1137             {
1138               t = FAILURE;
1139               gfc_error ("Pointer initialization target at %L "
1140                          "must not be ALLOCATABLE ", &cons->expr->where);
1141             }
1142           if (!a.save)
1143             {
1144               t = FAILURE;
1145               gfc_error ("Pointer initialization target at %L "
1146                          "must have the SAVE attribute", &cons->expr->where);
1147             }
1148         }
1149
1150       /* F2003, C1272 (3).  */
1151       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
1152           && (gfc_impure_variable (cons->expr->symtree->n.sym)
1153               || gfc_is_coindexed (cons->expr)))
1154         {
1155           t = FAILURE;
1156           gfc_error ("Invalid expression in the derived type constructor for "
1157                      "pointer component '%s' at %L in PURE procedure",
1158                      comp->name, &cons->expr->where);
1159         }
1160
1161       if (gfc_implicit_pure (NULL)
1162             && cons->expr->expr_type == EXPR_VARIABLE
1163             && (gfc_impure_variable (cons->expr->symtree->n.sym)
1164                 || gfc_is_coindexed (cons->expr)))
1165         gfc_current_ns->proc_name->attr.implicit_pure = 0;
1166
1167     }
1168
1169   return t;
1170 }
1171
1172
1173 /****************** Expression name resolution ******************/
1174
1175 /* Returns 0 if a symbol was not declared with a type or
1176    attribute declaration statement, nonzero otherwise.  */
1177
1178 static int
1179 was_declared (gfc_symbol *sym)
1180 {
1181   symbol_attribute a;
1182
1183   a = sym->attr;
1184
1185   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1186     return 1;
1187
1188   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1189       || a.optional || a.pointer || a.save || a.target || a.volatile_
1190       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1191       || a.asynchronous || a.codimension)
1192     return 1;
1193
1194   return 0;
1195 }
1196
1197
1198 /* Determine if a symbol is generic or not.  */
1199
1200 static int
1201 generic_sym (gfc_symbol *sym)
1202 {
1203   gfc_symbol *s;
1204
1205   if (sym->attr.generic ||
1206       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1207     return 1;
1208
1209   if (was_declared (sym) || sym->ns->parent == NULL)
1210     return 0;
1211
1212   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1213   
1214   if (s != NULL)
1215     {
1216       if (s == sym)
1217         return 0;
1218       else
1219         return generic_sym (s);
1220     }
1221
1222   return 0;
1223 }
1224
1225
1226 /* Determine if a symbol is specific or not.  */
1227
1228 static int
1229 specific_sym (gfc_symbol *sym)
1230 {
1231   gfc_symbol *s;
1232
1233   if (sym->attr.if_source == IFSRC_IFBODY
1234       || sym->attr.proc == PROC_MODULE
1235       || sym->attr.proc == PROC_INTERNAL
1236       || sym->attr.proc == PROC_ST_FUNCTION
1237       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1238       || sym->attr.external)
1239     return 1;
1240
1241   if (was_declared (sym) || sym->ns->parent == NULL)
1242     return 0;
1243
1244   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1245
1246   return (s == NULL) ? 0 : specific_sym (s);
1247 }
1248
1249
1250 /* Figure out if the procedure is specific, generic or unknown.  */
1251
1252 typedef enum
1253 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1254 proc_type;
1255
1256 static proc_type
1257 procedure_kind (gfc_symbol *sym)
1258 {
1259   if (generic_sym (sym))
1260     return PTYPE_GENERIC;
1261
1262   if (specific_sym (sym))
1263     return PTYPE_SPECIFIC;
1264
1265   return PTYPE_UNKNOWN;
1266 }
1267
1268 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1269    is nonzero when matching actual arguments.  */
1270
1271 static int need_full_assumed_size = 0;
1272
1273 static bool
1274 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1275 {
1276   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1277       return false;
1278
1279   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1280      What should it be?  */
1281   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1282           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1283                && (e->ref->u.ar.type == AR_FULL))
1284     {
1285       gfc_error ("The upper bound in the last dimension must "
1286                  "appear in the reference to the assumed size "
1287                  "array '%s' at %L", sym->name, &e->where);
1288       return true;
1289     }
1290   return false;
1291 }
1292
1293
1294 /* Look for bad assumed size array references in argument expressions
1295   of elemental and array valued intrinsic procedures.  Since this is
1296   called from procedure resolution functions, it only recurses at
1297   operators.  */
1298
1299 static bool
1300 resolve_assumed_size_actual (gfc_expr *e)
1301 {
1302   if (e == NULL)
1303    return false;
1304
1305   switch (e->expr_type)
1306     {
1307     case EXPR_VARIABLE:
1308       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1309         return true;
1310       break;
1311
1312     case EXPR_OP:
1313       if (resolve_assumed_size_actual (e->value.op.op1)
1314           || resolve_assumed_size_actual (e->value.op.op2))
1315         return true;
1316       break;
1317
1318     default:
1319       break;
1320     }
1321   return false;
1322 }
1323
1324
1325 /* Check a generic procedure, passed as an actual argument, to see if
1326    there is a matching specific name.  If none, it is an error, and if
1327    more than one, the reference is ambiguous.  */
1328 static int
1329 count_specific_procs (gfc_expr *e)
1330 {
1331   int n;
1332   gfc_interface *p;
1333   gfc_symbol *sym;
1334         
1335   n = 0;
1336   sym = e->symtree->n.sym;
1337
1338   for (p = sym->generic; p; p = p->next)
1339     if (strcmp (sym->name, p->sym->name) == 0)
1340       {
1341         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1342                                        sym->name);
1343         n++;
1344       }
1345
1346   if (n > 1)
1347     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1348                &e->where);
1349
1350   if (n == 0)
1351     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1352                "argument at %L", sym->name, &e->where);
1353
1354   return n;
1355 }
1356
1357
1358 /* See if a call to sym could possibly be a not allowed RECURSION because of
1359    a missing RECURIVE declaration.  This means that either sym is the current
1360    context itself, or sym is the parent of a contained procedure calling its
1361    non-RECURSIVE containing procedure.
1362    This also works if sym is an ENTRY.  */
1363
1364 static bool
1365 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1366 {
1367   gfc_symbol* proc_sym;
1368   gfc_symbol* context_proc;
1369   gfc_namespace* real_context;
1370
1371   if (sym->attr.flavor == FL_PROGRAM)
1372     return false;
1373
1374   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1375
1376   /* If we've got an ENTRY, find real procedure.  */
1377   if (sym->attr.entry && sym->ns->entries)
1378     proc_sym = sym->ns->entries->sym;
1379   else
1380     proc_sym = sym;
1381
1382   /* If sym is RECURSIVE, all is well of course.  */
1383   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1384     return false;
1385
1386   /* Find the context procedure's "real" symbol if it has entries.
1387      We look for a procedure symbol, so recurse on the parents if we don't
1388      find one (like in case of a BLOCK construct).  */
1389   for (real_context = context; ; real_context = real_context->parent)
1390     {
1391       /* We should find something, eventually!  */
1392       gcc_assert (real_context);
1393
1394       context_proc = (real_context->entries ? real_context->entries->sym
1395                                             : real_context->proc_name);
1396
1397       /* In some special cases, there may not be a proc_name, like for this
1398          invalid code:
1399          real(bad_kind()) function foo () ...
1400          when checking the call to bad_kind ().
1401          In these cases, we simply return here and assume that the
1402          call is ok.  */
1403       if (!context_proc)
1404         return false;
1405
1406       if (context_proc->attr.flavor != FL_LABEL)
1407         break;
1408     }
1409
1410   /* A call from sym's body to itself is recursion, of course.  */
1411   if (context_proc == proc_sym)
1412     return true;
1413
1414   /* The same is true if context is a contained procedure and sym the
1415      containing one.  */
1416   if (context_proc->attr.contained)
1417     {
1418       gfc_symbol* parent_proc;
1419
1420       gcc_assert (context->parent);
1421       parent_proc = (context->parent->entries ? context->parent->entries->sym
1422                                               : context->parent->proc_name);
1423
1424       if (parent_proc == proc_sym)
1425         return true;
1426     }
1427
1428   return false;
1429 }
1430
1431
1432 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1433    its typespec and formal argument list.  */
1434
1435 static gfc_try
1436 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1437 {
1438   gfc_intrinsic_sym* isym = NULL;
1439   const char* symstd;
1440
1441   if (sym->formal)
1442     return SUCCESS;
1443
1444   /* Already resolved.  */
1445   if (sym->from_intmod && sym->ts.type != BT_UNKNOWN)
1446     return SUCCESS;
1447
1448   /* We already know this one is an intrinsic, so we don't call
1449      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1450      gfc_find_subroutine directly to check whether it is a function or
1451      subroutine.  */
1452
1453   if (sym->intmod_sym_id)
1454     isym = gfc_intrinsic_function_by_id ((gfc_isym_id) sym->intmod_sym_id);
1455   else
1456     isym = gfc_find_function (sym->name);
1457
1458   if (isym)
1459     {
1460       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1461           && !sym->attr.implicit_type)
1462         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1463                       " ignored", sym->name, &sym->declared_at);
1464
1465       if (!sym->attr.function &&
1466           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1467         return FAILURE;
1468
1469       sym->ts = isym->ts;
1470     }
1471   else if ((isym = gfc_find_subroutine (sym->name)))
1472     {
1473       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1474         {
1475           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1476                       " specifier", sym->name, &sym->declared_at);
1477           return FAILURE;
1478         }
1479
1480       if (!sym->attr.subroutine &&
1481           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1482         return FAILURE;
1483     }
1484   else
1485     {
1486       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1487                  &sym->declared_at);
1488       return FAILURE;
1489     }
1490
1491   gfc_copy_formal_args_intr (sym, isym);
1492
1493   /* Check it is actually available in the standard settings.  */
1494   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1495       == FAILURE)
1496     {
1497       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1498                  " available in the current standard settings but %s.  Use"
1499                  " an appropriate -std=* option or enable -fall-intrinsics"
1500                  " in order to use it.",
1501                  sym->name, &sym->declared_at, symstd);
1502       return FAILURE;
1503     }
1504
1505   return SUCCESS;
1506 }
1507
1508
1509 /* Resolve a procedure expression, like passing it to a called procedure or as
1510    RHS for a procedure pointer assignment.  */
1511
1512 static gfc_try
1513 resolve_procedure_expression (gfc_expr* expr)
1514 {
1515   gfc_symbol* sym;
1516
1517   if (expr->expr_type != EXPR_VARIABLE)
1518     return SUCCESS;
1519   gcc_assert (expr->symtree);
1520
1521   sym = expr->symtree->n.sym;
1522
1523   if (sym->attr.intrinsic)
1524     resolve_intrinsic (sym, &expr->where);
1525
1526   if (sym->attr.flavor != FL_PROCEDURE
1527       || (sym->attr.function && sym->result == sym))
1528     return SUCCESS;
1529
1530   /* A non-RECURSIVE procedure that is used as procedure expression within its
1531      own body is in danger of being called recursively.  */
1532   if (is_illegal_recursion (sym, gfc_current_ns))
1533     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1534                  " itself recursively.  Declare it RECURSIVE or use"
1535                  " -frecursive", sym->name, &expr->where);
1536   
1537   return SUCCESS;
1538 }
1539
1540
1541 /* Resolve an actual argument list.  Most of the time, this is just
1542    resolving the expressions in the list.
1543    The exception is that we sometimes have to decide whether arguments
1544    that look like procedure arguments are really simple variable
1545    references.  */
1546
1547 static gfc_try
1548 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1549                         bool no_formal_args)
1550 {
1551   gfc_symbol *sym;
1552   gfc_symtree *parent_st;
1553   gfc_expr *e;
1554   int save_need_full_assumed_size;
1555
1556   for (; arg; arg = arg->next)
1557     {
1558       e = arg->expr;
1559       if (e == NULL)
1560         {
1561           /* Check the label is a valid branching target.  */
1562           if (arg->label)
1563             {
1564               if (arg->label->defined == ST_LABEL_UNKNOWN)
1565                 {
1566                   gfc_error ("Label %d referenced at %L is never defined",
1567                              arg->label->value, &arg->label->where);
1568                   return FAILURE;
1569                 }
1570             }
1571           continue;
1572         }
1573
1574       if (e->expr_type == EXPR_VARIABLE
1575             && e->symtree->n.sym->attr.generic
1576             && no_formal_args
1577             && count_specific_procs (e) != 1)
1578         return FAILURE;
1579
1580       if (e->ts.type != BT_PROCEDURE)
1581         {
1582           save_need_full_assumed_size = need_full_assumed_size;
1583           if (e->expr_type != EXPR_VARIABLE)
1584             need_full_assumed_size = 0;
1585           if (gfc_resolve_expr (e) != SUCCESS)
1586             return FAILURE;
1587           need_full_assumed_size = save_need_full_assumed_size;
1588           goto argument_list;
1589         }
1590
1591       /* See if the expression node should really be a variable reference.  */
1592
1593       sym = e->symtree->n.sym;
1594
1595       if (sym->attr.flavor == FL_PROCEDURE
1596           || sym->attr.intrinsic
1597           || sym->attr.external)
1598         {
1599           int actual_ok;
1600
1601           /* If a procedure is not already determined to be something else
1602              check if it is intrinsic.  */
1603           if (!sym->attr.intrinsic
1604               && !(sym->attr.external || sym->attr.use_assoc
1605                    || sym->attr.if_source == IFSRC_IFBODY)
1606               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1607             sym->attr.intrinsic = 1;
1608
1609           if (sym->attr.proc == PROC_ST_FUNCTION)
1610             {
1611               gfc_error ("Statement function '%s' at %L is not allowed as an "
1612                          "actual argument", sym->name, &e->where);
1613             }
1614
1615           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1616                                                sym->attr.subroutine);
1617           if (sym->attr.intrinsic && actual_ok == 0)
1618             {
1619               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1620                          "actual argument", sym->name, &e->where);
1621             }
1622
1623           if (sym->attr.contained && !sym->attr.use_assoc
1624               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1625             {
1626               if (gfc_notify_std (GFC_STD_F2008,
1627                                   "Fortran 2008: Internal procedure '%s' is"
1628                                   " used as actual argument at %L",
1629                                   sym->name, &e->where) == FAILURE)
1630                 return FAILURE;
1631             }
1632
1633           if (sym->attr.elemental && !sym->attr.intrinsic)
1634             {
1635               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1636                          "allowed as an actual argument at %L", sym->name,
1637                          &e->where);
1638             }
1639
1640           /* Check if a generic interface has a specific procedure
1641             with the same name before emitting an error.  */
1642           if (sym->attr.generic && count_specific_procs (e) != 1)
1643             return FAILURE;
1644           
1645           /* Just in case a specific was found for the expression.  */
1646           sym = e->symtree->n.sym;
1647
1648           /* If the symbol is the function that names the current (or
1649              parent) scope, then we really have a variable reference.  */
1650
1651           if (gfc_is_function_return_value (sym, sym->ns))
1652             goto got_variable;
1653
1654           /* If all else fails, see if we have a specific intrinsic.  */
1655           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1656             {
1657               gfc_intrinsic_sym *isym;
1658
1659               isym = gfc_find_function (sym->name);
1660               if (isym == NULL || !isym->specific)
1661                 {
1662                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1663                              "for the reference '%s' at %L", sym->name,
1664                              &e->where);
1665                   return FAILURE;
1666                 }
1667               sym->ts = isym->ts;
1668               sym->attr.intrinsic = 1;
1669               sym->attr.function = 1;
1670             }
1671
1672           if (gfc_resolve_expr (e) == FAILURE)
1673             return FAILURE;
1674           goto argument_list;
1675         }
1676
1677       /* See if the name is a module procedure in a parent unit.  */
1678
1679       if (was_declared (sym) || sym->ns->parent == NULL)
1680         goto got_variable;
1681
1682       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1683         {
1684           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1685           return FAILURE;
1686         }
1687
1688       if (parent_st == NULL)
1689         goto got_variable;
1690
1691       sym = parent_st->n.sym;
1692       e->symtree = parent_st;           /* Point to the right thing.  */
1693
1694       if (sym->attr.flavor == FL_PROCEDURE
1695           || sym->attr.intrinsic
1696           || sym->attr.external)
1697         {
1698           if (gfc_resolve_expr (e) == FAILURE)
1699             return FAILURE;
1700           goto argument_list;
1701         }
1702
1703     got_variable:
1704       e->expr_type = EXPR_VARIABLE;
1705       e->ts = sym->ts;
1706       if (sym->as != NULL)
1707         {
1708           e->rank = sym->as->rank;
1709           e->ref = gfc_get_ref ();
1710           e->ref->type = REF_ARRAY;
1711           e->ref->u.ar.type = AR_FULL;
1712           e->ref->u.ar.as = sym->as;
1713         }
1714
1715       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1716          primary.c (match_actual_arg). If above code determines that it
1717          is a  variable instead, it needs to be resolved as it was not
1718          done at the beginning of this function.  */
1719       save_need_full_assumed_size = need_full_assumed_size;
1720       if (e->expr_type != EXPR_VARIABLE)
1721         need_full_assumed_size = 0;
1722       if (gfc_resolve_expr (e) != SUCCESS)
1723         return FAILURE;
1724       need_full_assumed_size = save_need_full_assumed_size;
1725
1726     argument_list:
1727       /* Check argument list functions %VAL, %LOC and %REF.  There is
1728          nothing to do for %REF.  */
1729       if (arg->name && arg->name[0] == '%')
1730         {
1731           if (strncmp ("%VAL", arg->name, 4) == 0)
1732             {
1733               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1734                 {
1735                   gfc_error ("By-value argument at %L is not of numeric "
1736                              "type", &e->where);
1737                   return FAILURE;
1738                 }
1739
1740               if (e->rank)
1741                 {
1742                   gfc_error ("By-value argument at %L cannot be an array or "
1743                              "an array section", &e->where);
1744                 return FAILURE;
1745                 }
1746
1747               /* Intrinsics are still PROC_UNKNOWN here.  However,
1748                  since same file external procedures are not resolvable
1749                  in gfortran, it is a good deal easier to leave them to
1750                  intrinsic.c.  */
1751               if (ptype != PROC_UNKNOWN
1752                   && ptype != PROC_DUMMY
1753                   && ptype != PROC_EXTERNAL
1754                   && ptype != PROC_MODULE)
1755                 {
1756                   gfc_error ("By-value argument at %L is not allowed "
1757                              "in this context", &e->where);
1758                   return FAILURE;
1759                 }
1760             }
1761
1762           /* Statement functions have already been excluded above.  */
1763           else if (strncmp ("%LOC", arg->name, 4) == 0
1764                    && e->ts.type == BT_PROCEDURE)
1765             {
1766               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1767                 {
1768                   gfc_error ("Passing internal procedure at %L by location "
1769                              "not allowed", &e->where);
1770                   return FAILURE;
1771                 }
1772             }
1773         }
1774
1775       /* Fortran 2008, C1237.  */
1776       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1777           && gfc_has_ultimate_pointer (e))
1778         {
1779           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1780                      "component", &e->where);
1781           return FAILURE;
1782         }
1783     }
1784
1785   return SUCCESS;
1786 }
1787
1788
1789 /* Do the checks of the actual argument list that are specific to elemental
1790    procedures.  If called with c == NULL, we have a function, otherwise if
1791    expr == NULL, we have a subroutine.  */
1792
1793 static gfc_try
1794 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1795 {
1796   gfc_actual_arglist *arg0;
1797   gfc_actual_arglist *arg;
1798   gfc_symbol *esym = NULL;
1799   gfc_intrinsic_sym *isym = NULL;
1800   gfc_expr *e = NULL;
1801   gfc_intrinsic_arg *iformal = NULL;
1802   gfc_formal_arglist *eformal = NULL;
1803   bool formal_optional = false;
1804   bool set_by_optional = false;
1805   int i;
1806   int rank = 0;
1807
1808   /* Is this an elemental procedure?  */
1809   if (expr && expr->value.function.actual != NULL)
1810     {
1811       if (expr->value.function.esym != NULL
1812           && expr->value.function.esym->attr.elemental)
1813         {
1814           arg0 = expr->value.function.actual;
1815           esym = expr->value.function.esym;
1816         }
1817       else if (expr->value.function.isym != NULL
1818                && expr->value.function.isym->elemental)
1819         {
1820           arg0 = expr->value.function.actual;
1821           isym = expr->value.function.isym;
1822         }
1823       else
1824         return SUCCESS;
1825     }
1826   else if (c && c->ext.actual != NULL)
1827     {
1828       arg0 = c->ext.actual;
1829       
1830       if (c->resolved_sym)
1831         esym = c->resolved_sym;
1832       else
1833         esym = c->symtree->n.sym;
1834       gcc_assert (esym);
1835
1836       if (!esym->attr.elemental)
1837         return SUCCESS;
1838     }
1839   else
1840     return SUCCESS;
1841
1842   /* The rank of an elemental is the rank of its array argument(s).  */
1843   for (arg = arg0; arg; arg = arg->next)
1844     {
1845       if (arg->expr != NULL && arg->expr->rank > 0)
1846         {
1847           rank = arg->expr->rank;
1848           if (arg->expr->expr_type == EXPR_VARIABLE
1849               && arg->expr->symtree->n.sym->attr.optional)
1850             set_by_optional = true;
1851
1852           /* Function specific; set the result rank and shape.  */
1853           if (expr)
1854             {
1855               expr->rank = rank;
1856               if (!expr->shape && arg->expr->shape)
1857                 {
1858                   expr->shape = gfc_get_shape (rank);
1859                   for (i = 0; i < rank; i++)
1860                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1861                 }
1862             }
1863           break;
1864         }
1865     }
1866
1867   /* If it is an array, it shall not be supplied as an actual argument
1868      to an elemental procedure unless an array of the same rank is supplied
1869      as an actual argument corresponding to a nonoptional dummy argument of
1870      that elemental procedure(12.4.1.5).  */
1871   formal_optional = false;
1872   if (isym)
1873     iformal = isym->formal;
1874   else
1875     eformal = esym->formal;
1876
1877   for (arg = arg0; arg; arg = arg->next)
1878     {
1879       if (eformal)
1880         {
1881           if (eformal->sym && eformal->sym->attr.optional)
1882             formal_optional = true;
1883           eformal = eformal->next;
1884         }
1885       else if (isym && iformal)
1886         {
1887           if (iformal->optional)
1888             formal_optional = true;
1889           iformal = iformal->next;
1890         }
1891       else if (isym)
1892         formal_optional = true;
1893
1894       if (pedantic && arg->expr != NULL
1895           && arg->expr->expr_type == EXPR_VARIABLE
1896           && arg->expr->symtree->n.sym->attr.optional
1897           && formal_optional
1898           && arg->expr->rank
1899           && (set_by_optional || arg->expr->rank != rank)
1900           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1901         {
1902           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1903                        "MISSING, it cannot be the actual argument of an "
1904                        "ELEMENTAL procedure unless there is a non-optional "
1905                        "argument with the same rank (12.4.1.5)",
1906                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1907           return FAILURE;
1908         }
1909     }
1910
1911   for (arg = arg0; arg; arg = arg->next)
1912     {
1913       if (arg->expr == NULL || arg->expr->rank == 0)
1914         continue;
1915
1916       /* Being elemental, the last upper bound of an assumed size array
1917          argument must be present.  */
1918       if (resolve_assumed_size_actual (arg->expr))
1919         return FAILURE;
1920
1921       /* Elemental procedure's array actual arguments must conform.  */
1922       if (e != NULL)
1923         {
1924           if (gfc_check_conformance (arg->expr, e,
1925                                      "elemental procedure") == FAILURE)
1926             return FAILURE;
1927         }
1928       else
1929         e = arg->expr;
1930     }
1931
1932   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1933      is an array, the intent inout/out variable needs to be also an array.  */
1934   if (rank > 0 && esym && expr == NULL)
1935     for (eformal = esym->formal, arg = arg0; arg && eformal;
1936          arg = arg->next, eformal = eformal->next)
1937       if ((eformal->sym->attr.intent == INTENT_OUT
1938            || eformal->sym->attr.intent == INTENT_INOUT)
1939           && arg->expr && arg->expr->rank == 0)
1940         {
1941           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1942                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1943                      "actual argument is an array", &arg->expr->where,
1944                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1945                      : "INOUT", eformal->sym->name, esym->name);
1946           return FAILURE;
1947         }
1948   return SUCCESS;
1949 }
1950
1951
1952 /* This function does the checking of references to global procedures
1953    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1954    77 and 95 standards.  It checks for a gsymbol for the name, making
1955    one if it does not already exist.  If it already exists, then the
1956    reference being resolved must correspond to the type of gsymbol.
1957    Otherwise, the new symbol is equipped with the attributes of the
1958    reference.  The corresponding code that is called in creating
1959    global entities is parse.c.
1960
1961    In addition, for all but -std=legacy, the gsymbols are used to
1962    check the interfaces of external procedures from the same file.
1963    The namespace of the gsymbol is resolved and then, once this is
1964    done the interface is checked.  */
1965
1966
1967 static bool
1968 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1969 {
1970   if (!gsym_ns->proc_name->attr.recursive)
1971     return true;
1972
1973   if (sym->ns == gsym_ns)
1974     return false;
1975
1976   if (sym->ns->parent && sym->ns->parent == gsym_ns)
1977     return false;
1978
1979   return true;
1980 }
1981
1982 static bool
1983 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
1984 {
1985   if (gsym_ns->entries)
1986     {
1987       gfc_entry_list *entry = gsym_ns->entries;
1988
1989       for (; entry; entry = entry->next)
1990         {
1991           if (strcmp (sym->name, entry->sym->name) == 0)
1992             {
1993               if (strcmp (gsym_ns->proc_name->name,
1994                           sym->ns->proc_name->name) == 0)
1995                 return false;
1996
1997               if (sym->ns->parent
1998                   && strcmp (gsym_ns->proc_name->name,
1999                              sym->ns->parent->proc_name->name) == 0)
2000                 return false;
2001             }
2002         }
2003     }
2004   return true;
2005 }
2006
2007 static void
2008 resolve_global_procedure (gfc_symbol *sym, locus *where,
2009                           gfc_actual_arglist **actual, int sub)
2010 {
2011   gfc_gsymbol * gsym;
2012   gfc_namespace *ns;
2013   enum gfc_symbol_type type;
2014
2015   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
2016
2017   gsym = gfc_get_gsymbol (sym->name);
2018
2019   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
2020     gfc_global_used (gsym, where);
2021
2022   if (gfc_option.flag_whole_file
2023         && (sym->attr.if_source == IFSRC_UNKNOWN
2024             || sym->attr.if_source == IFSRC_IFBODY)
2025         && gsym->type != GSYM_UNKNOWN
2026         && gsym->ns
2027         && gsym->ns->resolved != -1
2028         && gsym->ns->proc_name
2029         && not_in_recursive (sym, gsym->ns)
2030         && not_entry_self_reference (sym, gsym->ns))
2031     {
2032       gfc_symbol *def_sym;
2033
2034       /* Resolve the gsymbol namespace if needed.  */
2035       if (!gsym->ns->resolved)
2036         {
2037           gfc_dt_list *old_dt_list;
2038           struct gfc_omp_saved_state old_omp_state;
2039
2040           /* Stash away derived types so that the backend_decls do not
2041              get mixed up.  */
2042           old_dt_list = gfc_derived_types;
2043           gfc_derived_types = NULL;
2044           /* And stash away openmp state.  */
2045           gfc_omp_save_and_clear_state (&old_omp_state);
2046
2047           gfc_resolve (gsym->ns);
2048
2049           /* Store the new derived types with the global namespace.  */
2050           if (gfc_derived_types)
2051             gsym->ns->derived_types = gfc_derived_types;
2052
2053           /* Restore the derived types of this namespace.  */
2054           gfc_derived_types = old_dt_list;
2055           /* And openmp state.  */
2056           gfc_omp_restore_state (&old_omp_state);
2057         }
2058
2059       /* Make sure that translation for the gsymbol occurs before
2060          the procedure currently being resolved.  */
2061       ns = gfc_global_ns_list;
2062       for (; ns && ns != gsym->ns; ns = ns->sibling)
2063         {
2064           if (ns->sibling == gsym->ns)
2065             {
2066               ns->sibling = gsym->ns->sibling;
2067               gsym->ns->sibling = gfc_global_ns_list;
2068               gfc_global_ns_list = gsym->ns;
2069               break;
2070             }
2071         }
2072
2073       def_sym = gsym->ns->proc_name;
2074       if (def_sym->attr.entry_master)
2075         {
2076           gfc_entry_list *entry;
2077           for (entry = gsym->ns->entries; entry; entry = entry->next)
2078             if (strcmp (entry->sym->name, sym->name) == 0)
2079               {
2080                 def_sym = entry->sym;
2081                 break;
2082               }
2083         }
2084
2085       /* Differences in constant character lengths.  */
2086       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
2087         {
2088           long int l1 = 0, l2 = 0;
2089           gfc_charlen *cl1 = sym->ts.u.cl;
2090           gfc_charlen *cl2 = def_sym->ts.u.cl;
2091
2092           if (cl1 != NULL
2093               && cl1->length != NULL
2094               && cl1->length->expr_type == EXPR_CONSTANT)
2095             l1 = mpz_get_si (cl1->length->value.integer);
2096
2097           if (cl2 != NULL
2098               && cl2->length != NULL
2099               && cl2->length->expr_type == EXPR_CONSTANT)
2100             l2 = mpz_get_si (cl2->length->value.integer);
2101
2102           if (l1 && l2 && l1 != l2)
2103             gfc_error ("Character length mismatch in return type of "
2104                        "function '%s' at %L (%ld/%ld)", sym->name,
2105                        &sym->declared_at, l1, l2);
2106         }
2107
2108      /* Type mismatch of function return type and expected type.  */
2109      if (sym->attr.function
2110          && !gfc_compare_types (&sym->ts, &def_sym->ts))
2111         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
2112                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2113                    gfc_typename (&def_sym->ts));
2114
2115       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
2116         {
2117           gfc_formal_arglist *arg = def_sym->formal;
2118           for ( ; arg; arg = arg->next)
2119             if (!arg->sym)
2120               continue;
2121             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
2122             else if (arg->sym->attr.allocatable
2123                      || arg->sym->attr.asynchronous
2124                      || arg->sym->attr.optional
2125                      || arg->sym->attr.pointer
2126                      || arg->sym->attr.target
2127                      || arg->sym->attr.value
2128                      || arg->sym->attr.volatile_)
2129               {
2130                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
2131                            "has an attribute that requires an explicit "
2132                            "interface for this procedure", arg->sym->name,
2133                            sym->name, &sym->declared_at);
2134                 break;
2135               }
2136             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
2137             else if (arg->sym && arg->sym->as
2138                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
2139               {
2140                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
2141                            "argument '%s' must have an explicit interface",
2142                            sym->name, &sym->declared_at, arg->sym->name);
2143                 break;
2144               }
2145             /* F2008, 12.4.2.2 (2c)  */
2146             else if (arg->sym->attr.codimension)
2147               {
2148                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
2149                            "'%s' must have an explicit interface",
2150                            sym->name, &sym->declared_at, arg->sym->name);
2151                 break;
2152               }
2153             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
2154             else if (false) /* TODO: is a parametrized derived type  */
2155               {
2156                 gfc_error ("Procedure '%s' at %L with parametrized derived "
2157                            "type argument '%s' must have an explicit "
2158                            "interface", sym->name, &sym->declared_at,
2159                            arg->sym->name);
2160                 break;
2161               }
2162             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
2163             else if (arg->sym->ts.type == BT_CLASS)
2164               {
2165                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
2166                            "argument '%s' must have an explicit interface",
2167                            sym->name, &sym->declared_at, arg->sym->name);
2168                 break;
2169               }
2170         }
2171
2172       if (def_sym->attr.function)
2173         {
2174           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
2175           if (def_sym->as && def_sym->as->rank
2176               && (!sym->as || sym->as->rank != def_sym->as->rank))
2177             gfc_error ("The reference to function '%s' at %L either needs an "
2178                        "explicit INTERFACE or the rank is incorrect", sym->name,
2179                        where);
2180
2181           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
2182           if ((def_sym->result->attr.pointer
2183                || def_sym->result->attr.allocatable)
2184                && (sym->attr.if_source != IFSRC_IFBODY
2185                    || def_sym->result->attr.pointer
2186                         != sym->result->attr.pointer
2187                    || def_sym->result->attr.allocatable
2188                         != sym->result->attr.allocatable))
2189             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
2190                        "result must have an explicit interface", sym->name,
2191                        where);
2192
2193           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
2194           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
2195               && def_sym->ts.type == BT_CHARACTER && def_sym->ts.u.cl->length != NULL)
2196             {
2197               gfc_charlen *cl = sym->ts.u.cl;
2198
2199               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
2200                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
2201                 {
2202                   gfc_error ("Nonconstant character-length function '%s' at %L "
2203                              "must have an explicit interface", sym->name,
2204                              &sym->declared_at);
2205                 }
2206             }
2207         }
2208
2209       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2210       if (def_sym->attr.elemental && !sym->attr.elemental)
2211         {
2212           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2213                      "interface", sym->name, &sym->declared_at);
2214         }
2215
2216       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2217       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2218         {
2219           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2220                      "an explicit interface", sym->name, &sym->declared_at);
2221         }
2222
2223       if (gfc_option.flag_whole_file == 1
2224           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2225               && !(gfc_option.warn_std & GFC_STD_GNU)))
2226         gfc_errors_to_warnings (1);
2227
2228       if (sym->attr.if_source != IFSRC_IFBODY)  
2229         gfc_procedure_use (def_sym, actual, where);
2230
2231       gfc_errors_to_warnings (0);
2232     }
2233
2234   if (gsym->type == GSYM_UNKNOWN)
2235     {
2236       gsym->type = type;
2237       gsym->where = *where;
2238     }
2239
2240   gsym->used = 1;
2241 }
2242
2243
2244 /************* Function resolution *************/
2245
2246 /* Resolve a function call known to be generic.
2247    Section 14.1.2.4.1.  */
2248
2249 static match
2250 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2251 {
2252   gfc_symbol *s;
2253
2254   if (sym->attr.generic)
2255     {
2256       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2257       if (s != NULL)
2258         {
2259           expr->value.function.name = s->name;
2260           expr->value.function.esym = s;
2261
2262           if (s->ts.type != BT_UNKNOWN)
2263             expr->ts = s->ts;
2264           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2265             expr->ts = s->result->ts;
2266
2267           if (s->as != NULL)
2268             expr->rank = s->as->rank;
2269           else if (s->result != NULL && s->result->as != NULL)
2270             expr->rank = s->result->as->rank;
2271
2272           gfc_set_sym_referenced (expr->value.function.esym);
2273
2274           return MATCH_YES;
2275         }
2276
2277       /* TODO: Need to search for elemental references in generic
2278          interface.  */
2279     }
2280
2281   if (sym->attr.intrinsic)
2282     return gfc_intrinsic_func_interface (expr, 0);
2283
2284   return MATCH_NO;
2285 }
2286
2287
2288 static gfc_try
2289 resolve_generic_f (gfc_expr *expr)
2290 {
2291   gfc_symbol *sym;
2292   match m;
2293
2294   sym = expr->symtree->n.sym;
2295
2296   for (;;)
2297     {
2298       m = resolve_generic_f0 (expr, sym);
2299       if (m == MATCH_YES)
2300         return SUCCESS;
2301       else if (m == MATCH_ERROR)
2302         return FAILURE;
2303
2304 generic:
2305       if (sym->ns->parent == NULL)
2306         break;
2307       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2308
2309       if (sym == NULL)
2310         break;
2311       if (!generic_sym (sym))
2312         goto generic;
2313     }
2314
2315   /* Last ditch attempt.  See if the reference is to an intrinsic
2316      that possesses a matching interface.  14.1.2.4  */
2317   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
2318     {
2319       gfc_error ("There is no specific function for the generic '%s' at %L",
2320                  expr->symtree->n.sym->name, &expr->where);
2321       return FAILURE;
2322     }
2323
2324   m = gfc_intrinsic_func_interface (expr, 0);
2325   if (m == MATCH_YES)
2326     return SUCCESS;
2327   if (m == MATCH_NO)
2328     gfc_error ("Generic function '%s' at %L is not consistent with a "
2329                "specific intrinsic interface", expr->symtree->n.sym->name,
2330                &expr->where);
2331
2332   return FAILURE;
2333 }
2334
2335
2336 /* Resolve a function call known to be specific.  */
2337
2338 static match
2339 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2340 {
2341   match m;
2342
2343   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2344     {
2345       if (sym->attr.dummy)
2346         {
2347           sym->attr.proc = PROC_DUMMY;
2348           goto found;
2349         }
2350
2351       sym->attr.proc = PROC_EXTERNAL;
2352       goto found;
2353     }
2354
2355   if (sym->attr.proc == PROC_MODULE
2356       || sym->attr.proc == PROC_ST_FUNCTION
2357       || sym->attr.proc == PROC_INTERNAL)
2358     goto found;
2359
2360   if (sym->attr.intrinsic)
2361     {
2362       m = gfc_intrinsic_func_interface (expr, 1);
2363       if (m == MATCH_YES)
2364         return MATCH_YES;
2365       if (m == MATCH_NO)
2366         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2367                    "with an intrinsic", sym->name, &expr->where);
2368
2369       return MATCH_ERROR;
2370     }
2371
2372   return MATCH_NO;
2373
2374 found:
2375   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2376
2377   if (sym->result)
2378     expr->ts = sym->result->ts;
2379   else
2380     expr->ts = sym->ts;
2381   expr->value.function.name = sym->name;
2382   expr->value.function.esym = sym;
2383   if (sym->as != NULL)
2384     expr->rank = sym->as->rank;
2385
2386   return MATCH_YES;
2387 }
2388
2389
2390 static gfc_try
2391 resolve_specific_f (gfc_expr *expr)
2392 {
2393   gfc_symbol *sym;
2394   match m;
2395
2396   sym = expr->symtree->n.sym;
2397
2398   for (;;)
2399     {
2400       m = resolve_specific_f0 (sym, expr);
2401       if (m == MATCH_YES)
2402         return SUCCESS;
2403       if (m == MATCH_ERROR)
2404         return FAILURE;
2405
2406       if (sym->ns->parent == NULL)
2407         break;
2408
2409       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2410
2411       if (sym == NULL)
2412         break;
2413     }
2414
2415   gfc_error ("Unable to resolve the specific function '%s' at %L",
2416              expr->symtree->n.sym->name, &expr->where);
2417
2418   return SUCCESS;
2419 }
2420
2421
2422 /* Resolve a procedure call not known to be generic nor specific.  */
2423
2424 static gfc_try
2425 resolve_unknown_f (gfc_expr *expr)
2426 {
2427   gfc_symbol *sym;
2428   gfc_typespec *ts;
2429
2430   sym = expr->symtree->n.sym;
2431
2432   if (sym->attr.dummy)
2433     {
2434       sym->attr.proc = PROC_DUMMY;
2435       expr->value.function.name = sym->name;
2436       goto set_type;
2437     }
2438
2439   /* See if we have an intrinsic function reference.  */
2440
2441   if (gfc_is_intrinsic (sym, 0, expr->where))
2442     {
2443       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2444         return SUCCESS;
2445       return FAILURE;
2446     }
2447
2448   /* The reference is to an external name.  */
2449
2450   sym->attr.proc = PROC_EXTERNAL;
2451   expr->value.function.name = sym->name;
2452   expr->value.function.esym = expr->symtree->n.sym;
2453
2454   if (sym->as != NULL)
2455     expr->rank = sym->as->rank;
2456
2457   /* Type of the expression is either the type of the symbol or the
2458      default type of the symbol.  */
2459
2460 set_type:
2461   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2462
2463   if (sym->ts.type != BT_UNKNOWN)
2464     expr->ts = sym->ts;
2465   else
2466     {
2467       ts = gfc_get_default_type (sym->name, sym->ns);
2468
2469       if (ts->type == BT_UNKNOWN)
2470         {
2471           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2472                      sym->name, &expr->where);
2473           return FAILURE;
2474         }
2475       else
2476         expr->ts = *ts;
2477     }
2478
2479   return SUCCESS;
2480 }
2481
2482
2483 /* Return true, if the symbol is an external procedure.  */
2484 static bool
2485 is_external_proc (gfc_symbol *sym)
2486 {
2487   if (!sym->attr.dummy && !sym->attr.contained
2488         && !(sym->attr.intrinsic
2489               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2490         && sym->attr.proc != PROC_ST_FUNCTION
2491         && !sym->attr.proc_pointer
2492         && !sym->attr.use_assoc
2493         && sym->name)
2494     return true;
2495
2496   return false;
2497 }
2498
2499
2500 /* Figure out if a function reference is pure or not.  Also set the name
2501    of the function for a potential error message.  Return nonzero if the
2502    function is PURE, zero if not.  */
2503 static int
2504 pure_stmt_function (gfc_expr *, gfc_symbol *);
2505
2506 static int
2507 pure_function (gfc_expr *e, const char **name)
2508 {
2509   int pure;
2510
2511   *name = NULL;
2512
2513   if (e->symtree != NULL
2514         && e->symtree->n.sym != NULL
2515         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2516     return pure_stmt_function (e, e->symtree->n.sym);
2517
2518   if (e->value.function.esym)
2519     {
2520       pure = gfc_pure (e->value.function.esym);
2521       *name = e->value.function.esym->name;
2522     }
2523   else if (e->value.function.isym)
2524     {
2525       pure = e->value.function.isym->pure
2526              || e->value.function.isym->elemental;
2527       *name = e->value.function.isym->name;
2528     }
2529   else
2530     {
2531       /* Implicit functions are not pure.  */
2532       pure = 0;
2533       *name = e->value.function.name;
2534     }
2535
2536   return pure;
2537 }
2538
2539
2540 static bool
2541 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2542                  int *f ATTRIBUTE_UNUSED)
2543 {
2544   const char *name;
2545
2546   /* Don't bother recursing into other statement functions
2547      since they will be checked individually for purity.  */
2548   if (e->expr_type != EXPR_FUNCTION
2549         || !e->symtree
2550         || e->symtree->n.sym == sym
2551         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2552     return false;
2553
2554   return pure_function (e, &name) ? false : true;
2555 }
2556
2557
2558 static int
2559 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2560 {
2561   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2562 }
2563
2564
2565 static gfc_try
2566 is_scalar_expr_ptr (gfc_expr *expr)
2567 {
2568   gfc_try retval = SUCCESS;
2569   gfc_ref *ref;
2570   int start;
2571   int end;
2572
2573   /* See if we have a gfc_ref, which means we have a substring, array
2574      reference, or a component.  */
2575   if (expr->ref != NULL)
2576     {
2577       ref = expr->ref;
2578       while (ref->next != NULL)
2579         ref = ref->next;
2580
2581       switch (ref->type)
2582         {
2583         case REF_SUBSTRING:
2584           if (ref->u.ss.start == NULL || ref->u.ss.end == NULL
2585               || gfc_dep_compare_expr (ref->u.ss.start, ref->u.ss.end) != 0)
2586             retval = FAILURE;
2587           break;
2588
2589         case REF_ARRAY:
2590           if (ref->u.ar.type == AR_ELEMENT)
2591             retval = SUCCESS;
2592           else if (ref->u.ar.type == AR_FULL)
2593             {
2594               /* The user can give a full array if the array is of size 1.  */
2595               if (ref->u.ar.as != NULL
2596                   && ref->u.ar.as->rank == 1
2597                   && ref->u.ar.as->type == AS_EXPLICIT
2598                   && ref->u.ar.as->lower[0] != NULL
2599                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2600                   && ref->u.ar.as->upper[0] != NULL
2601                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2602                 {
2603                   /* If we have a character string, we need to check if
2604                      its length is one.  */
2605                   if (expr->ts.type == BT_CHARACTER)
2606                     {
2607                       if (expr->ts.u.cl == NULL
2608                           || expr->ts.u.cl->length == NULL
2609                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2610                           != 0)
2611                         retval = FAILURE;
2612                     }
2613                   else
2614                     {
2615                       /* We have constant lower and upper bounds.  If the
2616                          difference between is 1, it can be considered a
2617                          scalar.  
2618                          FIXME: Use gfc_dep_compare_expr instead.  */
2619                       start = (int) mpz_get_si
2620                                 (ref->u.ar.as->lower[0]->value.integer);
2621                       end = (int) mpz_get_si
2622                                 (ref->u.ar.as->upper[0]->value.integer);
2623                       if (end - start + 1 != 1)
2624                         retval = FAILURE;
2625                    }
2626                 }
2627               else
2628                 retval = FAILURE;
2629             }
2630           else
2631             retval = FAILURE;
2632           break;
2633         default:
2634           retval = SUCCESS;
2635           break;
2636         }
2637     }
2638   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2639     {
2640       /* Character string.  Make sure it's of length 1.  */
2641       if (expr->ts.u.cl == NULL
2642           || expr->ts.u.cl->length == NULL
2643           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2644         retval = FAILURE;
2645     }
2646   else if (expr->rank != 0)
2647     retval = FAILURE;
2648
2649   return retval;
2650 }
2651
2652
2653 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2654    and, in the case of c_associated, set the binding label based on
2655    the arguments.  */
2656
2657 static gfc_try
2658 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2659                           gfc_symbol **new_sym)
2660 {
2661   char name[GFC_MAX_SYMBOL_LEN + 1];
2662   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2663   int optional_arg = 0;
2664   gfc_try retval = SUCCESS;
2665   gfc_symbol *args_sym;
2666   gfc_typespec *arg_ts;
2667   symbol_attribute arg_attr;
2668
2669   if (args->expr->expr_type == EXPR_CONSTANT
2670       || args->expr->expr_type == EXPR_OP
2671       || args->expr->expr_type == EXPR_NULL)
2672     {
2673       gfc_error ("Argument to '%s' at %L is not a variable",
2674                  sym->name, &(args->expr->where));
2675       return FAILURE;
2676     }
2677
2678   args_sym = args->expr->symtree->n.sym;
2679
2680   /* The typespec for the actual arg should be that stored in the expr
2681      and not necessarily that of the expr symbol (args_sym), because
2682      the actual expression could be a part-ref of the expr symbol.  */
2683   arg_ts = &(args->expr->ts);
2684   arg_attr = gfc_expr_attr (args->expr);
2685     
2686   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2687     {
2688       /* If the user gave two args then they are providing something for
2689          the optional arg (the second cptr).  Therefore, set the name and
2690          binding label to the c_associated for two cptrs.  Otherwise,
2691          set c_associated to expect one cptr.  */
2692       if (args->next)
2693         {
2694           /* two args.  */
2695           sprintf (name, "%s_2", sym->name);
2696           sprintf (binding_label, "%s_2", sym->binding_label);
2697           optional_arg = 1;
2698         }
2699       else
2700         {
2701           /* one arg.  */
2702           sprintf (name, "%s_1", sym->name);
2703           sprintf (binding_label, "%s_1", sym->binding_label);
2704           optional_arg = 0;
2705         }
2706
2707       /* Get a new symbol for the version of c_associated that
2708          will get called.  */
2709       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2710     }
2711   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2712            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2713     {
2714       sprintf (name, "%s", sym->name);
2715       sprintf (binding_label, "%s", sym->binding_label);
2716
2717       /* Error check the call.  */
2718       if (args->next != NULL)
2719         {
2720           gfc_error_now ("More actual than formal arguments in '%s' "
2721                          "call at %L", name, &(args->expr->where));
2722           retval = FAILURE;
2723         }
2724       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2725         {
2726           gfc_ref *ref;
2727           bool seen_section;
2728
2729           /* Make sure we have either the target or pointer attribute.  */
2730           if (!arg_attr.target && !arg_attr.pointer)
2731             {
2732               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2733                              "a TARGET or an associated pointer",
2734                              args_sym->name,
2735                              sym->name, &(args->expr->where));
2736               retval = FAILURE;
2737             }
2738
2739           if (gfc_is_coindexed (args->expr))
2740             {
2741               gfc_error_now ("Coindexed argument not permitted"
2742                              " in '%s' call at %L", name,
2743                              &(args->expr->where));
2744               retval = FAILURE;
2745             }
2746
2747           /* Follow references to make sure there are no array
2748              sections.  */
2749           seen_section = false;
2750
2751           for (ref=args->expr->ref; ref; ref = ref->next)
2752             {
2753               if (ref->type == REF_ARRAY)
2754                 {
2755                   if (ref->u.ar.type == AR_SECTION)
2756                     seen_section = true;
2757
2758                   if (ref->u.ar.type != AR_ELEMENT)
2759                     {
2760                       gfc_ref *r;
2761                       for (r = ref->next; r; r=r->next)
2762                         if (r->type == REF_COMPONENT)
2763                           {
2764                             gfc_error_now ("Array section not permitted"
2765                                            " in '%s' call at %L", name,
2766                                            &(args->expr->where));
2767                             retval = FAILURE;
2768                             break;
2769                           }
2770                     }
2771                 }
2772             }
2773
2774           if (seen_section && retval == SUCCESS)
2775             gfc_warning ("Array section in '%s' call at %L", name,
2776                          &(args->expr->where));
2777                          
2778           /* See if we have interoperable type and type param.  */
2779           if (verify_c_interop (arg_ts) == SUCCESS
2780               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2781             {
2782               if (args_sym->attr.target == 1)
2783                 {
2784                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2785                      has the target attribute and is interoperable.  */
2786                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2787                      allocatable variable that has the TARGET attribute and
2788                      is not an array of zero size.  */
2789                   if (args_sym->attr.allocatable == 1)
2790                     {
2791                       if (args_sym->attr.dimension != 0 
2792                           && (args_sym->as && args_sym->as->rank == 0))
2793                         {
2794                           gfc_error_now ("Allocatable variable '%s' used as a "
2795                                          "parameter to '%s' at %L must not be "
2796                                          "an array of zero size",
2797                                          args_sym->name, sym->name,
2798                                          &(args->expr->where));
2799                           retval = FAILURE;
2800                         }
2801                     }
2802                   else
2803                     {
2804                       /* A non-allocatable target variable with C
2805                          interoperable type and type parameters must be
2806                          interoperable.  */
2807                       if (args_sym && args_sym->attr.dimension)
2808                         {
2809                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2810                             {
2811                               gfc_error ("Assumed-shape array '%s' at %L "
2812                                          "cannot be an argument to the "
2813                                          "procedure '%s' because "
2814                                          "it is not C interoperable",
2815                                          args_sym->name,
2816                                          &(args->expr->where), sym->name);
2817                               retval = FAILURE;
2818                             }
2819                           else if (args_sym->as->type == AS_DEFERRED)
2820                             {
2821                               gfc_error ("Deferred-shape array '%s' at %L "
2822                                          "cannot be an argument to the "
2823                                          "procedure '%s' because "
2824                                          "it is not C interoperable",
2825                                          args_sym->name,
2826                                          &(args->expr->where), sym->name);
2827                               retval = FAILURE;
2828                             }
2829                         }
2830                               
2831                       /* Make sure it's not a character string.  Arrays of
2832                          any type should be ok if the variable is of a C
2833                          interoperable type.  */
2834                       if (arg_ts->type == BT_CHARACTER)
2835                         if (arg_ts->u.cl != NULL
2836                             && (arg_ts->u.cl->length == NULL
2837                                 || arg_ts->u.cl->length->expr_type
2838                                    != EXPR_CONSTANT
2839                                 || mpz_cmp_si
2840                                     (arg_ts->u.cl->length->value.integer, 1)
2841                                    != 0)
2842                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2843                           {
2844                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2845                                            "at %L must have a length of 1",
2846                                            args_sym->name, sym->name,
2847                                            &(args->expr->where));
2848                             retval = FAILURE;
2849                           }
2850                     }
2851                 }
2852               else if (arg_attr.pointer
2853                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2854                 {
2855                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2856                      scalar pointer.  */
2857                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2858                                  "associated scalar POINTER", args_sym->name,
2859                                  sym->name, &(args->expr->where));
2860                   retval = FAILURE;
2861                 }
2862             }
2863           else
2864             {
2865               /* The parameter is not required to be C interoperable.  If it
2866                  is not C interoperable, it must be a nonpolymorphic scalar
2867                  with no length type parameters.  It still must have either
2868                  the pointer or target attribute, and it can be
2869                  allocatable (but must be allocated when c_loc is called).  */
2870               if (args->expr->rank != 0 
2871                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2872                 {
2873                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2874                                  "scalar", args_sym->name, sym->name,
2875                                  &(args->expr->where));
2876                   retval = FAILURE;
2877                 }
2878               else if (arg_ts->type == BT_CHARACTER 
2879                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2880                 {
2881                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2882                                  "%L must have a length of 1",
2883                                  args_sym->name, sym->name,
2884                                  &(args->expr->where));
2885                   retval = FAILURE;
2886                 }
2887               else if (arg_ts->type == BT_CLASS)
2888                 {
2889                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
2890                                  "polymorphic", args_sym->name, sym->name,
2891                                  &(args->expr->where));
2892                   retval = FAILURE;
2893                 }
2894             }
2895         }
2896       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2897         {
2898           if (args_sym->attr.flavor != FL_PROCEDURE)
2899             {
2900               /* TODO: Update this error message to allow for procedure
2901                  pointers once they are implemented.  */
2902               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2903                              "procedure",
2904                              args_sym->name, sym->name,
2905                              &(args->expr->where));
2906               retval = FAILURE;
2907             }
2908           else if (args_sym->attr.is_bind_c != 1)
2909             {
2910               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2911                              "BIND(C)",
2912                              args_sym->name, sym->name,
2913                              &(args->expr->where));
2914               retval = FAILURE;
2915             }
2916         }
2917       
2918       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2919       *new_sym = sym;
2920     }
2921   else
2922     {
2923       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2924                           "iso_c_binding function: '%s'!\n", sym->name);
2925     }
2926
2927   return retval;
2928 }
2929
2930
2931 /* Resolve a function call, which means resolving the arguments, then figuring
2932    out which entity the name refers to.  */
2933
2934 static gfc_try
2935 resolve_function (gfc_expr *expr)
2936 {
2937   gfc_actual_arglist *arg;
2938   gfc_symbol *sym;
2939   const char *name;
2940   gfc_try t;
2941   int temp;
2942   procedure_type p = PROC_INTRINSIC;
2943   bool no_formal_args;
2944
2945   sym = NULL;
2946   if (expr->symtree)
2947     sym = expr->symtree->n.sym;
2948
2949   /* If this is a procedure pointer component, it has already been resolved.  */
2950   if (gfc_is_proc_ptr_comp (expr, NULL))
2951     return SUCCESS;
2952   
2953   if (sym && sym->attr.intrinsic
2954       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2955     return FAILURE;
2956
2957   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2958     {
2959       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2960       return FAILURE;
2961     }
2962
2963   /* If this ia a deferred TBP with an abstract interface (which may
2964      of course be referenced), expr->value.function.esym will be set.  */
2965   if (sym && sym->attr.abstract && !expr->value.function.esym)
2966     {
2967       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2968                  sym->name, &expr->where);
2969       return FAILURE;
2970     }
2971
2972   /* Switch off assumed size checking and do this again for certain kinds
2973      of procedure, once the procedure itself is resolved.  */
2974   need_full_assumed_size++;
2975
2976   if (expr->symtree && expr->symtree->n.sym)
2977     p = expr->symtree->n.sym->attr.proc;
2978
2979   if (expr->value.function.isym && expr->value.function.isym->inquiry)
2980     inquiry_argument = true;
2981   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2982
2983   if (resolve_actual_arglist (expr->value.function.actual,
2984                               p, no_formal_args) == FAILURE)
2985     {
2986       inquiry_argument = false;
2987       return FAILURE;
2988     }
2989
2990   inquiry_argument = false;
2991  
2992   /* Need to setup the call to the correct c_associated, depending on
2993      the number of cptrs to user gives to compare.  */
2994   if (sym && sym->attr.is_iso_c == 1)
2995     {
2996       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2997           == FAILURE)
2998         return FAILURE;
2999       
3000       /* Get the symtree for the new symbol (resolved func).
3001          the old one will be freed later, when it's no longer used.  */
3002       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
3003     }
3004   
3005   /* Resume assumed_size checking.  */
3006   need_full_assumed_size--;
3007
3008   /* If the procedure is external, check for usage.  */
3009   if (sym && is_external_proc (sym))
3010     resolve_global_procedure (sym, &expr->where,
3011                               &expr->value.function.actual, 0);
3012
3013   if (sym && sym->ts.type == BT_CHARACTER
3014       && sym->ts.u.cl
3015       && sym->ts.u.cl->length == NULL
3016       && !sym->attr.dummy
3017       && !sym->ts.deferred
3018       && expr->value.function.esym == NULL
3019       && !sym->attr.contained)
3020     {
3021       /* Internal procedures are taken care of in resolve_contained_fntype.  */
3022       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
3023                  "be used at %L since it is not a dummy argument",
3024                  sym->name, &expr->where);
3025       return FAILURE;
3026     }
3027
3028   /* See if function is already resolved.  */
3029
3030   if (expr->value.function.name != NULL)
3031     {
3032       if (expr->ts.type == BT_UNKNOWN)
3033         expr->ts = sym->ts;
3034       t = SUCCESS;
3035     }
3036   else
3037     {
3038       /* Apply the rules of section 14.1.2.  */
3039
3040       switch (procedure_kind (sym))
3041         {
3042         case PTYPE_GENERIC:
3043           t = resolve_generic_f (expr);
3044           break;
3045
3046         case PTYPE_SPECIFIC:
3047           t = resolve_specific_f (expr);
3048           break;
3049
3050         case PTYPE_UNKNOWN:
3051           t = resolve_unknown_f (expr);
3052           break;
3053
3054         default:
3055           gfc_internal_error ("resolve_function(): bad function type");
3056         }
3057     }
3058
3059   /* If the expression is still a function (it might have simplified),
3060      then we check to see if we are calling an elemental function.  */
3061
3062   if (expr->expr_type != EXPR_FUNCTION)
3063     return t;
3064
3065   temp = need_full_assumed_size;
3066   need_full_assumed_size = 0;
3067
3068   if (resolve_elemental_actual (expr, NULL) == FAILURE)
3069     return FAILURE;
3070
3071   if (omp_workshare_flag
3072       && expr->value.function.esym
3073       && ! gfc_elemental (expr->value.function.esym))
3074     {
3075       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
3076                  "in WORKSHARE construct", expr->value.function.esym->name,
3077                  &expr->where);
3078       t = FAILURE;
3079     }
3080
3081 #define GENERIC_ID expr->value.function.isym->id
3082   else if (expr->value.function.actual != NULL
3083            && expr->value.function.isym != NULL
3084            && GENERIC_ID != GFC_ISYM_LBOUND
3085            && GENERIC_ID != GFC_ISYM_LEN
3086            && GENERIC_ID != GFC_ISYM_LOC
3087            && GENERIC_ID != GFC_ISYM_PRESENT)
3088     {
3089       /* Array intrinsics must also have the last upper bound of an
3090          assumed size array argument.  UBOUND and SIZE have to be
3091          excluded from the check if the second argument is anything
3092          than a constant.  */
3093
3094       for (arg = expr->value.function.actual; arg; arg = arg->next)
3095         {
3096           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3097               && arg->next != NULL && arg->next->expr)
3098             {
3099               if (arg->next->expr->expr_type != EXPR_CONSTANT)
3100                 break;
3101
3102               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
3103                 break;
3104
3105               if ((int)mpz_get_si (arg->next->expr->value.integer)
3106                         < arg->expr->rank)
3107                 break;
3108             }
3109
3110           if (arg->expr != NULL
3111               && arg->expr->rank > 0
3112               && resolve_assumed_size_actual (arg->expr))
3113             return FAILURE;
3114         }
3115     }
3116 #undef GENERIC_ID
3117
3118   need_full_assumed_size = temp;
3119   name = NULL;
3120
3121   if (!pure_function (expr, &name) && name)
3122     {
3123       if (forall_flag)
3124         {
3125           gfc_error ("reference to non-PURE function '%s' at %L inside a "
3126                      "FORALL %s", name, &expr->where,
3127                      forall_flag == 2 ? "mask" : "block");
3128           t = FAILURE;
3129         }
3130       else if (gfc_pure (NULL))
3131         {
3132           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
3133                      "procedure within a PURE procedure", name, &expr->where);
3134           t = FAILURE;
3135         }
3136     }
3137
3138   if (!pure_function (expr, &name) && name && gfc_implicit_pure (NULL))
3139     gfc_current_ns->proc_name->attr.implicit_pure = 0;
3140
3141   /* Functions without the RECURSIVE attribution are not allowed to
3142    * call themselves.  */
3143   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3144     {
3145       gfc_symbol *esym;
3146       esym = expr->value.function.esym;
3147
3148       if (is_illegal_recursion (esym, gfc_current_ns))
3149       {
3150         if (esym->attr.entry && esym->ns->entries)
3151           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3152                      " function '%s' is not RECURSIVE",
3153                      esym->name, &expr->where, esym->ns->entries->sym->name);
3154         else
3155           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
3156                      " is not RECURSIVE", esym->name, &expr->where);
3157
3158         t = FAILURE;
3159       }
3160     }
3161
3162   /* Character lengths of use associated functions may contains references to
3163      symbols not referenced from the current program unit otherwise.  Make sure
3164      those symbols are marked as referenced.  */
3165
3166   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3167       && expr->value.function.esym->attr.use_assoc)
3168     {
3169       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3170     }
3171
3172   /* Make sure that the expression has a typespec that works.  */
3173   if (expr->ts.type == BT_UNKNOWN)
3174     {
3175       if (expr->symtree->n.sym->result
3176             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3177             && !expr->symtree->n.sym->result->attr.proc_pointer)
3178         expr->ts = expr->symtree->n.sym->result->ts;
3179     }
3180
3181   return t;
3182 }
3183
3184
3185 /************* Subroutine resolution *************/
3186
3187 static void
3188 pure_subroutine (gfc_code *c, gfc_symbol *sym)
3189 {
3190   if (gfc_pure (sym))
3191     return;
3192
3193   if (forall_flag)
3194     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
3195                sym->name, &c->loc);
3196   else if (gfc_pure (NULL))
3197     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
3198                &c->loc);
3199 }
3200
3201
3202 static match
3203 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3204 {
3205   gfc_symbol *s;
3206
3207   if (sym->attr.generic)
3208     {
3209       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3210       if (s != NULL)
3211         {
3212           c->resolved_sym = s;
3213           pure_subroutine (c, s);
3214           return MATCH_YES;
3215         }
3216
3217       /* TODO: Need to search for elemental references in generic interface.  */
3218     }
3219
3220   if (sym->attr.intrinsic)
3221     return gfc_intrinsic_sub_interface (c, 0);
3222
3223   return MATCH_NO;
3224 }
3225
3226
3227 static gfc_try
3228 resolve_generic_s (gfc_code *c)
3229 {
3230   gfc_symbol *sym;
3231   match m;
3232
3233   sym = c->symtree->n.sym;
3234
3235   for (;;)
3236     {
3237       m = resolve_generic_s0 (c, sym);
3238       if (m == MATCH_YES)
3239         return SUCCESS;
3240       else if (m == MATCH_ERROR)
3241         return FAILURE;
3242
3243 generic:
3244       if (sym->ns->parent == NULL)
3245         break;
3246       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3247
3248       if (sym == NULL)
3249         break;
3250       if (!generic_sym (sym))
3251         goto generic;
3252     }
3253
3254   /* Last ditch attempt.  See if the reference is to an intrinsic
3255      that possesses a matching interface.  14.1.2.4  */
3256   sym = c->symtree->n.sym;
3257
3258   if (!gfc_is_intrinsic (sym, 1, c->loc))
3259     {
3260       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3261                  sym->name, &c->loc);
3262       return FAILURE;
3263     }
3264
3265   m = gfc_intrinsic_sub_interface (c, 0);
3266   if (m == MATCH_YES)
3267     return SUCCESS;
3268   if (m == MATCH_NO)
3269     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3270                "intrinsic subroutine interface", sym->name, &c->loc);
3271
3272   return FAILURE;
3273 }
3274
3275
3276 /* Set the name and binding label of the subroutine symbol in the call
3277    expression represented by 'c' to include the type and kind of the
3278    second parameter.  This function is for resolving the appropriate
3279    version of c_f_pointer() and c_f_procpointer().  For example, a
3280    call to c_f_pointer() for a default integer pointer could have a
3281    name of c_f_pointer_i4.  If no second arg exists, which is an error
3282    for these two functions, it defaults to the generic symbol's name
3283    and binding label.  */
3284
3285 static void
3286 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3287                     char *name, char *binding_label)
3288 {
3289   gfc_expr *arg = NULL;
3290   char type;
3291   int kind;
3292
3293   /* The second arg of c_f_pointer and c_f_procpointer determines
3294      the type and kind for the procedure name.  */
3295   arg = c->ext.actual->next->expr;
3296
3297   if (arg != NULL)
3298     {
3299       /* Set up the name to have the given symbol's name,
3300          plus the type and kind.  */
3301       /* a derived type is marked with the type letter 'u' */
3302       if (arg->ts.type == BT_DERIVED)
3303         {
3304           type = 'd';
3305           kind = 0; /* set the kind as 0 for now */
3306         }
3307       else
3308         {
3309           type = gfc_type_letter (arg->ts.type);
3310           kind = arg->ts.kind;
3311         }
3312
3313       if (arg->ts.type == BT_CHARACTER)
3314         /* Kind info for character strings not needed.  */
3315         kind = 0;
3316
3317       sprintf (name, "%s_%c%d", sym->name, type, kind);
3318       /* Set up the binding label as the given symbol's label plus
3319          the type and kind.  */
3320       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
3321     }
3322   else
3323     {
3324       /* If the second arg is missing, set the name and label as
3325          was, cause it should at least be found, and the missing
3326          arg error will be caught by compare_parameters().  */
3327       sprintf (name, "%s", sym->name);
3328       sprintf (binding_label, "%s", sym->binding_label);
3329     }
3330    
3331   return;
3332 }
3333
3334
3335 /* Resolve a generic version of the iso_c_binding procedure given
3336    (sym) to the specific one based on the type and kind of the
3337    argument(s).  Currently, this function resolves c_f_pointer() and
3338    c_f_procpointer based on the type and kind of the second argument
3339    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3340    Upon successfully exiting, c->resolved_sym will hold the resolved
3341    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3342    otherwise.  */
3343
3344 match
3345 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3346 {
3347   gfc_symbol *new_sym;
3348   /* this is fine, since we know the names won't use the max */
3349   char name[GFC_MAX_SYMBOL_LEN + 1];
3350   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3351   /* default to success; will override if find error */
3352   match m = MATCH_YES;
3353
3354   /* Make sure the actual arguments are in the necessary order (based on the 
3355      formal args) before resolving.  */
3356   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3357
3358   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3359       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3360     {
3361       set_name_and_label (c, sym, name, binding_label);
3362       
3363       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3364         {
3365           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3366             {
3367               /* Make sure we got a third arg if the second arg has non-zero
3368                  rank.  We must also check that the type and rank are
3369                  correct since we short-circuit this check in
3370                  gfc_procedure_use() (called above to sort actual args).  */
3371               if (c->ext.actual->next->expr->rank != 0)
3372                 {
3373                   if(c->ext.actual->next->next == NULL 
3374                      || c->ext.actual->next->next->expr == NULL)
3375                     {
3376                       m = MATCH_ERROR;
3377                       gfc_error ("Missing SHAPE parameter for call to %s "
3378                                  "at %L", sym->name, &(c->loc));
3379                     }
3380                   else if (c->ext.actual->next->next->expr->ts.type
3381                            != BT_INTEGER
3382                            || c->ext.actual->next->next->expr->rank != 1)
3383                     {
3384                       m = MATCH_ERROR;
3385                       gfc_error ("SHAPE parameter for call to %s at %L must "
3386                                  "be a rank 1 INTEGER array", sym->name,
3387                                  &(c->loc));
3388                     }
3389                 }
3390             }
3391         }
3392       
3393       if (m != MATCH_ERROR)
3394         {
3395           /* the 1 means to add the optional arg to formal list */
3396           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3397          
3398           /* for error reporting, say it's declared where the original was */
3399           new_sym->declared_at = sym->declared_at;
3400         }
3401     }
3402   else
3403     {
3404       /* no differences for c_loc or c_funloc */
3405       new_sym = sym;
3406     }
3407
3408   /* set the resolved symbol */
3409   if (m != MATCH_ERROR)
3410     c->resolved_sym = new_sym;
3411   else
3412     c->resolved_sym = sym;
3413   
3414   return m;
3415 }
3416
3417
3418 /* Resolve a subroutine call known to be specific.  */
3419
3420 static match
3421 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3422 {
3423   match m;
3424
3425   if(sym->attr.is_iso_c)
3426     {
3427       m = gfc_iso_c_sub_interface (c,sym);
3428       return m;
3429     }
3430   
3431   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3432     {
3433       if (sym->attr.dummy)
3434         {
3435           sym->attr.proc = PROC_DUMMY;
3436           goto found;
3437         }
3438
3439       sym->attr.proc = PROC_EXTERNAL;
3440       goto found;
3441     }
3442
3443   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3444     goto found;
3445
3446   if (sym->attr.intrinsic)
3447     {
3448       m = gfc_intrinsic_sub_interface (c, 1);
3449       if (m == MATCH_YES)
3450         return MATCH_YES;
3451       if (m == MATCH_NO)
3452         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3453                    "with an intrinsic", sym->name, &c->loc);
3454
3455       return MATCH_ERROR;
3456     }
3457
3458   return MATCH_NO;
3459
3460 found:
3461   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3462
3463   c->resolved_sym = sym;
3464   pure_subroutine (c, sym);
3465
3466   return MATCH_YES;
3467 }
3468
3469
3470 static gfc_try
3471 resolve_specific_s (gfc_code *c)
3472 {
3473   gfc_symbol *sym;
3474   match m;
3475
3476   sym = c->symtree->n.sym;
3477
3478   for (;;)
3479     {
3480       m = resolve_specific_s0 (c, sym);
3481       if (m == MATCH_YES)
3482         return SUCCESS;
3483       if (m == MATCH_ERROR)
3484         return FAILURE;
3485
3486       if (sym->ns->parent == NULL)
3487         break;
3488
3489       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3490
3491       if (sym == NULL)
3492         break;
3493     }
3494
3495   sym = c->symtree->n.sym;
3496   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3497              sym->name, &c->loc);
3498
3499   return FAILURE;
3500 }
3501
3502
3503 /* Resolve a subroutine call not known to be generic nor specific.  */
3504
3505 static gfc_try
3506 resolve_unknown_s (gfc_code *c)
3507 {
3508   gfc_symbol *sym;
3509
3510   sym = c->symtree->n.sym;
3511
3512   if (sym->attr.dummy)
3513     {
3514       sym->attr.proc = PROC_DUMMY;
3515       goto found;
3516     }
3517
3518   /* See if we have an intrinsic function reference.  */
3519
3520   if (gfc_is_intrinsic (sym, 1, c->loc))
3521     {
3522       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3523         return SUCCESS;
3524       return FAILURE;
3525     }
3526
3527   /* The reference is to an external name.  */
3528
3529 found:
3530   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3531
3532   c->resolved_sym = sym;
3533
3534   pure_subroutine (c, sym);
3535
3536   return SUCCESS;
3537 }
3538
3539
3540 /* Resolve a subroutine call.  Although it was tempting to use the same code
3541    for functions, subroutines and functions are stored differently and this
3542    makes things awkward.  */
3543
3544 static gfc_try
3545 resolve_call (gfc_code *c)
3546 {
3547   gfc_try t;
3548   procedure_type ptype = PROC_INTRINSIC;
3549   gfc_symbol *csym, *sym;
3550   bool no_formal_args;
3551
3552   csym = c->symtree ? c->symtree->n.sym : NULL;
3553
3554   if (csym && csym->ts.type != BT_UNKNOWN)
3555     {
3556       gfc_error ("'%s' at %L has a type, which is not consistent with "
3557                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3558       return FAILURE;
3559     }
3560
3561   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3562     {
3563       gfc_symtree *st;
3564       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3565       sym = st ? st->n.sym : NULL;
3566       if (sym && csym != sym
3567               && sym->ns == gfc_current_ns
3568               && sym->attr.flavor == FL_PROCEDURE
3569               && sym->attr.contained)
3570         {
3571           sym->refs++;
3572           if (csym->attr.generic)
3573             c->symtree->n.sym = sym;
3574           else
3575             c->symtree = st;
3576           csym = c->symtree->n.sym;
3577         }
3578     }
3579
3580   /* If this ia a deferred TBP with an abstract interface
3581      (which may of course be referenced), c->expr1 will be set.  */
3582   if (csym && csym->attr.abstract && !c->expr1)
3583     {
3584       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3585                  csym->name, &c->loc);
3586       return FAILURE;
3587     }
3588
3589   /* Subroutines without the RECURSIVE attribution are not allowed to
3590    * call themselves.  */
3591   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3592     {
3593       if (csym->attr.entry && csym->ns->entries)
3594         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3595                    " subroutine '%s' is not RECURSIVE",
3596                    csym->name, &c->loc, csym->ns->entries->sym->name);
3597       else
3598         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3599                    " is not RECURSIVE", csym->name, &c->loc);
3600
3601       t = FAILURE;
3602     }
3603
3604   /* Switch off assumed size checking and do this again for certain kinds
3605      of procedure, once the procedure itself is resolved.  */
3606   need_full_assumed_size++;
3607
3608   if (csym)
3609     ptype = csym->attr.proc;
3610
3611   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3612   if (resolve_actual_arglist (c->ext.actual, ptype,
3613                               no_formal_args) == FAILURE)
3614     return FAILURE;
3615
3616   /* Resume assumed_size checking.  */
3617   need_full_assumed_size--;
3618
3619   /* If external, check for usage.  */
3620   if (csym && is_external_proc (csym))
3621     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3622
3623   t = SUCCESS;
3624   if (c->resolved_sym == NULL)
3625     {
3626       c->resolved_isym = NULL;
3627       switch (procedure_kind (csym))
3628         {
3629         case PTYPE_GENERIC:
3630           t = resolve_generic_s (c);
3631           break;
3632
3633         case PTYPE_SPECIFIC:
3634           t = resolve_specific_s (c);
3635           break;
3636
3637         case PTYPE_UNKNOWN:
3638           t = resolve_unknown_s (c);
3639           break;
3640
3641         default:
3642           gfc_internal_error ("resolve_subroutine(): bad function type");
3643         }
3644     }
3645
3646   /* Some checks of elemental subroutine actual arguments.  */
3647   if (resolve_elemental_actual (NULL, c) == FAILURE)
3648     return FAILURE;
3649
3650   return t;
3651 }
3652
3653
3654 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3655    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3656    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3657    if their shapes do not match.  If either op1->shape or op2->shape is
3658    NULL, return SUCCESS.  */
3659
3660 static gfc_try
3661 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3662 {
3663   gfc_try t;
3664   int i;
3665
3666   t = SUCCESS;
3667
3668   if (op1->shape != NULL && op2->shape != NULL)
3669     {
3670       for (i = 0; i < op1->rank; i++)
3671         {
3672           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3673            {
3674              gfc_error ("Shapes for operands at %L and %L are not conformable",
3675                          &op1->where, &op2->where);
3676              t = FAILURE;
3677              break;
3678            }
3679         }
3680     }
3681
3682   return t;
3683 }
3684
3685
3686 /* Resolve an operator expression node.  This can involve replacing the
3687    operation with a user defined function call.  */
3688
3689 static gfc_try
3690 resolve_operator (gfc_expr *e)
3691 {
3692   gfc_expr *op1, *op2;
3693   char msg[200];
3694   bool dual_locus_error;
3695   gfc_try t;
3696
3697   /* Resolve all subnodes-- give them types.  */
3698
3699   switch (e->value.op.op)
3700     {
3701     default:
3702       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3703         return FAILURE;
3704
3705     /* Fall through...  */
3706
3707     case INTRINSIC_NOT:
3708     case INTRINSIC_UPLUS:
3709     case INTRINSIC_UMINUS:
3710     case INTRINSIC_PARENTHESES:
3711       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3712         return FAILURE;
3713       break;
3714     }
3715
3716   /* Typecheck the new node.  */
3717
3718   op1 = e->value.op.op1;
3719   op2 = e->value.op.op2;
3720   dual_locus_error = false;
3721
3722   if ((op1 && op1->expr_type == EXPR_NULL)
3723       || (op2 && op2->expr_type == EXPR_NULL))
3724     {
3725       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3726       goto bad_op;
3727     }
3728
3729   switch (e->value.op.op)
3730     {
3731     case INTRINSIC_UPLUS:
3732     case INTRINSIC_UMINUS:
3733       if (op1->ts.type == BT_INTEGER
3734           || op1->ts.type == BT_REAL
3735           || op1->ts.type == BT_COMPLEX)
3736         {
3737           e->ts = op1->ts;
3738           break;
3739         }
3740
3741       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3742                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3743       goto bad_op;
3744
3745     case INTRINSIC_PLUS:
3746     case INTRINSIC_MINUS:
3747     case INTRINSIC_TIMES:
3748     case INTRINSIC_DIVIDE:
3749     case INTRINSIC_POWER:
3750       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3751         {
3752           gfc_type_convert_binary (e, 1);
3753           break;
3754         }
3755
3756       sprintf (msg,
3757                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3758                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3759                gfc_typename (&op2->ts));
3760       goto bad_op;
3761
3762     case INTRINSIC_CONCAT:
3763       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3764           && op1->ts.kind == op2->ts.kind)
3765         {
3766           e->ts.type = BT_CHARACTER;
3767           e->ts.kind = op1->ts.kind;
3768           break;
3769         }
3770
3771       sprintf (msg,
3772                _("Operands of string concatenation operator at %%L are %s/%s"),
3773                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3774       goto bad_op;
3775
3776     case INTRINSIC_AND:
3777     case INTRINSIC_OR:
3778     case INTRINSIC_EQV:
3779     case INTRINSIC_NEQV:
3780       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3781         {
3782           e->ts.type = BT_LOGICAL;
3783           e->ts.kind = gfc_kind_max (op1, op2);
3784           if (op1->ts.kind < e->ts.kind)
3785             gfc_convert_type (op1, &e->ts, 2);
3786           else if (op2->ts.kind < e->ts.kind)
3787             gfc_convert_type (op2, &e->ts, 2);
3788           break;
3789         }
3790
3791       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3792                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3793                gfc_typename (&op2->ts));
3794
3795       goto bad_op;
3796
3797     case INTRINSIC_NOT:
3798       if (op1->ts.type == BT_LOGICAL)
3799         {
3800           e->ts.type = BT_LOGICAL;
3801           e->ts.kind = op1->ts.kind;
3802           break;
3803         }
3804
3805       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3806                gfc_typename (&op1->ts));
3807       goto bad_op;
3808
3809     case INTRINSIC_GT:
3810     case INTRINSIC_GT_OS:
3811     case INTRINSIC_GE:
3812     case INTRINSIC_GE_OS:
3813     case INTRINSIC_LT:
3814     case INTRINSIC_LT_OS:
3815     case INTRINSIC_LE:
3816     case INTRINSIC_LE_OS:
3817       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3818         {
3819           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3820           goto bad_op;
3821         }
3822
3823       /* Fall through...  */
3824
3825     case INTRINSIC_EQ:
3826     case INTRINSIC_EQ_OS:
3827     case INTRINSIC_NE:
3828     case INTRINSIC_NE_OS:
3829       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3830           && op1->ts.kind == op2->ts.kind)
3831         {
3832           e->ts.type = BT_LOGICAL;
3833           e->ts.kind = gfc_default_logical_kind;
3834           break;
3835         }
3836
3837       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3838         {
3839           gfc_type_convert_binary (e, 1);
3840
3841           e->ts.type = BT_LOGICAL;
3842           e->ts.kind = gfc_default_logical_kind;
3843           break;
3844         }
3845
3846       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3847         sprintf (msg,
3848                  _("Logicals at %%L must be compared with %s instead of %s"),
3849                  (e->value.op.op == INTRINSIC_EQ 
3850                   || e->value.op.op == INTRINSIC_EQ_OS)
3851                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3852       else
3853         sprintf (msg,
3854                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3855                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3856                  gfc_typename (&op2->ts));
3857
3858       goto bad_op;
3859
3860     case INTRINSIC_USER:
3861       if (e->value.op.uop->op == NULL)
3862         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3863       else if (op2 == NULL)
3864         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3865                  e->value.op.uop->name, gfc_typename (&op1->ts));
3866       else
3867         {
3868           sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3869                    e->value.op.uop->name, gfc_typename (&op1->ts),
3870                    gfc_typename (&op2->ts));
3871           e->value.op.uop->op->sym->attr.referenced = 1;
3872         }
3873
3874       goto bad_op;
3875
3876     case INTRINSIC_PARENTHESES:
3877       e->ts = op1->ts;
3878       if (e->ts.type == BT_CHARACTER)
3879         e->ts.u.cl = op1->ts.u.cl;
3880       break;
3881
3882     default:
3883       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3884     }
3885
3886   /* Deal with arrayness of an operand through an operator.  */
3887
3888   t = SUCCESS;
3889
3890   switch (e->value.op.op)
3891     {
3892     case INTRINSIC_PLUS:
3893     case INTRINSIC_MINUS:
3894     case INTRINSIC_TIMES:
3895     case INTRINSIC_DIVIDE:
3896     case INTRINSIC_POWER:
3897     case INTRINSIC_CONCAT:
3898     case INTRINSIC_AND:
3899     case INTRINSIC_OR:
3900     case INTRINSIC_EQV:
3901     case INTRINSIC_NEQV:
3902     case INTRINSIC_EQ:
3903     case INTRINSIC_EQ_OS:
3904     case INTRINSIC_NE:
3905     case INTRINSIC_NE_OS:
3906     case INTRINSIC_GT:
3907     case INTRINSIC_GT_OS:
3908     case INTRINSIC_GE:
3909     case INTRINSIC_GE_OS:
3910     case INTRINSIC_LT:
3911     case INTRINSIC_LT_OS:
3912     case INTRINSIC_LE:
3913     case INTRINSIC_LE_OS:
3914
3915       if (op1->rank == 0 && op2->rank == 0)
3916         e->rank = 0;
3917
3918       if (op1->rank == 0 && op2->rank != 0)
3919         {
3920           e->rank = op2->rank;
3921
3922           if (e->shape == NULL)
3923             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3924         }
3925
3926       if (op1->rank != 0 && op2->rank == 0)
3927         {
3928           e->rank = op1->rank;
3929
3930           if (e->shape == NULL)
3931             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3932         }
3933
3934       if (op1->rank != 0 && op2->rank != 0)
3935         {
3936           if (op1->rank == op2->rank)
3937             {
3938               e->rank = op1->rank;
3939               if (e->shape == NULL)
3940                 {
3941                   t = compare_shapes (op1, op2);
3942                   if (t == FAILURE)
3943                     e->shape = NULL;
3944                   else
3945                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
3946                 }
3947             }
3948           else
3949             {
3950               /* Allow higher level expressions to work.  */
3951               e->rank = 0;
3952
3953               /* Try user-defined operators, and otherwise throw an error.  */
3954               dual_locus_error = true;
3955               sprintf (msg,
3956                        _("Inconsistent ranks for operator at %%L and %%L"));
3957               goto bad_op;
3958             }
3959         }
3960
3961       break;
3962
3963     case INTRINSIC_PARENTHESES:
3964     case INTRINSIC_NOT:
3965     case INTRINSIC_UPLUS:
3966     case INTRINSIC_UMINUS:
3967       /* Simply copy arrayness attribute */
3968       e->rank = op1->rank;
3969
3970       if (e->shape == NULL)
3971         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3972
3973       break;
3974
3975     default:
3976       break;
3977     }
3978
3979   /* Attempt to simplify the expression.  */
3980   if (t == SUCCESS)
3981     {
3982       t = gfc_simplify_expr (e, 0);
3983       /* Some calls do not succeed in simplification and return FAILURE
3984          even though there is no error; e.g. variable references to
3985          PARAMETER arrays.  */
3986       if (!gfc_is_constant_expr (e))
3987         t = SUCCESS;
3988     }
3989   return t;
3990
3991 bad_op:
3992
3993   {
3994     bool real_error;
3995     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3996       return SUCCESS;
3997
3998     if (real_error)
3999       return FAILURE;
4000   }
4001
4002   if (dual_locus_error)
4003     gfc_error (msg, &op1->where, &op2->where);
4004   else
4005     gfc_error (msg, &e->where);
4006
4007   return FAILURE;
4008 }
4009
4010
4011 /************** Array resolution subroutines **************/
4012
4013 typedef enum
4014 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
4015 comparison;
4016
4017 /* Compare two integer expressions.  */
4018
4019 static comparison
4020 compare_bound (gfc_expr *a, gfc_expr *b)
4021 {
4022   int i;
4023
4024   if (a == NULL || a->expr_type != EXPR_CONSTANT
4025       || b == NULL || b->expr_type != EXPR_CONSTANT)
4026     return CMP_UNKNOWN;
4027
4028   /* If either of the types isn't INTEGER, we must have
4029      raised an error earlier.  */
4030
4031   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
4032     return CMP_UNKNOWN;
4033
4034   i = mpz_cmp (a->value.integer, b->value.integer);
4035
4036   if (i < 0)
4037     return CMP_LT;
4038   if (i > 0)
4039     return CMP_GT;
4040   return CMP_EQ;
4041 }
4042
4043
4044 /* Compare an integer expression with an integer.  */
4045
4046 static comparison
4047 compare_bound_int (gfc_expr *a, int b)
4048 {
4049   int i;
4050
4051   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4052     return CMP_UNKNOWN;
4053
4054   if (a->ts.type != BT_INTEGER)
4055     gfc_internal_error ("compare_bound_int(): Bad expression");
4056
4057   i = mpz_cmp_si (a->value.integer, b);
4058
4059   if (i < 0)
4060     return CMP_LT;
4061   if (i > 0)
4062     return CMP_GT;
4063   return CMP_EQ;
4064 }
4065
4066
4067 /* Compare an integer expression with a mpz_t.  */
4068
4069 static comparison
4070 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
4071 {
4072   int i;
4073
4074   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4075     return CMP_UNKNOWN;
4076
4077   if (a->ts.type != BT_INTEGER)
4078     gfc_internal_error ("compare_bound_int(): Bad expression");
4079
4080   i = mpz_cmp (a->value.integer, b);
4081
4082   if (i < 0)
4083     return CMP_LT;
4084   if (i > 0)
4085     return CMP_GT;
4086   return CMP_EQ;
4087 }
4088
4089
4090 /* Compute the last value of a sequence given by a triplet.  
4091    Return 0 if it wasn't able to compute the last value, or if the
4092    sequence if empty, and 1 otherwise.  */
4093
4094 static int
4095 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
4096                                 gfc_expr *stride, mpz_t last)
4097 {
4098   mpz_t rem;
4099
4100   if (start == NULL || start->expr_type != EXPR_CONSTANT
4101       || end == NULL || end->expr_type != EXPR_CONSTANT
4102       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
4103     return 0;
4104
4105   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
4106       || (stride != NULL && stride->ts.type != BT_INTEGER))
4107     return 0;
4108
4109   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
4110     {
4111       if (compare_bound (start, end) == CMP_GT)
4112         return 0;
4113       mpz_set (last, end->value.integer);
4114       return 1;
4115     }
4116
4117   if (compare_bound_int (stride, 0) == CMP_GT)
4118     {
4119       /* Stride is positive */
4120       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
4121         return 0;
4122     }
4123   else
4124     {
4125       /* Stride is negative */
4126       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
4127         return 0;
4128     }
4129
4130   mpz_init (rem);
4131   mpz_sub (rem, end->value.integer, start->value.integer);
4132   mpz_tdiv_r (rem, rem, stride->value.integer);
4133   mpz_sub (last, end->value.integer, rem);
4134   mpz_clear (rem);
4135
4136   return 1;
4137 }
4138
4139
4140 /* Compare a single dimension of an array reference to the array
4141    specification.  */
4142
4143 static gfc_try
4144 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
4145 {
4146   mpz_t last_value;
4147
4148   if (ar->dimen_type[i] == DIMEN_STAR)
4149     {
4150       gcc_assert (ar->stride[i] == NULL);
4151       /* This implies [*] as [*:] and [*:3] are not possible.  */
4152       if (ar->start[i] == NULL)
4153         {
4154           gcc_assert (ar->end[i] == NULL);
4155           return SUCCESS;
4156         }
4157     }
4158
4159 /* Given start, end and stride values, calculate the minimum and
4160    maximum referenced indexes.  */
4161
4162   switch (ar->dimen_type[i])
4163     {
4164     case DIMEN_VECTOR:
4165     case DIMEN_THIS_IMAGE:
4166       break;
4167
4168     case DIMEN_STAR:
4169     case DIMEN_ELEMENT:
4170       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4171         {
4172           if (i < as->rank)
4173             gfc_warning ("Array reference at %L is out of bounds "
4174                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
4175                          mpz_get_si (ar->start[i]->value.integer),
4176                          mpz_get_si (as->lower[i]->value.integer), i+1);
4177           else
4178             gfc_warning ("Array reference at %L is out of bounds "
4179                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
4180                          mpz_get_si (ar->start[i]->value.integer),
4181                          mpz_get_si (as->lower[i]->value.integer),
4182                          i + 1 - as->rank);
4183           return SUCCESS;
4184         }
4185       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4186         {
4187           if (i < as->rank)
4188             gfc_warning ("Array reference at %L is out of bounds "
4189                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
4190                          mpz_get_si (ar->start[i]->value.integer),
4191                          mpz_get_si (as->upper[i]->value.integer), i+1);
4192           else
4193             gfc_warning ("Array reference at %L is out of bounds "
4194                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
4195                          mpz_get_si (ar->start[i]->value.integer),
4196                          mpz_get_si (as->upper[i]->value.integer),
4197                          i + 1 - as->rank);
4198           return SUCCESS;
4199         }
4200
4201       break;
4202
4203     case DIMEN_RANGE:
4204       {
4205 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4206 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4207
4208         comparison comp_start_end = compare_bound (AR_START, AR_END);
4209
4210         /* Check for zero stride, which is not allowed.  */
4211         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4212           {
4213             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4214             return FAILURE;
4215           }
4216
4217         /* if start == len || (stride > 0 && start < len)
4218                            || (stride < 0 && start > len),
4219            then the array section contains at least one element.  In this
4220            case, there is an out-of-bounds access if
4221            (start < lower || start > upper).  */
4222         if (compare_bound (AR_START, AR_END) == CMP_EQ
4223             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4224                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4225             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4226                 && comp_start_end == CMP_GT))
4227           {
4228             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4229               {
4230                 gfc_warning ("Lower array reference at %L is out of bounds "
4231                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4232                        mpz_get_si (AR_START->value.integer),
4233                        mpz_get_si (as->lower[i]->value.integer), i+1);
4234                 return SUCCESS;
4235               }
4236             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4237               {
4238                 gfc_warning ("Lower array reference at %L is out of bounds "
4239                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4240                        mpz_get_si (AR_START->value.integer),
4241                        mpz_get_si (as->upper[i]->value.integer), i+1);
4242                 return SUCCESS;
4243               }
4244           }
4245
4246         /* If we can compute the highest index of the array section,
4247            then it also has to be between lower and upper.  */
4248         mpz_init (last_value);
4249         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4250                                             last_value))
4251           {
4252             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4253               {
4254                 gfc_warning ("Upper array reference at %L is out of bounds "
4255                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4256                        mpz_get_si (last_value),
4257                        mpz_get_si (as->lower[i]->value.integer), i+1);
4258                 mpz_clear (last_value);
4259                 return SUCCESS;
4260               }
4261             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4262               {
4263                 gfc_warning ("Upper array reference at %L is out of bounds "
4264                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4265                        mpz_get_si (last_value),
4266                        mpz_get_si (as->upper[i]->value.integer), i+1);
4267                 mpz_clear (last_value);
4268                 return SUCCESS;
4269               }
4270           }
4271         mpz_clear (last_value);
4272
4273 #undef AR_START
4274 #undef AR_END
4275       }
4276       break;
4277
4278     default:
4279       gfc_internal_error ("check_dimension(): Bad array reference");
4280     }
4281
4282   return SUCCESS;
4283 }
4284
4285
4286 /* Compare an array reference with an array specification.  */
4287
4288 static gfc_try
4289 compare_spec_to_ref (gfc_array_ref *ar)
4290 {
4291   gfc_array_spec *as;
4292   int i;
4293
4294   as = ar->as;
4295   i = as->rank - 1;
4296   /* TODO: Full array sections are only allowed as actual parameters.  */
4297   if (as->type == AS_ASSUMED_SIZE
4298       && (/*ar->type == AR_FULL
4299           ||*/ (ar->type == AR_SECTION
4300               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4301     {
4302       gfc_error ("Rightmost upper bound of assumed size array section "
4303                  "not specified at %L", &ar->where);
4304       return FAILURE;
4305     }
4306
4307   if (ar->type == AR_FULL)
4308     return SUCCESS;
4309
4310   if (as->rank != ar->dimen)
4311     {
4312       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4313                  &ar->where, ar->dimen, as->rank);
4314       return FAILURE;
4315     }
4316
4317   /* ar->codimen == 0 is a local array.  */
4318   if (as->corank != ar->codimen && ar->codimen != 0)
4319     {
4320       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4321                  &ar->where, ar->codimen, as->corank);
4322       return FAILURE;
4323     }
4324
4325   for (i = 0; i < as->rank; i++)
4326     if (check_dimension (i, ar, as) == FAILURE)
4327       return FAILURE;
4328
4329   /* Local access has no coarray spec.  */
4330   if (ar->codimen != 0)
4331     for (i = as->rank; i < as->rank + as->corank; i++)
4332       {
4333         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate
4334             && ar->dimen_type[i] != DIMEN_THIS_IMAGE)
4335           {
4336             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4337                        i + 1 - as->rank, &ar->where);
4338             return FAILURE;
4339           }
4340         if (check_dimension (i, ar, as) == FAILURE)
4341           return FAILURE;
4342       }
4343
4344   if (as->corank && ar->codimen == 0)
4345     {
4346       int n;
4347       ar->codimen = as->corank;
4348       for (n = ar->dimen; n < ar->dimen + ar->codimen; n++)
4349         ar->dimen_type[n] = DIMEN_THIS_IMAGE;
4350     }
4351
4352   return SUCCESS;
4353 }
4354
4355
4356 /* Resolve one part of an array index.  */
4357
4358 static gfc_try
4359 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4360                      int force_index_integer_kind)
4361 {
4362   gfc_typespec ts;
4363
4364   if (index == NULL)
4365     return SUCCESS;
4366
4367   if (gfc_resolve_expr (index) == FAILURE)
4368     return FAILURE;
4369
4370   if (check_scalar && index->rank != 0)
4371     {
4372       gfc_error ("Array index at %L must be scalar", &index->where);
4373       return FAILURE;
4374     }
4375
4376   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4377     {
4378       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4379                  &index->where, gfc_basic_typename (index->ts.type));
4380       return FAILURE;
4381     }
4382
4383   if (index->ts.type == BT_REAL)
4384     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4385                         &index->where) == FAILURE)
4386       return FAILURE;
4387
4388   if ((index->ts.kind != gfc_index_integer_kind
4389        && force_index_integer_kind)
4390       || index->ts.type != BT_INTEGER)
4391     {
4392       gfc_clear_ts (&ts);
4393       ts.type = BT_INTEGER;
4394       ts.kind = gfc_index_integer_kind;
4395
4396       gfc_convert_type_warn (index, &ts, 2, 0);
4397     }
4398
4399   return SUCCESS;
4400 }
4401
4402 /* Resolve one part of an array index.  */
4403
4404 gfc_try
4405 gfc_resolve_index (gfc_expr *index, int check_scalar)
4406 {
4407   return gfc_resolve_index_1 (index, check_scalar, 1);
4408 }
4409
4410 /* Resolve a dim argument to an intrinsic function.  */
4411
4412 gfc_try
4413 gfc_resolve_dim_arg (gfc_expr *dim)
4414 {
4415   if (dim == NULL)
4416     return SUCCESS;
4417
4418   if (gfc_resolve_expr (dim) == FAILURE)
4419     return FAILURE;
4420
4421   if (dim->rank != 0)
4422     {
4423       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4424       return FAILURE;
4425
4426     }
4427
4428   if (dim->ts.type != BT_INTEGER)
4429     {
4430       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4431       return FAILURE;
4432     }
4433
4434   if (dim->ts.kind != gfc_index_integer_kind)
4435     {
4436       gfc_typespec ts;
4437
4438       gfc_clear_ts (&ts);
4439       ts.type = BT_INTEGER;
4440       ts.kind = gfc_index_integer_kind;
4441
4442       gfc_convert_type_warn (dim, &ts, 2, 0);
4443     }
4444
4445   return SUCCESS;
4446 }
4447
4448 /* Given an expression that contains array references, update those array
4449    references to point to the right array specifications.  While this is
4450    filled in during matching, this information is difficult to save and load
4451    in a module, so we take care of it here.
4452
4453    The idea here is that the original array reference comes from the
4454    base symbol.  We traverse the list of reference structures, setting
4455    the stored reference to references.  Component references can
4456    provide an additional array specification.  */
4457
4458 static void
4459 find_array_spec (gfc_expr *e)
4460 {
4461   gfc_array_spec *as;
4462   gfc_component *c;
4463   gfc_symbol *derived;
4464   gfc_ref *ref;
4465
4466   if (e->symtree->n.sym->ts.type == BT_CLASS)
4467     as = CLASS_DATA (e->symtree->n.sym)->as;
4468   else
4469     as = e->symtree->n.sym->as;
4470   derived = NULL;
4471
4472   for (ref = e->ref; ref; ref = ref->next)
4473     switch (ref->type)
4474       {
4475       case REF_ARRAY:
4476         if (as == NULL)
4477           gfc_internal_error ("find_array_spec(): Missing spec");
4478
4479         ref->u.ar.as = as;
4480         as = NULL;
4481         break;
4482
4483       case REF_COMPONENT:
4484         if (derived == NULL)
4485           derived = e->symtree->n.sym->ts.u.derived;
4486
4487         if (derived->attr.is_class)
4488           derived = derived->components->ts.u.derived;
4489
4490         c = derived->components;
4491
4492         for (; c; c = c->next)
4493           if (c == ref->u.c.component)
4494             {
4495               /* Track the sequence of component references.  */
4496               if (c->ts.type == BT_DERIVED)
4497                 derived = c->ts.u.derived;
4498               break;
4499             }
4500
4501         if (c == NULL)
4502           gfc_internal_error ("find_array_spec(): Component not found");
4503
4504         if (c->attr.dimension)
4505           {
4506             if (as != NULL)
4507               gfc_internal_error ("find_array_spec(): unused as(1)");
4508             as = c->as;
4509           }
4510
4511         break;
4512
4513       case REF_SUBSTRING:
4514         break;
4515       }
4516
4517   if (as != NULL)
4518     gfc_internal_error ("find_array_spec(): unused as(2)");
4519 }
4520
4521
4522 /* Resolve an array reference.  */
4523
4524 static gfc_try
4525 resolve_array_ref (gfc_array_ref *ar)
4526 {
4527   int i, check_scalar;
4528   gfc_expr *e;
4529
4530   for (i = 0; i < ar->dimen + ar->codimen; i++)
4531     {
4532       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4533
4534       /* Do not force gfc_index_integer_kind for the start.  We can
4535          do fine with any integer kind.  This avoids temporary arrays
4536          created for indexing with a vector.  */
4537       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4538         return FAILURE;
4539       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4540         return FAILURE;
4541       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4542         return FAILURE;
4543
4544       e = ar->start[i];
4545
4546       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4547         switch (e->rank)
4548           {
4549           case 0:
4550             ar->dimen_type[i] = DIMEN_ELEMENT;
4551             break;
4552
4553           case 1:
4554             ar->dimen_type[i] = DIMEN_VECTOR;
4555             if (e->expr_type == EXPR_VARIABLE
4556                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4557               ar->start[i] = gfc_get_parentheses (e);
4558             break;
4559
4560           default:
4561             gfc_error ("Array index at %L is an array of rank %d",
4562                        &ar->c_where[i], e->rank);
4563             return FAILURE;
4564           }
4565
4566       /* Fill in the upper bound, which may be lower than the
4567          specified one for something like a(2:10:5), which is
4568          identical to a(2:7:5).  Only relevant for strides not equal
4569          to one.  */
4570       if (ar->dimen_type[i] == DIMEN_RANGE
4571           && ar->stride[i] != NULL && ar->stride[i]->expr_type == EXPR_CONSTANT
4572           && mpz_cmp_si (ar->stride[i]->value.integer, 1L) != 0)
4573         {
4574           mpz_t size, end;
4575
4576           if (gfc_ref_dimen_size (ar, i, &size, &end) == SUCCESS)
4577             {
4578               if (ar->end[i] == NULL)
4579                 {
4580                   ar->end[i] =
4581                     gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
4582                                            &ar->where);
4583                   mpz_set (ar->end[i]->value.integer, end);
4584                 }
4585               else if (ar->end[i]->ts.type == BT_INTEGER
4586                        && ar->end[i]->expr_type == EXPR_CONSTANT)
4587                 {
4588                   mpz_set (ar->end[i]->value.integer, end);
4589                 }
4590               else
4591                 gcc_unreachable ();
4592
4593               mpz_clear (size);
4594               mpz_clear (end);
4595             }
4596         }
4597     }
4598
4599   if (ar->type == AR_FULL && ar->as->rank == 0)
4600     ar->type = AR_ELEMENT;
4601
4602   /* If the reference type is unknown, figure out what kind it is.  */
4603
4604   if (ar->type == AR_UNKNOWN)
4605     {
4606       ar->type = AR_ELEMENT;
4607       for (i = 0; i < ar->dimen; i++)
4608         if (ar->dimen_type[i] == DIMEN_RANGE
4609             || ar->dimen_type[i] == DIMEN_VECTOR)
4610           {
4611             ar->type = AR_SECTION;
4612             break;
4613           }
4614     }
4615
4616   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4617     return FAILURE;
4618
4619   return SUCCESS;
4620 }
4621
4622
4623 static gfc_try
4624 resolve_substring (gfc_ref *ref)
4625 {
4626   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4627
4628   if (ref->u.ss.start != NULL)
4629     {
4630       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4631         return FAILURE;
4632
4633       if (ref->u.ss.start->ts.type != BT_INTEGER)
4634         {
4635           gfc_error ("Substring start index at %L must be of type INTEGER",
4636                      &ref->u.ss.start->where);
4637           return FAILURE;
4638         }
4639
4640       if (ref->u.ss.start->rank != 0)
4641         {
4642           gfc_error ("Substring start index at %L must be scalar",
4643                      &ref->u.ss.start->where);
4644           return FAILURE;
4645         }
4646
4647       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4648           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4649               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4650         {
4651           gfc_error ("Substring start index at %L is less than one",
4652                      &ref->u.ss.start->where);
4653           return FAILURE;
4654         }
4655     }
4656
4657   if (ref->u.ss.end != NULL)
4658     {
4659       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4660         return FAILURE;
4661
4662       if (ref->u.ss.end->ts.type != BT_INTEGER)
4663         {
4664           gfc_error ("Substring end index at %L must be of type INTEGER",
4665                      &ref->u.ss.end->where);
4666           return FAILURE;
4667         }
4668
4669       if (ref->u.ss.end->rank != 0)
4670         {
4671           gfc_error ("Substring end index at %L must be scalar",
4672                      &ref->u.ss.end->where);
4673           return FAILURE;
4674         }
4675
4676       if (ref->u.ss.length != NULL
4677           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4678           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4679               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4680         {
4681           gfc_error ("Substring end index at %L exceeds the string length",
4682                      &ref->u.ss.start->where);
4683           return FAILURE;
4684         }
4685
4686       if (compare_bound_mpz_t (ref->u.ss.end,
4687                                gfc_integer_kinds[k].huge) == CMP_GT
4688           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4689               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4690         {
4691           gfc_error ("Substring end index at %L is too large",
4692                      &ref->u.ss.end->where);
4693           return FAILURE;
4694         }
4695     }
4696
4697   return SUCCESS;
4698 }
4699
4700
4701 /* This function supplies missing substring charlens.  */
4702
4703 void
4704 gfc_resolve_substring_charlen (gfc_expr *e)
4705 {
4706   gfc_ref *char_ref;
4707   gfc_expr *start, *end;
4708
4709   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4710     if (char_ref->type == REF_SUBSTRING)
4711       break;
4712
4713   if (!char_ref)
4714     return;
4715
4716   gcc_assert (char_ref->next == NULL);
4717
4718   if (e->ts.u.cl)
4719     {
4720       if (e->ts.u.cl->length)
4721         gfc_free_expr (e->ts.u.cl->length);
4722       else if (e->expr_type == EXPR_VARIABLE
4723                  && e->symtree->n.sym->attr.dummy)
4724         return;
4725     }
4726
4727   e->ts.type = BT_CHARACTER;
4728   e->ts.kind = gfc_default_character_kind;
4729
4730   if (!e->ts.u.cl)
4731     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4732
4733   if (char_ref->u.ss.start)
4734     start = gfc_copy_expr (char_ref->u.ss.start);
4735   else
4736     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4737
4738   if (char_ref->u.ss.end)
4739     end = gfc_copy_expr (char_ref->u.ss.end);
4740   else if (e->expr_type == EXPR_VARIABLE)
4741     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4742   else
4743     end = NULL;
4744
4745   if (!start || !end)
4746     return;
4747
4748   /* Length = (end - start +1).  */
4749   e->ts.u.cl->length = gfc_subtract (end, start);
4750   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4751                                 gfc_get_int_expr (gfc_default_integer_kind,
4752                                                   NULL, 1));
4753
4754   e->ts.u.cl->length->ts.type = BT_INTEGER;
4755   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4756
4757   /* Make sure that the length is simplified.  */
4758   gfc_simplify_expr (e->ts.u.cl->length, 1);
4759   gfc_resolve_expr (e->ts.u.cl->length);
4760 }
4761
4762
4763 /* Resolve subtype references.  */
4764
4765 static gfc_try
4766 resolve_ref (gfc_expr *expr)
4767 {
4768   int current_part_dimension, n_components, seen_part_dimension;
4769   gfc_ref *ref;
4770
4771   for (ref = expr->ref; ref; ref = ref->next)
4772     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4773       {
4774         find_array_spec (expr);
4775         break;
4776       }
4777
4778   for (ref = expr->ref; ref; ref = ref->next)
4779     switch (ref->type)
4780       {
4781       case REF_ARRAY:
4782         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4783           return FAILURE;
4784         break;
4785
4786       case REF_COMPONENT:
4787         break;
4788
4789       case REF_SUBSTRING:
4790         resolve_substring (ref);
4791         break;
4792       }
4793
4794   /* Check constraints on part references.  */
4795
4796   current_part_dimension = 0;
4797   seen_part_dimension = 0;
4798   n_components = 0;
4799
4800   for (ref = expr->ref; ref; ref = ref->next)
4801     {
4802       switch (ref->type)
4803         {
4804         case REF_ARRAY:
4805           switch (ref->u.ar.type)
4806             {
4807             case AR_FULL:
4808               /* Coarray scalar.  */
4809               if (ref->u.ar.as->rank == 0)
4810                 {
4811                   current_part_dimension = 0;
4812                   break;
4813                 }
4814               /* Fall through.  */
4815             case AR_SECTION:
4816               current_part_dimension = 1;
4817               break;
4818
4819             case AR_ELEMENT:
4820               current_part_dimension = 0;
4821               break;
4822
4823             case AR_UNKNOWN:
4824               gfc_internal_error ("resolve_ref(): Bad array reference");
4825             }
4826
4827           break;
4828
4829         case REF_COMPONENT:
4830           if (current_part_dimension || seen_part_dimension)
4831             {
4832               /* F03:C614.  */
4833               if (ref->u.c.component->attr.pointer
4834                   || ref->u.c.component->attr.proc_pointer)
4835                 {
4836                   gfc_error ("Component to the right of a part reference "
4837                              "with nonzero rank must not have the POINTER "
4838                              "attribute at %L", &expr->where);
4839                   return FAILURE;
4840                 }
4841               else if (ref->u.c.component->attr.allocatable)
4842                 {
4843                   gfc_error ("Component to the right of a part reference "
4844                              "with nonzero rank must not have the ALLOCATABLE "
4845                              "attribute at %L", &expr->where);
4846                   return FAILURE;
4847                 }
4848             }
4849
4850           n_components++;
4851           break;
4852
4853         case REF_SUBSTRING:
4854           break;
4855         }
4856
4857       if (((ref->type == REF_COMPONENT && n_components > 1)
4858            || ref->next == NULL)
4859           && current_part_dimension
4860           && seen_part_dimension)
4861         {
4862           gfc_error ("Two or more part references with nonzero rank must "
4863                      "not be specified at %L", &expr->where);
4864           return FAILURE;
4865         }
4866
4867       if (ref->type == REF_COMPONENT)
4868         {
4869           if (current_part_dimension)
4870             seen_part_dimension = 1;
4871
4872           /* reset to make sure */
4873           current_part_dimension = 0;
4874         }
4875     }
4876
4877   return SUCCESS;
4878 }
4879
4880
4881 /* Given an expression, determine its shape.  This is easier than it sounds.
4882    Leaves the shape array NULL if it is not possible to determine the shape.  */
4883
4884 static void
4885 expression_shape (gfc_expr *e)
4886 {
4887   mpz_t array[GFC_MAX_DIMENSIONS];
4888   int i;
4889
4890   if (e->rank == 0 || e->shape != NULL)
4891     return;
4892
4893   for (i = 0; i < e->rank; i++)
4894     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4895       goto fail;
4896
4897   e->shape = gfc_get_shape (e->rank);
4898
4899   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4900
4901   return;
4902
4903 fail:
4904   for (i--; i >= 0; i--)
4905     mpz_clear (array[i]);
4906 }
4907
4908
4909 /* Given a variable expression node, compute the rank of the expression by
4910    examining the base symbol and any reference structures it may have.  */
4911
4912 static void
4913 expression_rank (gfc_expr *e)
4914 {
4915   gfc_ref *ref;
4916   int i, rank;
4917
4918   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4919      could lead to serious confusion...  */
4920   gcc_assert (e->expr_type != EXPR_COMPCALL);
4921
4922   if (e->ref == NULL)
4923     {
4924       if (e->expr_type == EXPR_ARRAY)
4925         goto done;
4926       /* Constructors can have a rank different from one via RESHAPE().  */
4927
4928       if (e->symtree == NULL)
4929         {
4930           e->rank = 0;
4931           goto done;
4932         }
4933
4934       e->rank = (e->symtree->n.sym->as == NULL)
4935                 ? 0 : e->symtree->n.sym->as->rank;
4936       goto done;
4937     }
4938
4939   rank = 0;
4940
4941   for (ref = e->ref; ref; ref = ref->next)
4942     {
4943       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.proc_pointer
4944           && ref->u.c.component->attr.function && !ref->next)
4945         rank = ref->u.c.component->as ? ref->u.c.component->as->rank : 0;
4946
4947       if (ref->type != REF_ARRAY)
4948         continue;
4949
4950       if (ref->u.ar.type == AR_FULL)
4951         {
4952           rank = ref->u.ar.as->rank;
4953           break;
4954         }
4955
4956       if (ref->u.ar.type == AR_SECTION)
4957         {
4958           /* Figure out the rank of the section.  */
4959           if (rank != 0)
4960             gfc_internal_error ("expression_rank(): Two array specs");
4961
4962           for (i = 0; i < ref->u.ar.dimen; i++)
4963             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4964                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4965               rank++;
4966
4967           break;
4968         }
4969     }
4970
4971   e->rank = rank;
4972
4973 done:
4974   expression_shape (e);
4975 }
4976
4977
4978 /* Resolve a variable expression.  */
4979
4980 static gfc_try
4981 resolve_variable (gfc_expr *e)
4982 {
4983   gfc_symbol *sym;
4984   gfc_try t;
4985
4986   t = SUCCESS;
4987
4988   if (e->symtree == NULL)
4989     return FAILURE;
4990   sym = e->symtree->n.sym;
4991
4992   /* If this is an associate-name, it may be parsed with an array reference
4993      in error even though the target is scalar.  Fail directly in this case.  */
4994   if (sym->assoc && !sym->attr.dimension && e->ref && e->ref->type == REF_ARRAY)
4995     return FAILURE;
4996
4997   /* On the other hand, the parser may not have known this is an array;
4998      in this case, we have to add a FULL reference.  */
4999   if (sym->assoc && sym->attr.dimension && !e->ref)
5000     {
5001       e->ref = gfc_get_ref ();
5002       e->ref->type = REF_ARRAY;
5003       e->ref->u.ar.type = AR_FULL;
5004       e->ref->u.ar.dimen = 0;
5005     }
5006
5007   if (e->ref && resolve_ref (e) == FAILURE)
5008     return FAILURE;
5009
5010   if (sym->attr.flavor == FL_PROCEDURE
5011       && (!sym->attr.function
5012           || (sym->attr.function && sym->result
5013               && sym->result->attr.proc_pointer
5014               && !sym->result->attr.function)))
5015     {
5016       e->ts.type = BT_PROCEDURE;
5017       goto resolve_procedure;
5018     }
5019
5020   if (sym->ts.type != BT_UNKNOWN)
5021     gfc_variable_attr (e, &e->ts);
5022   else
5023     {
5024       /* Must be a simple variable reference.  */
5025       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
5026         return FAILURE;
5027       e->ts = sym->ts;
5028     }
5029
5030   if (check_assumed_size_reference (sym, e))
5031     return FAILURE;
5032
5033   /* Deal with forward references to entries during resolve_code, to
5034      satisfy, at least partially, 12.5.2.5.  */
5035   if (gfc_current_ns->entries
5036       && current_entry_id == sym->entry_id
5037       && cs_base
5038       && cs_base->current
5039       && cs_base->current->op != EXEC_ENTRY)
5040     {
5041       gfc_entry_list *entry;
5042       gfc_formal_arglist *formal;
5043       int n;
5044       bool seen;
5045
5046       /* If the symbol is a dummy...  */
5047       if (sym->attr.dummy && sym->ns == gfc_current_ns)
5048         {
5049           entry = gfc_current_ns->entries;
5050           seen = false;
5051
5052           /* ...test if the symbol is a parameter of previous entries.  */
5053           for (; entry && entry->id <= current_entry_id; entry = entry->next)
5054             for (formal = entry->sym->formal; formal; formal = formal->next)
5055               {
5056                 if (formal->sym && sym->name == formal->sym->name)
5057                   seen = true;
5058               }
5059
5060           /*  If it has not been seen as a dummy, this is an error.  */
5061           if (!seen)
5062             {
5063               if (specification_expr)
5064                 gfc_error ("Variable '%s', used in a specification expression"
5065                            ", is referenced at %L before the ENTRY statement "
5066                            "in which it is a parameter",
5067                            sym->name, &cs_base->current->loc);
5068               else
5069                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
5070                            "statement in which it is a parameter",
5071                            sym->name, &cs_base->current->loc);
5072               t = FAILURE;
5073             }
5074         }
5075
5076       /* Now do the same check on the specification expressions.  */
5077       specification_expr = 1;
5078       if (sym->ts.type == BT_CHARACTER
5079           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
5080         t = FAILURE;
5081
5082       if (sym->as)
5083         for (n = 0; n < sym->as->rank; n++)
5084           {
5085              specification_expr = 1;
5086              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
5087                t = FAILURE;
5088              specification_expr = 1;
5089              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
5090                t = FAILURE;
5091           }
5092       specification_expr = 0;
5093
5094       if (t == SUCCESS)
5095         /* Update the symbol's entry level.  */
5096         sym->entry_id = current_entry_id + 1;
5097     }
5098
5099   /* If a symbol has been host_associated mark it.  This is used latter,
5100      to identify if aliasing is possible via host association.  */
5101   if (sym->attr.flavor == FL_VARIABLE
5102         && gfc_current_ns->parent
5103         && (gfc_current_ns->parent == sym->ns
5104               || (gfc_current_ns->parent->parent
5105                     && gfc_current_ns->parent->parent == sym->ns)))
5106     sym->attr.host_assoc = 1;
5107
5108 resolve_procedure:
5109   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
5110     t = FAILURE;
5111
5112   /* F2008, C617 and C1229.  */
5113   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5114       && gfc_is_coindexed (e))
5115     {
5116       gfc_ref *ref, *ref2 = NULL;
5117
5118       for (ref = e->ref; ref; ref = ref->next)
5119         {
5120           if (ref->type == REF_COMPONENT)
5121             ref2 = ref;
5122           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5123             break;
5124         }
5125
5126       for ( ; ref; ref = ref->next)
5127         if (ref->type == REF_COMPONENT)
5128           break;
5129
5130       /* Expression itself is not coindexed object.  */
5131       if (ref && e->ts.type == BT_CLASS)
5132         {
5133           gfc_error ("Polymorphic subobject of coindexed object at %L",
5134                      &e->where);
5135           t = FAILURE;
5136         }
5137
5138       /* Expression itself is coindexed object.  */
5139       if (ref == NULL)
5140         {
5141           gfc_component *c;
5142           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5143           for ( ; c; c = c->next)
5144             if (c->attr.allocatable && c->ts.type == BT_CLASS)
5145               {
5146                 gfc_error ("Coindexed object with polymorphic allocatable "
5147                          "subcomponent at %L", &e->where);
5148                 t = FAILURE;
5149                 break;
5150               }
5151         }
5152     }
5153
5154   return t;
5155 }
5156
5157
5158 /* Checks to see that the correct symbol has been host associated.
5159    The only situation where this arises is that in which a twice
5160    contained function is parsed after the host association is made.
5161    Therefore, on detecting this, change the symbol in the expression
5162    and convert the array reference into an actual arglist if the old
5163    symbol is a variable.  */
5164 static bool
5165 check_host_association (gfc_expr *e)
5166 {
5167   gfc_symbol *sym, *old_sym;
5168   gfc_symtree *st;
5169   int n;
5170   gfc_ref *ref;
5171   gfc_actual_arglist *arg, *tail = NULL;
5172   bool retval = e->expr_type == EXPR_FUNCTION;
5173
5174   /*  If the expression is the result of substitution in
5175       interface.c(gfc_extend_expr) because there is no way in
5176       which the host association can be wrong.  */
5177   if (e->symtree == NULL
5178         || e->symtree->n.sym == NULL
5179         || e->user_operator)
5180     return retval;
5181
5182   old_sym = e->symtree->n.sym;
5183
5184   if (gfc_current_ns->parent
5185         && old_sym->ns != gfc_current_ns)
5186     {
5187       /* Use the 'USE' name so that renamed module symbols are
5188          correctly handled.  */
5189       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5190
5191       if (sym && old_sym != sym
5192               && sym->ts.type == old_sym->ts.type
5193               && sym->attr.flavor == FL_PROCEDURE
5194               && sym->attr.contained)
5195         {
5196           /* Clear the shape, since it might not be valid.  */
5197           if (e->shape != NULL)
5198             {
5199               for (n = 0; n < e->rank; n++)
5200                 mpz_clear (e->shape[n]);
5201
5202               free (e->shape);
5203             }
5204
5205           /* Give the expression the right symtree!  */
5206           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5207           gcc_assert (st != NULL);
5208
5209           if (old_sym->attr.flavor == FL_PROCEDURE
5210                 || e->expr_type == EXPR_FUNCTION)
5211             {
5212               /* Original was function so point to the new symbol, since
5213                  the actual argument list is already attached to the
5214                  expression. */
5215               e->value.function.esym = NULL;
5216               e->symtree = st;
5217             }
5218           else
5219             {
5220               /* Original was variable so convert array references into
5221                  an actual arglist. This does not need any checking now
5222                  since gfc_resolve_function will take care of it.  */
5223               e->value.function.actual = NULL;
5224               e->expr_type = EXPR_FUNCTION;
5225               e->symtree = st;
5226
5227               /* Ambiguity will not arise if the array reference is not
5228                  the last reference.  */
5229               for (ref = e->ref; ref; ref = ref->next)
5230                 if (ref->type == REF_ARRAY && ref->next == NULL)
5231                   break;
5232
5233               gcc_assert (ref->type == REF_ARRAY);
5234
5235               /* Grab the start expressions from the array ref and
5236                  copy them into actual arguments.  */
5237               for (n = 0; n < ref->u.ar.dimen; n++)
5238                 {
5239                   arg = gfc_get_actual_arglist ();
5240                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5241                   if (e->value.function.actual == NULL)
5242                     tail = e->value.function.actual = arg;
5243                   else
5244                     {
5245                       tail->next = arg;
5246                       tail = arg;
5247                     }
5248                 }
5249
5250               /* Dump the reference list and set the rank.  */
5251               gfc_free_ref_list (e->ref);
5252               e->ref = NULL;
5253               e->rank = sym->as ? sym->as->rank : 0;
5254             }
5255
5256           gfc_resolve_expr (e);
5257           sym->refs++;
5258         }
5259     }
5260   /* This might have changed!  */
5261   return e->expr_type == EXPR_FUNCTION;
5262 }
5263
5264
5265 static void
5266 gfc_resolve_character_operator (gfc_expr *e)
5267 {
5268   gfc_expr *op1 = e->value.op.op1;
5269   gfc_expr *op2 = e->value.op.op2;
5270   gfc_expr *e1 = NULL;
5271   gfc_expr *e2 = NULL;
5272
5273   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5274
5275   if (op1->ts.u.cl && op1->ts.u.cl->length)
5276     e1 = gfc_copy_expr (op1->ts.u.cl->length);
5277   else if (op1->expr_type == EXPR_CONSTANT)
5278     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5279                            op1->value.character.length);
5280
5281   if (op2->ts.u.cl && op2->ts.u.cl->length)
5282     e2 = gfc_copy_expr (op2->ts.u.cl->length);
5283   else if (op2->expr_type == EXPR_CONSTANT)
5284     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5285                            op2->value.character.length);
5286
5287   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5288
5289   if (!e1 || !e2)
5290     return;
5291
5292   e->ts.u.cl->length = gfc_add (e1, e2);
5293   e->ts.u.cl->length->ts.type = BT_INTEGER;
5294   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5295   gfc_simplify_expr (e->ts.u.cl->length, 0);
5296   gfc_resolve_expr (e->ts.u.cl->length);
5297
5298   return;
5299 }
5300
5301
5302 /*  Ensure that an character expression has a charlen and, if possible, a
5303     length expression.  */
5304
5305 static void
5306 fixup_charlen (gfc_expr *e)
5307 {
5308   /* The cases fall through so that changes in expression type and the need
5309      for multiple fixes are picked up.  In all circumstances, a charlen should
5310      be available for the middle end to hang a backend_decl on.  */
5311   switch (e->expr_type)
5312     {
5313     case EXPR_OP:
5314       gfc_resolve_character_operator (e);
5315
5316     case EXPR_ARRAY:
5317       if (e->expr_type == EXPR_ARRAY)
5318         gfc_resolve_character_array_constructor (e);
5319
5320     case EXPR_SUBSTRING:
5321       if (!e->ts.u.cl && e->ref)
5322         gfc_resolve_substring_charlen (e);
5323
5324     default:
5325       if (!e->ts.u.cl)
5326         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5327
5328       break;
5329     }
5330 }
5331
5332
5333 /* Update an actual argument to include the passed-object for type-bound
5334    procedures at the right position.  */
5335
5336 static gfc_actual_arglist*
5337 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5338                      const char *name)
5339 {
5340   gcc_assert (argpos > 0);
5341
5342   if (argpos == 1)
5343     {
5344       gfc_actual_arglist* result;
5345
5346       result = gfc_get_actual_arglist ();
5347       result->expr = po;
5348       result->next = lst;
5349       if (name)
5350         result->name = name;
5351
5352       return result;
5353     }
5354
5355   if (lst)
5356     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5357   else
5358     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5359   return lst;
5360 }
5361
5362
5363 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5364
5365 static gfc_expr*
5366 extract_compcall_passed_object (gfc_expr* e)
5367 {
5368   gfc_expr* po;
5369
5370   gcc_assert (e->expr_type == EXPR_COMPCALL);
5371
5372   if (e->value.compcall.base_object)
5373     po = gfc_copy_expr (e->value.compcall.base_object);
5374   else
5375     {
5376       po = gfc_get_expr ();
5377       po->expr_type = EXPR_VARIABLE;
5378       po->symtree = e->symtree;
5379       po->ref = gfc_copy_ref (e->ref);
5380       po->where = e->where;
5381     }
5382
5383   if (gfc_resolve_expr (po) == FAILURE)
5384     return NULL;
5385
5386   return po;
5387 }
5388
5389
5390 /* Update the arglist of an EXPR_COMPCALL expression to include the
5391    passed-object.  */
5392
5393 static gfc_try
5394 update_compcall_arglist (gfc_expr* e)
5395 {
5396   gfc_expr* po;
5397   gfc_typebound_proc* tbp;
5398
5399   tbp = e->value.compcall.tbp;
5400
5401   if (tbp->error)
5402     return FAILURE;
5403
5404   po = extract_compcall_passed_object (e);
5405   if (!po)
5406     return FAILURE;
5407
5408   if (tbp->nopass || e->value.compcall.ignore_pass)
5409     {
5410       gfc_free_expr (po);
5411       return SUCCESS;
5412     }
5413
5414   gcc_assert (tbp->pass_arg_num > 0);
5415   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5416                                                   tbp->pass_arg_num,
5417                                                   tbp->pass_arg);
5418
5419   return SUCCESS;
5420 }
5421
5422
5423 /* Extract the passed object from a PPC call (a copy of it).  */
5424
5425 static gfc_expr*
5426 extract_ppc_passed_object (gfc_expr *e)
5427 {
5428   gfc_expr *po;
5429   gfc_ref **ref;
5430
5431   po = gfc_get_expr ();
5432   po->expr_type = EXPR_VARIABLE;
5433   po->symtree = e->symtree;
5434   po->ref = gfc_copy_ref (e->ref);
5435   po->where = e->where;
5436
5437   /* Remove PPC reference.  */
5438   ref = &po->ref;
5439   while ((*ref)->next)
5440     ref = &(*ref)->next;
5441   gfc_free_ref_list (*ref);
5442   *ref = NULL;
5443
5444   if (gfc_resolve_expr (po) == FAILURE)
5445     return NULL;
5446
5447   return po;
5448 }
5449
5450
5451 /* Update the actual arglist of a procedure pointer component to include the
5452    passed-object.  */
5453
5454 static gfc_try
5455 update_ppc_arglist (gfc_expr* e)
5456 {
5457   gfc_expr* po;
5458   gfc_component *ppc;
5459   gfc_typebound_proc* tb;
5460
5461   if (!gfc_is_proc_ptr_comp (e, &ppc))
5462     return FAILURE;
5463
5464   tb = ppc->tb;
5465
5466   if (tb->error)
5467     return FAILURE;
5468   else if (tb->nopass)
5469     return SUCCESS;
5470
5471   po = extract_ppc_passed_object (e);
5472   if (!po)
5473     return FAILURE;
5474
5475   /* F08:R739.  */
5476   if (po->rank > 0)
5477     {
5478       gfc_error ("Passed-object at %L must be scalar", &e->where);
5479       return FAILURE;
5480     }
5481
5482   /* F08:C611.  */
5483   if (po->ts.type == BT_DERIVED && po->ts.u.derived->attr.abstract)
5484     {
5485       gfc_error ("Base object for procedure-pointer component call at %L is of"
5486                  " ABSTRACT type '%s'", &e->where, po->ts.u.derived->name);
5487       return FAILURE;
5488     }
5489
5490   gcc_assert (tb->pass_arg_num > 0);
5491   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5492                                                   tb->pass_arg_num,
5493                                                   tb->pass_arg);
5494
5495   return SUCCESS;
5496 }
5497
5498
5499 /* Check that the object a TBP is called on is valid, i.e. it must not be
5500    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5501
5502 static gfc_try
5503 check_typebound_baseobject (gfc_expr* e)
5504 {
5505   gfc_expr* base;
5506   gfc_try return_value = FAILURE;
5507
5508   base = extract_compcall_passed_object (e);
5509   if (!base)
5510     return FAILURE;
5511
5512   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5513
5514   /* F08:C611.  */
5515   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5516     {
5517       gfc_error ("Base object for type-bound procedure call at %L is of"
5518                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5519       goto cleanup;
5520     }
5521
5522   /* F08:C1230. If the procedure called is NOPASS,
5523      the base object must be scalar.  */
5524   if (e->value.compcall.tbp->nopass && base->rank > 0)
5525     {
5526       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5527                  " be scalar", &e->where);
5528       goto cleanup;
5529     }
5530
5531   /* FIXME: Remove once PR 43214 is fixed (TBP with non-scalar PASS).  */
5532   if (base->rank > 0)
5533     {
5534       gfc_error ("Non-scalar base object at %L currently not implemented",
5535                  &e->where);
5536       goto cleanup;
5537     }
5538
5539   return_value = SUCCESS;
5540
5541 cleanup:
5542   gfc_free_expr (base);
5543   return return_value;
5544 }
5545
5546
5547 /* Resolve a call to a type-bound procedure, either function or subroutine,
5548    statically from the data in an EXPR_COMPCALL expression.  The adapted
5549    arglist and the target-procedure symtree are returned.  */
5550
5551 static gfc_try
5552 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5553                           gfc_actual_arglist** actual)
5554 {
5555   gcc_assert (e->expr_type == EXPR_COMPCALL);
5556   gcc_assert (!e->value.compcall.tbp->is_generic);
5557
5558   /* Update the actual arglist for PASS.  */
5559   if (update_compcall_arglist (e) == FAILURE)
5560     return FAILURE;
5561
5562   *actual = e->value.compcall.actual;
5563   *target = e->value.compcall.tbp->u.specific;
5564
5565   gfc_free_ref_list (e->ref);
5566   e->ref = NULL;
5567   e->value.compcall.actual = NULL;
5568
5569   return SUCCESS;
5570 }
5571
5572
5573 /* Get the ultimate declared type from an expression.  In addition,
5574    return the last class/derived type reference and the copy of the
5575    reference list.  */
5576 static gfc_symbol*
5577 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5578                         gfc_expr *e)
5579 {
5580   gfc_symbol *declared;
5581   gfc_ref *ref;
5582
5583   declared = NULL;
5584   if (class_ref)
5585     *class_ref = NULL;
5586   if (new_ref)
5587     *new_ref = gfc_copy_ref (e->ref);
5588
5589   for (ref = e->ref; ref; ref = ref->next)
5590     {
5591       if (ref->type != REF_COMPONENT)
5592         continue;
5593
5594       if (ref->u.c.component->ts.type == BT_CLASS
5595             || ref->u.c.component->ts.type == BT_DERIVED)
5596         {
5597           declared = ref->u.c.component->ts.u.derived;
5598           if (class_ref)
5599             *class_ref = ref;
5600         }
5601     }
5602
5603   if (declared == NULL)
5604     declared = e->symtree->n.sym->ts.u.derived;
5605
5606   return declared;
5607 }
5608
5609
5610 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5611    which of the specific bindings (if any) matches the arglist and transform
5612    the expression into a call of that binding.  */
5613
5614 static gfc_try
5615 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5616 {
5617   gfc_typebound_proc* genproc;
5618   const char* genname;
5619   gfc_symtree *st;
5620   gfc_symbol *derived;
5621
5622   gcc_assert (e->expr_type == EXPR_COMPCALL);
5623   genname = e->value.compcall.name;
5624   genproc = e->value.compcall.tbp;
5625
5626   if (!genproc->is_generic)
5627     return SUCCESS;
5628
5629   /* Try the bindings on this type and in the inheritance hierarchy.  */
5630   for (; genproc; genproc = genproc->overridden)
5631     {
5632       gfc_tbp_generic* g;
5633
5634       gcc_assert (genproc->is_generic);
5635       for (g = genproc->u.generic; g; g = g->next)
5636         {
5637           gfc_symbol* target;
5638           gfc_actual_arglist* args;
5639           bool matches;
5640
5641           gcc_assert (g->specific);
5642
5643           if (g->specific->error)
5644             continue;
5645
5646           target = g->specific->u.specific->n.sym;
5647
5648           /* Get the right arglist by handling PASS/NOPASS.  */
5649           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5650           if (!g->specific->nopass)
5651             {
5652               gfc_expr* po;
5653               po = extract_compcall_passed_object (e);
5654               if (!po)
5655                 return FAILURE;
5656
5657               gcc_assert (g->specific->pass_arg_num > 0);
5658               gcc_assert (!g->specific->error);
5659               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5660                                           g->specific->pass_arg);
5661             }
5662           resolve_actual_arglist (args, target->attr.proc,
5663                                   is_external_proc (target) && !target->formal);
5664
5665           /* Check if this arglist matches the formal.  */
5666           matches = gfc_arglist_matches_symbol (&args, target);
5667
5668           /* Clean up and break out of the loop if we've found it.  */
5669           gfc_free_actual_arglist (args);
5670           if (matches)
5671             {
5672               e->value.compcall.tbp = g->specific;
5673               genname = g->specific_st->name;
5674               /* Pass along the name for CLASS methods, where the vtab
5675                  procedure pointer component has to be referenced.  */
5676               if (name)
5677                 *name = genname;
5678               goto success;
5679             }
5680         }
5681     }
5682
5683   /* Nothing matching found!  */
5684   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5685              " '%s' at %L", genname, &e->where);
5686   return FAILURE;
5687
5688 success:
5689   /* Make sure that we have the right specific instance for the name.  */
5690   derived = get_declared_from_expr (NULL, NULL, e);
5691
5692   st = gfc_find_typebound_proc (derived, NULL, genname, true, &e->where);
5693   if (st)
5694     e->value.compcall.tbp = st->n.tb;
5695
5696   return SUCCESS;
5697 }
5698
5699
5700 /* Resolve a call to a type-bound subroutine.  */
5701
5702 static gfc_try
5703 resolve_typebound_call (gfc_code* c, const char **name)
5704 {
5705   gfc_actual_arglist* newactual;
5706   gfc_symtree* target;
5707
5708   /* Check that's really a SUBROUTINE.  */
5709   if (!c->expr1->value.compcall.tbp->subroutine)
5710     {
5711       gfc_error ("'%s' at %L should be a SUBROUTINE",
5712                  c->expr1->value.compcall.name, &c->loc);
5713       return FAILURE;
5714     }
5715
5716   if (check_typebound_baseobject (c->expr1) == FAILURE)
5717     return FAILURE;
5718
5719   /* Pass along the name for CLASS methods, where the vtab
5720      procedure pointer component has to be referenced.  */
5721   if (name)
5722     *name = c->expr1->value.compcall.name;
5723
5724   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5725     return FAILURE;
5726
5727   /* Transform into an ordinary EXEC_CALL for now.  */
5728
5729   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5730     return FAILURE;
5731
5732   c->ext.actual = newactual;
5733   c->symtree = target;
5734   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5735
5736   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5737
5738   gfc_free_expr (c->expr1);
5739   c->expr1 = gfc_get_expr ();
5740   c->expr1->expr_type = EXPR_FUNCTION;
5741   c->expr1->symtree = target;
5742   c->expr1->where = c->loc;
5743
5744   return resolve_call (c);
5745 }
5746
5747
5748 /* Resolve a component-call expression.  */
5749 static gfc_try
5750 resolve_compcall (gfc_expr* e, const char **name)
5751 {
5752   gfc_actual_arglist* newactual;
5753   gfc_symtree* target;
5754
5755   /* Check that's really a FUNCTION.  */
5756   if (!e->value.compcall.tbp->function)
5757     {
5758       gfc_error ("'%s' at %L should be a FUNCTION",
5759                  e->value.compcall.name, &e->where);
5760       return FAILURE;
5761     }
5762
5763   /* These must not be assign-calls!  */
5764   gcc_assert (!e->value.compcall.assign);
5765
5766   if (check_typebound_baseobject (e) == FAILURE)
5767     return FAILURE;
5768
5769   /* Pass along the name for CLASS methods, where the vtab
5770      procedure pointer component has to be referenced.  */
5771   if (name)
5772     *name = e->value.compcall.name;
5773
5774   if (resolve_typebound_generic_call (e, name) == FAILURE)
5775     return FAILURE;
5776   gcc_assert (!e->value.compcall.tbp->is_generic);
5777
5778   /* Take the rank from the function's symbol.  */
5779   if (e->value.compcall.tbp->u.specific->n.sym->as)
5780     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5781
5782   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5783      arglist to the TBP's binding target.  */
5784
5785   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5786     return FAILURE;
5787
5788   e->value.function.actual = newactual;
5789   e->value.function.name = NULL;
5790   e->value.function.esym = target->n.sym;
5791   e->value.function.isym = NULL;
5792   e->symtree = target;
5793   e->ts = target->n.sym->ts;
5794   e->expr_type = EXPR_FUNCTION;
5795
5796   /* Resolution is not necessary if this is a class subroutine; this
5797      function only has to identify the specific proc. Resolution of
5798      the call will be done next in resolve_typebound_call.  */
5799   return gfc_resolve_expr (e);
5800 }
5801
5802
5803
5804 /* Resolve a typebound function, or 'method'. First separate all
5805    the non-CLASS references by calling resolve_compcall directly.  */
5806
5807 static gfc_try
5808 resolve_typebound_function (gfc_expr* e)
5809 {
5810   gfc_symbol *declared;
5811   gfc_component *c;
5812   gfc_ref *new_ref;
5813   gfc_ref *class_ref;
5814   gfc_symtree *st;
5815   const char *name;
5816   gfc_typespec ts;
5817   gfc_expr *expr;
5818
5819   st = e->symtree;
5820
5821   /* Deal with typebound operators for CLASS objects.  */
5822   expr = e->value.compcall.base_object;
5823   if (expr && expr->ts.type == BT_CLASS && e->value.compcall.name)
5824     {
5825       /* Since the typebound operators are generic, we have to ensure
5826          that any delays in resolution are corrected and that the vtab
5827          is present.  */
5828       ts = expr->ts;
5829       declared = ts.u.derived;
5830       c = gfc_find_component (declared, "_vptr", true, true);
5831       if (c->ts.u.derived == NULL)
5832         c->ts.u.derived = gfc_find_derived_vtab (declared);
5833
5834       if (resolve_compcall (e, &name) == FAILURE)
5835         return FAILURE;
5836
5837       /* Use the generic name if it is there.  */
5838       name = name ? name : e->value.function.esym->name;
5839       e->symtree = expr->symtree;
5840       e->ref = gfc_copy_ref (expr->ref);
5841       gfc_add_vptr_component (e);
5842       gfc_add_component_ref (e, name);
5843       e->value.function.esym = NULL;
5844       return SUCCESS;
5845     }
5846
5847   if (st == NULL)
5848     return resolve_compcall (e, NULL);
5849
5850   if (resolve_ref (e) == FAILURE)
5851     return FAILURE;
5852
5853   /* Get the CLASS declared type.  */
5854   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5855
5856   /* Weed out cases of the ultimate component being a derived type.  */
5857   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5858          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5859     {
5860       gfc_free_ref_list (new_ref);
5861       return resolve_compcall (e, NULL);
5862     }
5863
5864   c = gfc_find_component (declared, "_data", true, true);
5865   declared = c->ts.u.derived;
5866
5867   /* Treat the call as if it is a typebound procedure, in order to roll
5868      out the correct name for the specific function.  */
5869   if (resolve_compcall (e, &name) == FAILURE)
5870     return FAILURE;
5871   ts = e->ts;
5872
5873   /* Then convert the expression to a procedure pointer component call.  */
5874   e->value.function.esym = NULL;
5875   e->symtree = st;
5876
5877   if (new_ref)  
5878     e->ref = new_ref;
5879
5880   /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5881   gfc_add_vptr_component (e);
5882   gfc_add_component_ref (e, name);
5883
5884   /* Recover the typespec for the expression.  This is really only
5885      necessary for generic procedures, where the additional call
5886      to gfc_add_component_ref seems to throw the collection of the
5887      correct typespec.  */
5888   e->ts = ts;
5889   return SUCCESS;
5890 }
5891
5892 /* Resolve a typebound subroutine, or 'method'. First separate all
5893    the non-CLASS references by calling resolve_typebound_call
5894    directly.  */
5895
5896 static gfc_try
5897 resolve_typebound_subroutine (gfc_code *code)
5898 {
5899   gfc_symbol *declared;
5900   gfc_component *c;
5901   gfc_ref *new_ref;
5902   gfc_ref *class_ref;
5903   gfc_symtree *st;
5904   const char *name;
5905   gfc_typespec ts;
5906   gfc_expr *expr;
5907
5908   st = code->expr1->symtree;
5909
5910   /* Deal with typebound operators for CLASS objects.  */
5911   expr = code->expr1->value.compcall.base_object;
5912   if (expr && expr->ts.type == BT_CLASS && code->expr1->value.compcall.name)
5913     {
5914       /* Since the typebound operators are generic, we have to ensure
5915          that any delays in resolution are corrected and that the vtab
5916          is present.  */
5917       declared = expr->ts.u.derived;
5918       c = gfc_find_component (declared, "_vptr", true, true);
5919       if (c->ts.u.derived == NULL)
5920         c->ts.u.derived = gfc_find_derived_vtab (declared);
5921
5922       if (resolve_typebound_call (code, &name) == FAILURE)
5923         return FAILURE;
5924
5925       /* Use the generic name if it is there.  */
5926       name = name ? name : code->expr1->value.function.esym->name;
5927       code->expr1->symtree = expr->symtree;
5928       code->expr1->ref = gfc_copy_ref (expr->ref);
5929       gfc_add_vptr_component (code->expr1);
5930       gfc_add_component_ref (code->expr1, name);
5931       code->expr1->value.function.esym = NULL;
5932       return SUCCESS;
5933     }
5934
5935   if (st == NULL)
5936     return resolve_typebound_call (code, NULL);
5937
5938   if (resolve_ref (code->expr1) == FAILURE)
5939     return FAILURE;
5940
5941   /* Get the CLASS declared type.  */
5942   get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5943
5944   /* Weed out cases of the ultimate component being a derived type.  */
5945   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5946          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5947     {
5948       gfc_free_ref_list (new_ref);
5949       return resolve_typebound_call (code, NULL);
5950     }
5951
5952   if (resolve_typebound_call (code, &name) == FAILURE)
5953     return FAILURE;
5954   ts = code->expr1->ts;
5955
5956   /* Then convert the expression to a procedure pointer component call.  */
5957   code->expr1->value.function.esym = NULL;
5958   code->expr1->symtree = st;
5959
5960   if (new_ref)
5961     code->expr1->ref = new_ref;
5962
5963   /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5964   gfc_add_vptr_component (code->expr1);
5965   gfc_add_component_ref (code->expr1, name);
5966
5967   /* Recover the typespec for the expression.  This is really only
5968      necessary for generic procedures, where the additional call
5969      to gfc_add_component_ref seems to throw the collection of the
5970      correct typespec.  */
5971   code->expr1->ts = ts;
5972   return SUCCESS;
5973 }
5974
5975
5976 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5977
5978 static gfc_try
5979 resolve_ppc_call (gfc_code* c)
5980 {
5981   gfc_component *comp;
5982   bool b;
5983
5984   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5985   gcc_assert (b);
5986
5987   c->resolved_sym = c->expr1->symtree->n.sym;
5988   c->expr1->expr_type = EXPR_VARIABLE;
5989
5990   if (!comp->attr.subroutine)
5991     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5992
5993   if (resolve_ref (c->expr1) == FAILURE)
5994     return FAILURE;
5995
5996   if (update_ppc_arglist (c->expr1) == FAILURE)
5997     return FAILURE;
5998
5999   c->ext.actual = c->expr1->value.compcall.actual;
6000
6001   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
6002                               comp->formal == NULL) == FAILURE)
6003     return FAILURE;
6004
6005   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
6006
6007   return SUCCESS;
6008 }
6009
6010
6011 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
6012
6013 static gfc_try
6014 resolve_expr_ppc (gfc_expr* e)
6015 {
6016   gfc_component *comp;
6017   bool b;
6018
6019   b = gfc_is_proc_ptr_comp (e, &comp);
6020   gcc_assert (b);
6021
6022   /* Convert to EXPR_FUNCTION.  */
6023   e->expr_type = EXPR_FUNCTION;
6024   e->value.function.isym = NULL;
6025   e->value.function.actual = e->value.compcall.actual;
6026   e->ts = comp->ts;
6027   if (comp->as != NULL)
6028     e->rank = comp->as->rank;
6029
6030   if (!comp->attr.function)
6031     gfc_add_function (&comp->attr, comp->name, &e->where);
6032
6033   if (resolve_ref (e) == FAILURE)
6034     return FAILURE;
6035
6036   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
6037                               comp->formal == NULL) == FAILURE)
6038     return FAILURE;
6039
6040   if (update_ppc_arglist (e) == FAILURE)
6041     return FAILURE;
6042
6043   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
6044
6045   return SUCCESS;
6046 }
6047
6048
6049 static bool
6050 gfc_is_expandable_expr (gfc_expr *e)
6051 {
6052   gfc_constructor *con;
6053
6054   if (e->expr_type == EXPR_ARRAY)
6055     {
6056       /* Traverse the constructor looking for variables that are flavor
6057          parameter.  Parameters must be expanded since they are fully used at
6058          compile time.  */
6059       con = gfc_constructor_first (e->value.constructor);
6060       for (; con; con = gfc_constructor_next (con))
6061         {
6062           if (con->expr->expr_type == EXPR_VARIABLE
6063               && con->expr->symtree
6064               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
6065               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
6066             return true;
6067           if (con->expr->expr_type == EXPR_ARRAY
6068               && gfc_is_expandable_expr (con->expr))
6069             return true;
6070         }
6071     }
6072
6073   return false;
6074 }
6075
6076 /* Resolve an expression.  That is, make sure that types of operands agree
6077    with their operators, intrinsic operators are converted to function calls
6078    for overloaded types and unresolved function references are resolved.  */
6079
6080 gfc_try
6081 gfc_resolve_expr (gfc_expr *e)
6082 {
6083   gfc_try t;
6084   bool inquiry_save;
6085
6086   if (e == NULL)
6087     return SUCCESS;
6088
6089   /* inquiry_argument only applies to variables.  */
6090   inquiry_save = inquiry_argument;
6091   if (e->expr_type != EXPR_VARIABLE)
6092     inquiry_argument = false;
6093
6094   switch (e->expr_type)
6095     {
6096     case EXPR_OP:
6097       t = resolve_operator (e);
6098       break;
6099
6100     case EXPR_FUNCTION:
6101     case EXPR_VARIABLE:
6102
6103       if (check_host_association (e))
6104         t = resolve_function (e);
6105       else
6106         {
6107           t = resolve_variable (e);
6108           if (t == SUCCESS)
6109             expression_rank (e);
6110         }
6111
6112       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6113           && e->ref->type != REF_SUBSTRING)
6114         gfc_resolve_substring_charlen (e);
6115
6116       break;
6117
6118     case EXPR_COMPCALL:
6119       t = resolve_typebound_function (e);
6120       break;
6121
6122     case EXPR_SUBSTRING:
6123       t = resolve_ref (e);
6124       break;
6125
6126     case EXPR_CONSTANT:
6127     case EXPR_NULL:
6128       t = SUCCESS;
6129       break;
6130
6131     case EXPR_PPC:
6132       t = resolve_expr_ppc (e);
6133       break;
6134
6135     case EXPR_ARRAY:
6136       t = FAILURE;
6137       if (resolve_ref (e) == FAILURE)
6138         break;
6139
6140       t = gfc_resolve_array_constructor (e);
6141       /* Also try to expand a constructor.  */
6142       if (t == SUCCESS)
6143         {
6144           expression_rank (e);
6145           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6146             gfc_expand_constructor (e, false);
6147         }
6148
6149       /* This provides the opportunity for the length of constructors with
6150          character valued function elements to propagate the string length
6151          to the expression.  */
6152       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
6153         {
6154           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6155              here rather then add a duplicate test for it above.  */ 
6156           gfc_expand_constructor (e, false);
6157           t = gfc_resolve_character_array_constructor (e);
6158         }
6159
6160       break;
6161
6162     case EXPR_STRUCTURE:
6163       t = resolve_ref (e);
6164       if (t == FAILURE)
6165         break;
6166
6167       t = resolve_structure_cons (e, 0);
6168       if (t == FAILURE)
6169         break;
6170
6171       t = gfc_simplify_expr (e, 0);
6172       break;
6173
6174     default:
6175       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6176     }
6177
6178   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
6179     fixup_charlen (e);
6180
6181   inquiry_argument = inquiry_save;
6182
6183   return t;
6184 }
6185
6186
6187 /* Resolve an expression from an iterator.  They must be scalar and have
6188    INTEGER or (optionally) REAL type.  */
6189
6190 static gfc_try
6191 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6192                            const char *name_msgid)
6193 {
6194   if (gfc_resolve_expr (expr) == FAILURE)
6195     return FAILURE;
6196
6197   if (expr->rank != 0)
6198     {
6199       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6200       return FAILURE;
6201     }
6202
6203   if (expr->ts.type != BT_INTEGER)
6204     {
6205       if (expr->ts.type == BT_REAL)
6206         {
6207           if (real_ok)
6208             return gfc_notify_std (GFC_STD_F95_DEL,
6209                                    "Deleted feature: %s at %L must be integer",
6210                                    _(name_msgid), &expr->where);
6211           else
6212             {
6213               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6214                          &expr->where);
6215               return FAILURE;
6216             }
6217         }
6218       else
6219         {
6220           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6221           return FAILURE;
6222         }
6223     }
6224   return SUCCESS;
6225 }
6226
6227
6228 /* Resolve the expressions in an iterator structure.  If REAL_OK is
6229    false allow only INTEGER type iterators, otherwise allow REAL types.  */
6230
6231 gfc_try
6232 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
6233 {
6234   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
6235       == FAILURE)
6236     return FAILURE;
6237
6238   if (gfc_check_vardef_context (iter->var, false, _("iterator variable"))
6239       == FAILURE)
6240     return FAILURE;
6241
6242   if (gfc_resolve_iterator_expr (iter->start, real_ok,
6243                                  "Start expression in DO loop") == FAILURE)
6244     return FAILURE;
6245
6246   if (gfc_resolve_iterator_expr (iter->end, real_ok,
6247                                  "End expression in DO loop") == FAILURE)
6248     return FAILURE;
6249
6250   if (gfc_resolve_iterator_expr (iter->step, real_ok,
6251                                  "Step expression in DO loop") == FAILURE)
6252     return FAILURE;
6253
6254   if (iter->step->expr_type == EXPR_CONSTANT)
6255     {
6256       if ((iter->step->ts.type == BT_INTEGER
6257            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6258           || (iter->step->ts.type == BT_REAL
6259               && mpfr_sgn (iter->step->value.real) == 0))
6260         {
6261           gfc_error ("Step expression in DO loop at %L cannot be zero",
6262                      &iter->step->where);
6263           return FAILURE;
6264         }
6265     }
6266
6267   /* Convert start, end, and step to the same type as var.  */
6268   if (iter->start->ts.kind != iter->var->ts.kind
6269       || iter->start->ts.type != iter->var->ts.type)
6270     gfc_convert_type (iter->start, &iter->var->ts, 2);
6271
6272   if (iter->end->ts.kind != iter->var->ts.kind
6273       || iter->end->ts.type != iter->var->ts.type)
6274     gfc_convert_type (iter->end, &iter->var->ts, 2);
6275
6276   if (iter->step->ts.kind != iter->var->ts.kind
6277       || iter->step->ts.type != iter->var->ts.type)
6278     gfc_convert_type (iter->step, &iter->var->ts, 2);
6279
6280   if (iter->start->expr_type == EXPR_CONSTANT
6281       && iter->end->expr_type == EXPR_CONSTANT
6282       && iter->step->expr_type == EXPR_CONSTANT)
6283     {
6284       int sgn, cmp;
6285       if (iter->start->ts.type == BT_INTEGER)
6286         {
6287           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6288           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6289         }
6290       else
6291         {
6292           sgn = mpfr_sgn (iter->step->value.real);
6293           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6294         }
6295       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
6296         gfc_warning ("DO loop at %L will be executed zero times",
6297                      &iter->step->where);
6298     }
6299
6300   return SUCCESS;
6301 }
6302
6303
6304 /* Traversal function for find_forall_index.  f == 2 signals that
6305    that variable itself is not to be checked - only the references.  */
6306
6307 static bool
6308 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6309 {
6310   if (expr->expr_type != EXPR_VARIABLE)
6311     return false;
6312   
6313   /* A scalar assignment  */
6314   if (!expr->ref || *f == 1)
6315     {
6316       if (expr->symtree->n.sym == sym)
6317         return true;
6318       else
6319         return false;
6320     }
6321
6322   if (*f == 2)
6323     *f = 1;
6324   return false;
6325 }
6326
6327
6328 /* Check whether the FORALL index appears in the expression or not.
6329    Returns SUCCESS if SYM is found in EXPR.  */
6330
6331 gfc_try
6332 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6333 {
6334   if (gfc_traverse_expr (expr, sym, forall_index, f))
6335     return SUCCESS;
6336   else
6337     return FAILURE;
6338 }
6339
6340
6341 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6342    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6343    INTEGERs, and if stride is a constant it must be nonzero.
6344    Furthermore "A subscript or stride in a forall-triplet-spec shall
6345    not contain a reference to any index-name in the
6346    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6347
6348 static void
6349 resolve_forall_iterators (gfc_forall_iterator *it)
6350 {
6351   gfc_forall_iterator *iter, *iter2;
6352
6353   for (iter = it; iter; iter = iter->next)
6354     {
6355       if (gfc_resolve_expr (iter->var) == SUCCESS
6356           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6357         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6358                    &iter->var->where);
6359
6360       if (gfc_resolve_expr (iter->start) == SUCCESS
6361           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6362         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6363                    &iter->start->where);
6364       if (iter->var->ts.kind != iter->start->ts.kind)
6365         gfc_convert_type (iter->start, &iter->var->ts, 2);
6366
6367       if (gfc_resolve_expr (iter->end) == SUCCESS
6368           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6369         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6370                    &iter->end->where);
6371       if (iter->var->ts.kind != iter->end->ts.kind)
6372         gfc_convert_type (iter->end, &iter->var->ts, 2);
6373
6374       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6375         {
6376           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6377             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6378                        &iter->stride->where, "INTEGER");
6379
6380           if (iter->stride->expr_type == EXPR_CONSTANT
6381               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6382             gfc_error ("FORALL stride expression at %L cannot be zero",
6383                        &iter->stride->where);
6384         }
6385       if (iter->var->ts.kind != iter->stride->ts.kind)
6386         gfc_convert_type (iter->stride, &iter->var->ts, 2);
6387     }
6388
6389   for (iter = it; iter; iter = iter->next)
6390     for (iter2 = iter; iter2; iter2 = iter2->next)
6391       {
6392         if (find_forall_index (iter2->start,
6393                                iter->var->symtree->n.sym, 0) == SUCCESS
6394             || find_forall_index (iter2->end,
6395                                   iter->var->symtree->n.sym, 0) == SUCCESS
6396             || find_forall_index (iter2->stride,
6397                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6398           gfc_error ("FORALL index '%s' may not appear in triplet "
6399                      "specification at %L", iter->var->symtree->name,
6400                      &iter2->start->where);
6401       }
6402 }
6403
6404
6405 /* Given a pointer to a symbol that is a derived type, see if it's
6406    inaccessible, i.e. if it's defined in another module and the components are
6407    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6408    inaccessible components are found, nonzero otherwise.  */
6409
6410 static int
6411 derived_inaccessible (gfc_symbol *sym)
6412 {
6413   gfc_component *c;
6414
6415   if (sym->attr.use_assoc && sym->attr.private_comp)
6416     return 1;
6417
6418   for (c = sym->components; c; c = c->next)
6419     {
6420         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6421           return 1;
6422     }
6423
6424   return 0;
6425 }
6426
6427
6428 /* Resolve the argument of a deallocate expression.  The expression must be
6429    a pointer or a full array.  */
6430
6431 static gfc_try
6432 resolve_deallocate_expr (gfc_expr *e)
6433 {
6434   symbol_attribute attr;
6435   int allocatable, pointer;
6436   gfc_ref *ref;
6437   gfc_symbol *sym;
6438   gfc_component *c;
6439
6440   if (gfc_resolve_expr (e) == FAILURE)
6441     return FAILURE;
6442
6443   if (e->expr_type != EXPR_VARIABLE)
6444     goto bad;
6445
6446   sym = e->symtree->n.sym;
6447
6448   if (sym->ts.type == BT_CLASS)
6449     {
6450       allocatable = CLASS_DATA (sym)->attr.allocatable;
6451       pointer = CLASS_DATA (sym)->attr.class_pointer;
6452     }
6453   else
6454     {
6455       allocatable = sym->attr.allocatable;
6456       pointer = sym->attr.pointer;
6457     }
6458   for (ref = e->ref; ref; ref = ref->next)
6459     {
6460       switch (ref->type)
6461         {
6462         case REF_ARRAY:
6463           if (ref->u.ar.type != AR_FULL)
6464             allocatable = 0;
6465           break;
6466
6467         case REF_COMPONENT:
6468           c = ref->u.c.component;
6469           if (c->ts.type == BT_CLASS)
6470             {
6471               allocatable = CLASS_DATA (c)->attr.allocatable;
6472               pointer = CLASS_DATA (c)->attr.class_pointer;
6473             }
6474           else
6475             {
6476               allocatable = c->attr.allocatable;
6477               pointer = c->attr.pointer;
6478             }
6479           break;
6480
6481         case REF_SUBSTRING:
6482           allocatable = 0;
6483           break;
6484         }
6485     }
6486
6487   attr = gfc_expr_attr (e);
6488
6489   if (allocatable == 0 && attr.pointer == 0)
6490     {
6491     bad:
6492       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6493                  &e->where);
6494       return FAILURE;
6495     }
6496
6497   /* F2008, C644.  */
6498   if (gfc_is_coindexed (e))
6499     {
6500       gfc_error ("Coindexed allocatable object at %L", &e->where);
6501       return FAILURE;
6502     }
6503
6504   if (pointer
6505       && gfc_check_vardef_context (e, true, _("DEALLOCATE object")) == FAILURE)
6506     return FAILURE;
6507   if (gfc_check_vardef_context (e, false, _("DEALLOCATE object")) == FAILURE)
6508     return FAILURE;
6509
6510   return SUCCESS;
6511 }
6512
6513
6514 /* Returns true if the expression e contains a reference to the symbol sym.  */
6515 static bool
6516 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6517 {
6518   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6519     return true;
6520
6521   return false;
6522 }
6523
6524 bool
6525 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6526 {
6527   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6528 }
6529
6530
6531 /* Given the expression node e for an allocatable/pointer of derived type to be
6532    allocated, get the expression node to be initialized afterwards (needed for
6533    derived types with default initializers, and derived types with allocatable
6534    components that need nullification.)  */
6535
6536 gfc_expr *
6537 gfc_expr_to_initialize (gfc_expr *e)
6538 {
6539   gfc_expr *result;
6540   gfc_ref *ref;
6541   int i;
6542
6543   result = gfc_copy_expr (e);
6544
6545   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6546   for (ref = result->ref; ref; ref = ref->next)
6547     if (ref->type == REF_ARRAY && ref->next == NULL)
6548       {
6549         ref->u.ar.type = AR_FULL;
6550
6551         for (i = 0; i < ref->u.ar.dimen; i++)
6552           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6553
6554         result->rank = ref->u.ar.dimen;
6555         break;
6556       }
6557
6558   return result;
6559 }
6560
6561
6562 /* If the last ref of an expression is an array ref, return a copy of the
6563    expression with that one removed.  Otherwise, a copy of the original
6564    expression.  This is used for allocate-expressions and pointer assignment
6565    LHS, where there may be an array specification that needs to be stripped
6566    off when using gfc_check_vardef_context.  */
6567
6568 static gfc_expr*
6569 remove_last_array_ref (gfc_expr* e)
6570 {
6571   gfc_expr* e2;
6572   gfc_ref** r;
6573
6574   e2 = gfc_copy_expr (e);
6575   for (r = &e2->ref; *r; r = &(*r)->next)
6576     if ((*r)->type == REF_ARRAY && !(*r)->next)
6577       {
6578         gfc_free_ref_list (*r);
6579         *r = NULL;
6580         break;
6581       }
6582
6583   return e2;
6584 }
6585
6586
6587 /* Used in resolve_allocate_expr to check that a allocation-object and
6588    a source-expr are conformable.  This does not catch all possible 
6589    cases; in particular a runtime checking is needed.  */
6590
6591 static gfc_try
6592 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6593 {
6594   gfc_ref *tail;
6595   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6596   
6597   /* First compare rank.  */
6598   if (tail && e1->rank != tail->u.ar.as->rank)
6599     {
6600       gfc_error ("Source-expr at %L must be scalar or have the "
6601                  "same rank as the allocate-object at %L",
6602                  &e1->where, &e2->where);
6603       return FAILURE;
6604     }
6605
6606   if (e1->shape)
6607     {
6608       int i;
6609       mpz_t s;
6610
6611       mpz_init (s);
6612
6613       for (i = 0; i < e1->rank; i++)
6614         {
6615           if (tail->u.ar.end[i])
6616             {
6617               mpz_set (s, tail->u.ar.end[i]->value.integer);
6618               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6619               mpz_add_ui (s, s, 1);
6620             }
6621           else
6622             {
6623               mpz_set (s, tail->u.ar.start[i]->value.integer);
6624             }
6625
6626           if (mpz_cmp (e1->shape[i], s) != 0)
6627             {
6628               gfc_error ("Source-expr at %L and allocate-object at %L must "
6629                          "have the same shape", &e1->where, &e2->where);
6630               mpz_clear (s);
6631               return FAILURE;
6632             }
6633         }
6634
6635       mpz_clear (s);
6636     }
6637
6638   return SUCCESS;
6639 }
6640
6641
6642 /* Resolve the expression in an ALLOCATE statement, doing the additional
6643    checks to see whether the expression is OK or not.  The expression must
6644    have a trailing array reference that gives the size of the array.  */
6645
6646 static gfc_try
6647 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6648 {
6649   int i, pointer, allocatable, dimension, is_abstract;
6650   int codimension;
6651   bool coindexed;
6652   symbol_attribute attr;
6653   gfc_ref *ref, *ref2;
6654   gfc_expr *e2;
6655   gfc_array_ref *ar;
6656   gfc_symbol *sym = NULL;
6657   gfc_alloc *a;
6658   gfc_component *c;
6659   gfc_try t;
6660
6661   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6662      checking of coarrays.  */
6663   for (ref = e->ref; ref; ref = ref->next)
6664     if (ref->next == NULL)
6665       break;
6666
6667   if (ref && ref->type == REF_ARRAY)
6668     ref->u.ar.in_allocate = true;
6669
6670   if (gfc_resolve_expr (e) == FAILURE)
6671     goto failure;
6672
6673   /* Make sure the expression is allocatable or a pointer.  If it is
6674      pointer, the next-to-last reference must be a pointer.  */
6675
6676   ref2 = NULL;
6677   if (e->symtree)
6678     sym = e->symtree->n.sym;
6679
6680   /* Check whether ultimate component is abstract and CLASS.  */
6681   is_abstract = 0;
6682
6683   if (e->expr_type != EXPR_VARIABLE)
6684     {
6685       allocatable = 0;
6686       attr = gfc_expr_attr (e);
6687       pointer = attr.pointer;
6688       dimension = attr.dimension;
6689       codimension = attr.codimension;
6690     }
6691   else
6692     {
6693       if (sym->ts.type == BT_CLASS)
6694         {
6695           allocatable = CLASS_DATA (sym)->attr.allocatable;
6696           pointer = CLASS_DATA (sym)->attr.class_pointer;
6697           dimension = CLASS_DATA (sym)->attr.dimension;
6698           codimension = CLASS_DATA (sym)->attr.codimension;
6699           is_abstract = CLASS_DATA (sym)->attr.abstract;
6700         }
6701       else
6702         {
6703           allocatable = sym->attr.allocatable;
6704           pointer = sym->attr.pointer;
6705           dimension = sym->attr.dimension;
6706           codimension = sym->attr.codimension;
6707         }
6708
6709       coindexed = false;
6710
6711       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6712         {
6713           switch (ref->type)
6714             {
6715               case REF_ARRAY:
6716                 if (ref->u.ar.codimen > 0)
6717                   {
6718                     int n;
6719                     for (n = ref->u.ar.dimen;
6720                          n < ref->u.ar.dimen + ref->u.ar.codimen; n++)
6721                       if (ref->u.ar.dimen_type[n] != DIMEN_THIS_IMAGE)
6722                         {
6723                           coindexed = true;
6724                           break;
6725                         }
6726                    }
6727
6728                 if (ref->next != NULL)
6729                   pointer = 0;
6730                 break;
6731
6732               case REF_COMPONENT:
6733                 /* F2008, C644.  */
6734                 if (coindexed)
6735                   {
6736                     gfc_error ("Coindexed allocatable object at %L",
6737                                &e->where);
6738                     goto failure;
6739                   }
6740
6741                 c = ref->u.c.component;
6742                 if (c->ts.type == BT_CLASS)
6743                   {
6744                     allocatable = CLASS_DATA (c)->attr.allocatable;
6745                     pointer = CLASS_DATA (c)->attr.class_pointer;
6746                     dimension = CLASS_DATA (c)->attr.dimension;
6747                     codimension = CLASS_DATA (c)->attr.codimension;
6748                     is_abstract = CLASS_DATA (c)->attr.abstract;
6749                   }
6750                 else
6751                   {
6752                     allocatable = c->attr.allocatable;
6753                     pointer = c->attr.pointer;
6754                     dimension = c->attr.dimension;
6755                     codimension = c->attr.codimension;
6756                     is_abstract = c->attr.abstract;
6757                   }
6758                 break;
6759
6760               case REF_SUBSTRING:
6761                 allocatable = 0;
6762                 pointer = 0;
6763                 break;
6764             }
6765         }
6766     }
6767
6768   if (allocatable == 0 && pointer == 0)
6769     {
6770       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6771                  &e->where);
6772       goto failure;
6773     }
6774
6775   /* Some checks for the SOURCE tag.  */
6776   if (code->expr3)
6777     {
6778       /* Check F03:C631.  */
6779       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6780         {
6781           gfc_error ("Type of entity at %L is type incompatible with "
6782                       "source-expr at %L", &e->where, &code->expr3->where);
6783           goto failure;
6784         }
6785
6786       /* Check F03:C632 and restriction following Note 6.18.  */
6787       if (code->expr3->rank > 0
6788           && conformable_arrays (code->expr3, e) == FAILURE)
6789         goto failure;
6790
6791       /* Check F03:C633.  */
6792       if (code->expr3->ts.kind != e->ts.kind)
6793         {
6794           gfc_error ("The allocate-object at %L and the source-expr at %L "
6795                       "shall have the same kind type parameter",
6796                       &e->where, &code->expr3->where);
6797           goto failure;
6798         }
6799     }
6800
6801   /* Check F08:C629.  */
6802   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
6803       && !code->expr3)
6804     {
6805       gcc_assert (e->ts.type == BT_CLASS);
6806       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6807                  "type-spec or source-expr", sym->name, &e->where);
6808       goto failure;
6809     }
6810
6811   /* In the variable definition context checks, gfc_expr_attr is used
6812      on the expression.  This is fooled by the array specification
6813      present in e, thus we have to eliminate that one temporarily.  */
6814   e2 = remove_last_array_ref (e);
6815   t = SUCCESS;
6816   if (t == SUCCESS && pointer)
6817     t = gfc_check_vardef_context (e2, true, _("ALLOCATE object"));
6818   if (t == SUCCESS)
6819     t = gfc_check_vardef_context (e2, false, _("ALLOCATE object"));
6820   gfc_free_expr (e2);
6821   if (t == FAILURE)
6822     goto failure;
6823
6824   if (!code->expr3)
6825     {
6826       /* Set up default initializer if needed.  */
6827       gfc_typespec ts;
6828       gfc_expr *init_e;
6829
6830       if (code->ext.alloc.ts.type == BT_DERIVED)
6831         ts = code->ext.alloc.ts;
6832       else
6833         ts = e->ts;
6834
6835       if (ts.type == BT_CLASS)
6836         ts = ts.u.derived->components->ts;
6837
6838       if (ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&ts)))
6839         {
6840           gfc_code *init_st = gfc_get_code ();
6841           init_st->loc = code->loc;
6842           init_st->op = EXEC_INIT_ASSIGN;
6843           init_st->expr1 = gfc_expr_to_initialize (e);
6844           init_st->expr2 = init_e;
6845           init_st->next = code->next;
6846           code->next = init_st;
6847         }
6848     }
6849   else if (code->expr3->mold && code->expr3->ts.type == BT_DERIVED)
6850     {
6851       /* Default initialization via MOLD (non-polymorphic).  */
6852       gfc_expr *rhs = gfc_default_initializer (&code->expr3->ts);
6853       gfc_resolve_expr (rhs);
6854       gfc_free_expr (code->expr3);
6855       code->expr3 = rhs;
6856     }
6857
6858   if (e->ts.type == BT_CLASS)
6859     {
6860       /* Make sure the vtab symbol is present when
6861          the module variables are generated.  */
6862       gfc_typespec ts = e->ts;
6863       if (code->expr3)
6864         ts = code->expr3->ts;
6865       else if (code->ext.alloc.ts.type == BT_DERIVED)
6866         ts = code->ext.alloc.ts;
6867       gfc_find_derived_vtab (ts.u.derived);
6868     }
6869
6870   if (pointer || (dimension == 0 && codimension == 0))
6871     goto success;
6872
6873   /* Make sure the last reference node is an array specifiction.  */
6874
6875   if (!ref2 || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
6876       || (dimension && ref2->u.ar.dimen == 0))
6877     {
6878       gfc_error ("Array specification required in ALLOCATE statement "
6879                  "at %L", &e->where);
6880       goto failure;
6881     }
6882
6883   /* Make sure that the array section reference makes sense in the
6884     context of an ALLOCATE specification.  */
6885
6886   ar = &ref2->u.ar;
6887
6888   if (codimension)
6889     for (i = ar->dimen; i < ar->dimen + ar->codimen; i++)
6890       if (ar->dimen_type[i] == DIMEN_THIS_IMAGE)
6891         {
6892           gfc_error ("Coarray specification required in ALLOCATE statement "
6893                      "at %L", &e->where);
6894           goto failure;
6895         }
6896
6897   for (i = 0; i < ar->dimen; i++)
6898     {
6899       if (ref2->u.ar.type == AR_ELEMENT)
6900         goto check_symbols;
6901
6902       switch (ar->dimen_type[i])
6903         {
6904         case DIMEN_ELEMENT:
6905           break;
6906
6907         case DIMEN_RANGE:
6908           if (ar->start[i] != NULL
6909               && ar->end[i] != NULL
6910               && ar->stride[i] == NULL)
6911             break;
6912
6913           /* Fall Through...  */
6914
6915         case DIMEN_UNKNOWN:
6916         case DIMEN_VECTOR:
6917         case DIMEN_STAR:
6918         case DIMEN_THIS_IMAGE:
6919           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6920                      &e->where);
6921           goto failure;
6922         }
6923
6924 check_symbols:
6925       for (a = code->ext.alloc.list; a; a = a->next)
6926         {
6927           sym = a->expr->symtree->n.sym;
6928
6929           /* TODO - check derived type components.  */
6930           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6931             continue;
6932
6933           if ((ar->start[i] != NULL
6934                && gfc_find_sym_in_expr (sym, ar->start[i]))
6935               || (ar->end[i] != NULL
6936                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6937             {
6938               gfc_error ("'%s' must not appear in the array specification at "
6939                          "%L in the same ALLOCATE statement where it is "
6940                          "itself allocated", sym->name, &ar->where);
6941               goto failure;
6942             }
6943         }
6944     }
6945
6946   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
6947     {
6948       if (ar->dimen_type[i] == DIMEN_ELEMENT
6949           || ar->dimen_type[i] == DIMEN_RANGE)
6950         {
6951           if (i == (ar->dimen + ar->codimen - 1))
6952             {
6953               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
6954                          "statement at %L", &e->where);
6955               goto failure;
6956             }
6957           break;
6958         }
6959
6960       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
6961           && ar->stride[i] == NULL)
6962         break;
6963
6964       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
6965                  &e->where);
6966       goto failure;
6967     }
6968
6969   if (codimension && ar->as->rank == 0)
6970     {
6971       gfc_error ("Sorry, allocatable scalar coarrays are not yet supported "
6972                  "at %L", &e->where);
6973       goto failure;
6974     }
6975
6976 success:
6977   return SUCCESS;
6978
6979 failure:
6980   return FAILURE;
6981 }
6982
6983 static void
6984 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6985 {
6986   gfc_expr *stat, *errmsg, *pe, *qe;
6987   gfc_alloc *a, *p, *q;
6988
6989   stat = code->expr1;
6990   errmsg = code->expr2;
6991
6992   /* Check the stat variable.  */
6993   if (stat)
6994     {
6995       gfc_check_vardef_context (stat, false, _("STAT variable"));
6996
6997       if ((stat->ts.type != BT_INTEGER
6998            && !(stat->ref && (stat->ref->type == REF_ARRAY
6999                               || stat->ref->type == REF_COMPONENT)))
7000           || stat->rank > 0)
7001         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
7002                    "variable", &stat->where);
7003
7004       for (p = code->ext.alloc.list; p; p = p->next)
7005         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
7006           {
7007             gfc_ref *ref1, *ref2;
7008             bool found = true;
7009
7010             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
7011                  ref1 = ref1->next, ref2 = ref2->next)
7012               {
7013                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7014                   continue;
7015                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7016                   {
7017                     found = false;
7018                     break;
7019                   }
7020               }
7021
7022             if (found)
7023               {
7024                 gfc_error ("Stat-variable at %L shall not be %sd within "
7025                            "the same %s statement", &stat->where, fcn, fcn);
7026                 break;
7027               }
7028           }
7029     }
7030
7031   /* Check the errmsg variable.  */
7032   if (errmsg)
7033     {
7034       if (!stat)
7035         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
7036                      &errmsg->where);
7037
7038       gfc_check_vardef_context (errmsg, false, _("ERRMSG variable"));
7039
7040       if ((errmsg->ts.type != BT_CHARACTER
7041            && !(errmsg->ref
7042                 && (errmsg->ref->type == REF_ARRAY
7043                     || errmsg->ref->type == REF_COMPONENT)))
7044           || errmsg->rank > 0 )
7045         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
7046                    "variable", &errmsg->where);
7047
7048       for (p = code->ext.alloc.list; p; p = p->next)
7049         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
7050           {
7051             gfc_ref *ref1, *ref2;
7052             bool found = true;
7053
7054             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
7055                  ref1 = ref1->next, ref2 = ref2->next)
7056               {
7057                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7058                   continue;
7059                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7060                   {
7061                     found = false;
7062                     break;
7063                   }
7064               }
7065
7066             if (found)
7067               {
7068                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
7069                            "the same %s statement", &errmsg->where, fcn, fcn);
7070                 break;
7071               }
7072           }
7073     }
7074
7075   /* Check that an allocate-object appears only once in the statement.  
7076      FIXME: Checking derived types is disabled.  */
7077   for (p = code->ext.alloc.list; p; p = p->next)
7078     {
7079       pe = p->expr;
7080       for (q = p->next; q; q = q->next)
7081         {
7082           qe = q->expr;
7083           if (pe->symtree->n.sym->name == qe->symtree->n.sym->name)
7084             {
7085               /* This is a potential collision.  */
7086               gfc_ref *pr = pe->ref;
7087               gfc_ref *qr = qe->ref;
7088               
7089               /* Follow the references  until
7090                  a) They start to differ, in which case there is no error;
7091                  you can deallocate a%b and a%c in a single statement
7092                  b) Both of them stop, which is an error
7093                  c) One of them stops, which is also an error.  */
7094               while (1)
7095                 {
7096                   if (pr == NULL && qr == NULL)
7097                     {
7098                       gfc_error ("Allocate-object at %L also appears at %L",
7099                                  &pe->where, &qe->where);
7100                       break;
7101                     }
7102                   else if (pr != NULL && qr == NULL)
7103                     {
7104                       gfc_error ("Allocate-object at %L is subobject of"
7105                                  " object at %L", &pe->where, &qe->where);
7106                       break;
7107                     }
7108                   else if (pr == NULL && qr != NULL)
7109                     {
7110                       gfc_error ("Allocate-object at %L is subobject of"
7111                                  " object at %L", &qe->where, &pe->where);
7112                       break;
7113                     }
7114                   /* Here, pr != NULL && qr != NULL  */
7115                   gcc_assert(pr->type == qr->type);
7116                   if (pr->type == REF_ARRAY)
7117                     {
7118                       /* Handle cases like allocate(v(3)%x(3), v(2)%x(3)),
7119                          which are legal.  */
7120                       gcc_assert (qr->type == REF_ARRAY);
7121
7122                       if (pr->next && qr->next)
7123                         {
7124                           gfc_array_ref *par = &(pr->u.ar);
7125                           gfc_array_ref *qar = &(qr->u.ar);
7126                           if (gfc_dep_compare_expr (par->start[0],
7127                                                     qar->start[0]) != 0)
7128                               break;
7129                         }
7130                     }
7131                   else
7132                     {
7133                       if (pr->u.c.component->name != qr->u.c.component->name)
7134                         break;
7135                     }
7136                   
7137                   pr = pr->next;
7138                   qr = qr->next;
7139                 }
7140             }
7141         }
7142     }
7143
7144   if (strcmp (fcn, "ALLOCATE") == 0)
7145     {
7146       for (a = code->ext.alloc.list; a; a = a->next)
7147         resolve_allocate_expr (a->expr, code);
7148     }
7149   else
7150     {
7151       for (a = code->ext.alloc.list; a; a = a->next)
7152         resolve_deallocate_expr (a->expr);
7153     }
7154 }
7155
7156
7157 /************ SELECT CASE resolution subroutines ************/
7158
7159 /* Callback function for our mergesort variant.  Determines interval
7160    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7161    op1 > op2.  Assumes we're not dealing with the default case.  
7162    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7163    There are nine situations to check.  */
7164
7165 static int
7166 compare_cases (const gfc_case *op1, const gfc_case *op2)
7167 {
7168   int retval;
7169
7170   if (op1->low == NULL) /* op1 = (:L)  */
7171     {
7172       /* op2 = (:N), so overlap.  */
7173       retval = 0;
7174       /* op2 = (M:) or (M:N),  L < M  */
7175       if (op2->low != NULL
7176           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7177         retval = -1;
7178     }
7179   else if (op1->high == NULL) /* op1 = (K:)  */
7180     {
7181       /* op2 = (M:), so overlap.  */
7182       retval = 0;
7183       /* op2 = (:N) or (M:N), K > N  */
7184       if (op2->high != NULL
7185           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7186         retval = 1;
7187     }
7188   else /* op1 = (K:L)  */
7189     {
7190       if (op2->low == NULL)       /* op2 = (:N), K > N  */
7191         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7192                  ? 1 : 0;
7193       else if (op2->high == NULL) /* op2 = (M:), L < M  */
7194         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7195                  ? -1 : 0;
7196       else                      /* op2 = (M:N)  */
7197         {
7198           retval =  0;
7199           /* L < M  */
7200           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7201             retval =  -1;
7202           /* K > N  */
7203           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7204             retval =  1;
7205         }
7206     }
7207
7208   return retval;
7209 }
7210
7211
7212 /* Merge-sort a double linked case list, detecting overlap in the
7213    process.  LIST is the head of the double linked case list before it
7214    is sorted.  Returns the head of the sorted list if we don't see any
7215    overlap, or NULL otherwise.  */
7216
7217 static gfc_case *
7218 check_case_overlap (gfc_case *list)
7219 {
7220   gfc_case *p, *q, *e, *tail;
7221   int insize, nmerges, psize, qsize, cmp, overlap_seen;
7222
7223   /* If the passed list was empty, return immediately.  */
7224   if (!list)
7225     return NULL;
7226
7227   overlap_seen = 0;
7228   insize = 1;
7229
7230   /* Loop unconditionally.  The only exit from this loop is a return
7231      statement, when we've finished sorting the case list.  */
7232   for (;;)
7233     {
7234       p = list;
7235       list = NULL;
7236       tail = NULL;
7237
7238       /* Count the number of merges we do in this pass.  */
7239       nmerges = 0;
7240
7241       /* Loop while there exists a merge to be done.  */
7242       while (p)
7243         {
7244           int i;
7245
7246           /* Count this merge.  */
7247           nmerges++;
7248
7249           /* Cut the list in two pieces by stepping INSIZE places
7250              forward in the list, starting from P.  */
7251           psize = 0;
7252           q = p;
7253           for (i = 0; i < insize; i++)
7254             {
7255               psize++;
7256               q = q->right;
7257               if (!q)
7258                 break;
7259             }
7260           qsize = insize;
7261
7262           /* Now we have two lists.  Merge them!  */
7263           while (psize > 0 || (qsize > 0 && q != NULL))
7264             {
7265               /* See from which the next case to merge comes from.  */
7266               if (psize == 0)
7267                 {
7268                   /* P is empty so the next case must come from Q.  */
7269                   e = q;
7270                   q = q->right;
7271                   qsize--;
7272                 }
7273               else if (qsize == 0 || q == NULL)
7274                 {
7275                   /* Q is empty.  */
7276                   e = p;
7277                   p = p->right;
7278                   psize--;
7279                 }
7280               else
7281                 {
7282                   cmp = compare_cases (p, q);
7283                   if (cmp < 0)
7284                     {
7285                       /* The whole case range for P is less than the
7286                          one for Q.  */
7287                       e = p;
7288                       p = p->right;
7289                       psize--;
7290                     }
7291                   else if (cmp > 0)
7292                     {
7293                       /* The whole case range for Q is greater than
7294                          the case range for P.  */
7295                       e = q;
7296                       q = q->right;
7297                       qsize--;
7298                     }
7299                   else
7300                     {
7301                       /* The cases overlap, or they are the same
7302                          element in the list.  Either way, we must
7303                          issue an error and get the next case from P.  */
7304                       /* FIXME: Sort P and Q by line number.  */
7305                       gfc_error ("CASE label at %L overlaps with CASE "
7306                                  "label at %L", &p->where, &q->where);
7307                       overlap_seen = 1;
7308                       e = p;
7309                       p = p->right;
7310                       psize--;
7311                     }
7312                 }
7313
7314                 /* Add the next element to the merged list.  */
7315               if (tail)
7316                 tail->right = e;
7317               else
7318                 list = e;
7319               e->left = tail;
7320               tail = e;
7321             }
7322
7323           /* P has now stepped INSIZE places along, and so has Q.  So
7324              they're the same.  */
7325           p = q;
7326         }
7327       tail->right = NULL;
7328
7329       /* If we have done only one merge or none at all, we've
7330          finished sorting the cases.  */
7331       if (nmerges <= 1)
7332         {
7333           if (!overlap_seen)
7334             return list;
7335           else
7336             return NULL;
7337         }
7338
7339       /* Otherwise repeat, merging lists twice the size.  */
7340       insize *= 2;
7341     }
7342 }
7343
7344
7345 /* Check to see if an expression is suitable for use in a CASE statement.
7346    Makes sure that all case expressions are scalar constants of the same
7347    type.  Return FAILURE if anything is wrong.  */
7348
7349 static gfc_try
7350 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7351 {
7352   if (e == NULL) return SUCCESS;
7353
7354   if (e->ts.type != case_expr->ts.type)
7355     {
7356       gfc_error ("Expression in CASE statement at %L must be of type %s",
7357                  &e->where, gfc_basic_typename (case_expr->ts.type));
7358       return FAILURE;
7359     }
7360
7361   /* C805 (R808) For a given case-construct, each case-value shall be of
7362      the same type as case-expr.  For character type, length differences
7363      are allowed, but the kind type parameters shall be the same.  */
7364
7365   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7366     {
7367       gfc_error ("Expression in CASE statement at %L must be of kind %d",
7368                  &e->where, case_expr->ts.kind);
7369       return FAILURE;
7370     }
7371
7372   /* Convert the case value kind to that of case expression kind,
7373      if needed */
7374
7375   if (e->ts.kind != case_expr->ts.kind)
7376     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7377
7378   if (e->rank != 0)
7379     {
7380       gfc_error ("Expression in CASE statement at %L must be scalar",
7381                  &e->where);
7382       return FAILURE;
7383     }
7384
7385   return SUCCESS;
7386 }
7387
7388
7389 /* Given a completely parsed select statement, we:
7390
7391      - Validate all expressions and code within the SELECT.
7392      - Make sure that the selection expression is not of the wrong type.
7393      - Make sure that no case ranges overlap.
7394      - Eliminate unreachable cases and unreachable code resulting from
7395        removing case labels.
7396
7397    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7398    they are a hassle for code generation, and to prevent that, we just
7399    cut them out here.  This is not necessary for overlapping cases
7400    because they are illegal and we never even try to generate code.
7401
7402    We have the additional caveat that a SELECT construct could have
7403    been a computed GOTO in the source code. Fortunately we can fairly
7404    easily work around that here: The case_expr for a "real" SELECT CASE
7405    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7406    we have to do is make sure that the case_expr is a scalar integer
7407    expression.  */
7408
7409 static void
7410 resolve_select (gfc_code *code)
7411 {
7412   gfc_code *body;
7413   gfc_expr *case_expr;
7414   gfc_case *cp, *default_case, *tail, *head;
7415   int seen_unreachable;
7416   int seen_logical;
7417   int ncases;
7418   bt type;
7419   gfc_try t;
7420
7421   if (code->expr1 == NULL)
7422     {
7423       /* This was actually a computed GOTO statement.  */
7424       case_expr = code->expr2;
7425       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7426         gfc_error ("Selection expression in computed GOTO statement "
7427                    "at %L must be a scalar integer expression",
7428                    &case_expr->where);
7429
7430       /* Further checking is not necessary because this SELECT was built
7431          by the compiler, so it should always be OK.  Just move the
7432          case_expr from expr2 to expr so that we can handle computed
7433          GOTOs as normal SELECTs from here on.  */
7434       code->expr1 = code->expr2;
7435       code->expr2 = NULL;
7436       return;
7437     }
7438
7439   case_expr = code->expr1;
7440
7441   type = case_expr->ts.type;
7442   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7443     {
7444       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7445                  &case_expr->where, gfc_typename (&case_expr->ts));
7446
7447       /* Punt. Going on here just produce more garbage error messages.  */
7448       return;
7449     }
7450
7451   if (case_expr->rank != 0)
7452     {
7453       gfc_error ("Argument of SELECT statement at %L must be a scalar "
7454                  "expression", &case_expr->where);
7455
7456       /* Punt.  */
7457       return;
7458     }
7459
7460
7461   /* Raise a warning if an INTEGER case value exceeds the range of
7462      the case-expr. Later, all expressions will be promoted to the
7463      largest kind of all case-labels.  */
7464
7465   if (type == BT_INTEGER)
7466     for (body = code->block; body; body = body->block)
7467       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7468         {
7469           if (cp->low
7470               && gfc_check_integer_range (cp->low->value.integer,
7471                                           case_expr->ts.kind) != ARITH_OK)
7472             gfc_warning ("Expression in CASE statement at %L is "
7473                          "not in the range of %s", &cp->low->where,
7474                          gfc_typename (&case_expr->ts));
7475
7476           if (cp->high
7477               && cp->low != cp->high
7478               && gfc_check_integer_range (cp->high->value.integer,
7479                                           case_expr->ts.kind) != ARITH_OK)
7480             gfc_warning ("Expression in CASE statement at %L is "
7481                          "not in the range of %s", &cp->high->where,
7482                          gfc_typename (&case_expr->ts));
7483         }
7484
7485   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7486      of the SELECT CASE expression and its CASE values.  Walk the lists
7487      of case values, and if we find a mismatch, promote case_expr to
7488      the appropriate kind.  */
7489
7490   if (type == BT_LOGICAL || type == BT_INTEGER)
7491     {
7492       for (body = code->block; body; body = body->block)
7493         {
7494           /* Walk the case label list.  */
7495           for (cp = body->ext.block.case_list; cp; cp = cp->next)
7496             {
7497               /* Intercept the DEFAULT case.  It does not have a kind.  */
7498               if (cp->low == NULL && cp->high == NULL)
7499                 continue;
7500
7501               /* Unreachable case ranges are discarded, so ignore.  */
7502               if (cp->low != NULL && cp->high != NULL
7503                   && cp->low != cp->high
7504                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7505                 continue;
7506
7507               if (cp->low != NULL
7508                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7509                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7510
7511               if (cp->high != NULL
7512                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7513                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7514             }
7515          }
7516     }
7517
7518   /* Assume there is no DEFAULT case.  */
7519   default_case = NULL;
7520   head = tail = NULL;
7521   ncases = 0;
7522   seen_logical = 0;
7523
7524   for (body = code->block; body; body = body->block)
7525     {
7526       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7527       t = SUCCESS;
7528       seen_unreachable = 0;
7529
7530       /* Walk the case label list, making sure that all case labels
7531          are legal.  */
7532       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7533         {
7534           /* Count the number of cases in the whole construct.  */
7535           ncases++;
7536
7537           /* Intercept the DEFAULT case.  */
7538           if (cp->low == NULL && cp->high == NULL)
7539             {
7540               if (default_case != NULL)
7541                 {
7542                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7543                              "by a second DEFAULT CASE at %L",
7544                              &default_case->where, &cp->where);
7545                   t = FAILURE;
7546                   break;
7547                 }
7548               else
7549                 {
7550                   default_case = cp;
7551                   continue;
7552                 }
7553             }
7554
7555           /* Deal with single value cases and case ranges.  Errors are
7556              issued from the validation function.  */
7557           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7558               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7559             {
7560               t = FAILURE;
7561               break;
7562             }
7563
7564           if (type == BT_LOGICAL
7565               && ((cp->low == NULL || cp->high == NULL)
7566                   || cp->low != cp->high))
7567             {
7568               gfc_error ("Logical range in CASE statement at %L is not "
7569                          "allowed", &cp->low->where);
7570               t = FAILURE;
7571               break;
7572             }
7573
7574           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7575             {
7576               int value;
7577               value = cp->low->value.logical == 0 ? 2 : 1;
7578               if (value & seen_logical)
7579                 {
7580                   gfc_error ("Constant logical value in CASE statement "
7581                              "is repeated at %L",
7582                              &cp->low->where);
7583                   t = FAILURE;
7584                   break;
7585                 }
7586               seen_logical |= value;
7587             }
7588
7589           if (cp->low != NULL && cp->high != NULL
7590               && cp->low != cp->high
7591               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7592             {
7593               if (gfc_option.warn_surprising)
7594                 gfc_warning ("Range specification at %L can never "
7595                              "be matched", &cp->where);
7596
7597               cp->unreachable = 1;
7598               seen_unreachable = 1;
7599             }
7600           else
7601             {
7602               /* If the case range can be matched, it can also overlap with
7603                  other cases.  To make sure it does not, we put it in a
7604                  double linked list here.  We sort that with a merge sort
7605                  later on to detect any overlapping cases.  */
7606               if (!head)
7607                 {
7608                   head = tail = cp;
7609                   head->right = head->left = NULL;
7610                 }
7611               else
7612                 {
7613                   tail->right = cp;
7614                   tail->right->left = tail;
7615                   tail = tail->right;
7616                   tail->right = NULL;
7617                 }
7618             }
7619         }
7620
7621       /* It there was a failure in the previous case label, give up
7622          for this case label list.  Continue with the next block.  */
7623       if (t == FAILURE)
7624         continue;
7625
7626       /* See if any case labels that are unreachable have been seen.
7627          If so, we eliminate them.  This is a bit of a kludge because
7628          the case lists for a single case statement (label) is a
7629          single forward linked lists.  */
7630       if (seen_unreachable)
7631       {
7632         /* Advance until the first case in the list is reachable.  */
7633         while (body->ext.block.case_list != NULL
7634                && body->ext.block.case_list->unreachable)
7635           {
7636             gfc_case *n = body->ext.block.case_list;
7637             body->ext.block.case_list = body->ext.block.case_list->next;
7638             n->next = NULL;
7639             gfc_free_case_list (n);
7640           }
7641
7642         /* Strip all other unreachable cases.  */
7643         if (body->ext.block.case_list)
7644           {
7645             for (cp = body->ext.block.case_list; cp->next; cp = cp->next)
7646               {
7647                 if (cp->next->unreachable)
7648                   {
7649                     gfc_case *n = cp->next;
7650                     cp->next = cp->next->next;
7651                     n->next = NULL;
7652                     gfc_free_case_list (n);
7653                   }
7654               }
7655           }
7656       }
7657     }
7658
7659   /* See if there were overlapping cases.  If the check returns NULL,
7660      there was overlap.  In that case we don't do anything.  If head
7661      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7662      then used during code generation for SELECT CASE constructs with
7663      a case expression of a CHARACTER type.  */
7664   if (head)
7665     {
7666       head = check_case_overlap (head);
7667
7668       /* Prepend the default_case if it is there.  */
7669       if (head != NULL && default_case)
7670         {
7671           default_case->left = NULL;
7672           default_case->right = head;
7673           head->left = default_case;
7674         }
7675     }
7676
7677   /* Eliminate dead blocks that may be the result if we've seen
7678      unreachable case labels for a block.  */
7679   for (body = code; body && body->block; body = body->block)
7680     {
7681       if (body->block->ext.block.case_list == NULL)
7682         {
7683           /* Cut the unreachable block from the code chain.  */
7684           gfc_code *c = body->block;
7685           body->block = c->block;
7686
7687           /* Kill the dead block, but not the blocks below it.  */
7688           c->block = NULL;
7689           gfc_free_statements (c);
7690         }
7691     }
7692
7693   /* More than two cases is legal but insane for logical selects.
7694      Issue a warning for it.  */
7695   if (gfc_option.warn_surprising && type == BT_LOGICAL
7696       && ncases > 2)
7697     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7698                  &code->loc);
7699 }
7700
7701
7702 /* Check if a derived type is extensible.  */
7703
7704 bool
7705 gfc_type_is_extensible (gfc_symbol *sym)
7706 {
7707   return !(sym->attr.is_bind_c || sym->attr.sequence);
7708 }
7709
7710
7711 /* Resolve an associate name:  Resolve target and ensure the type-spec is
7712    correct as well as possibly the array-spec.  */
7713
7714 static void
7715 resolve_assoc_var (gfc_symbol* sym, bool resolve_target)
7716 {
7717   gfc_expr* target;
7718
7719   gcc_assert (sym->assoc);
7720   gcc_assert (sym->attr.flavor == FL_VARIABLE);
7721
7722   /* If this is for SELECT TYPE, the target may not yet be set.  In that
7723      case, return.  Resolution will be called later manually again when
7724      this is done.  */
7725   target = sym->assoc->target;
7726   if (!target)
7727     return;
7728   gcc_assert (!sym->assoc->dangling);
7729
7730   if (resolve_target && gfc_resolve_expr (target) != SUCCESS)
7731     return;
7732
7733   /* For variable targets, we get some attributes from the target.  */
7734   if (target->expr_type == EXPR_VARIABLE)
7735     {
7736       gfc_symbol* tsym;
7737
7738       gcc_assert (target->symtree);
7739       tsym = target->symtree->n.sym;
7740
7741       sym->attr.asynchronous = tsym->attr.asynchronous;
7742       sym->attr.volatile_ = tsym->attr.volatile_;
7743
7744       sym->attr.target = (tsym->attr.target || tsym->attr.pointer);
7745     }
7746
7747   /* Get type if this was not already set.  Note that it can be
7748      some other type than the target in case this is a SELECT TYPE
7749      selector!  So we must not update when the type is already there.  */
7750   if (sym->ts.type == BT_UNKNOWN)
7751     sym->ts = target->ts;
7752   gcc_assert (sym->ts.type != BT_UNKNOWN);
7753
7754   /* See if this is a valid association-to-variable.  */
7755   sym->assoc->variable = (target->expr_type == EXPR_VARIABLE
7756                           && !gfc_has_vector_subscript (target));
7757
7758   /* Finally resolve if this is an array or not.  */
7759   if (sym->attr.dimension && target->rank == 0)
7760     {
7761       gfc_error ("Associate-name '%s' at %L is used as array",
7762                  sym->name, &sym->declared_at);
7763       sym->attr.dimension = 0;
7764       return;
7765     }
7766   if (target->rank > 0)
7767     sym->attr.dimension = 1;
7768
7769   if (sym->attr.dimension)
7770     {
7771       sym->as = gfc_get_array_spec ();
7772       sym->as->rank = target->rank;
7773       sym->as->type = AS_DEFERRED;
7774
7775       /* Target must not be coindexed, thus the associate-variable
7776          has no corank.  */
7777       sym->as->corank = 0;
7778     }
7779 }
7780
7781
7782 /* Resolve a SELECT TYPE statement.  */
7783
7784 static void
7785 resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
7786 {
7787   gfc_symbol *selector_type;
7788   gfc_code *body, *new_st, *if_st, *tail;
7789   gfc_code *class_is = NULL, *default_case = NULL;
7790   gfc_case *c;
7791   gfc_symtree *st;
7792   char name[GFC_MAX_SYMBOL_LEN];
7793   gfc_namespace *ns;
7794   int error = 0;
7795
7796   ns = code->ext.block.ns;
7797   gfc_resolve (ns);
7798
7799   /* Check for F03:C813.  */
7800   if (code->expr1->ts.type != BT_CLASS
7801       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
7802     {
7803       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
7804                  "at %L", &code->loc);
7805       return;
7806     }
7807
7808   if (code->expr2)
7809     {
7810       if (code->expr1->symtree->n.sym->attr.untyped)
7811         code->expr1->symtree->n.sym->ts = code->expr2->ts;
7812       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
7813     }
7814   else
7815     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
7816
7817   /* Loop over TYPE IS / CLASS IS cases.  */
7818   for (body = code->block; body; body = body->block)
7819     {
7820       c = body->ext.block.case_list;
7821
7822       /* Check F03:C815.  */
7823       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7824           && !gfc_type_is_extensible (c->ts.u.derived))
7825         {
7826           gfc_error ("Derived type '%s' at %L must be extensible",
7827                      c->ts.u.derived->name, &c->where);
7828           error++;
7829           continue;
7830         }
7831
7832       /* Check F03:C816.  */
7833       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7834           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
7835         {
7836           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
7837                      c->ts.u.derived->name, &c->where, selector_type->name);
7838           error++;
7839           continue;
7840         }
7841
7842       /* Intercept the DEFAULT case.  */
7843       if (c->ts.type == BT_UNKNOWN)
7844         {
7845           /* Check F03:C818.  */
7846           if (default_case)
7847             {
7848               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7849                          "by a second DEFAULT CASE at %L",
7850                          &default_case->ext.block.case_list->where, &c->where);
7851               error++;
7852               continue;
7853             }
7854
7855           default_case = body;
7856         }
7857     }
7858     
7859   if (error > 0)
7860     return;
7861
7862   /* Transform SELECT TYPE statement to BLOCK and associate selector to
7863      target if present.  If there are any EXIT statements referring to the
7864      SELECT TYPE construct, this is no problem because the gfc_code
7865      reference stays the same and EXIT is equally possible from the BLOCK
7866      it is changed to.  */
7867   code->op = EXEC_BLOCK;
7868   if (code->expr2)
7869     {
7870       gfc_association_list* assoc;
7871
7872       assoc = gfc_get_association_list ();
7873       assoc->st = code->expr1->symtree;
7874       assoc->target = gfc_copy_expr (code->expr2);
7875       /* assoc->variable will be set by resolve_assoc_var.  */
7876       
7877       code->ext.block.assoc = assoc;
7878       code->expr1->symtree->n.sym->assoc = assoc;
7879
7880       resolve_assoc_var (code->expr1->symtree->n.sym, false);
7881     }
7882   else
7883     code->ext.block.assoc = NULL;
7884
7885   /* Add EXEC_SELECT to switch on type.  */
7886   new_st = gfc_get_code ();
7887   new_st->op = code->op;
7888   new_st->expr1 = code->expr1;
7889   new_st->expr2 = code->expr2;
7890   new_st->block = code->block;
7891   code->expr1 = code->expr2 =  NULL;
7892   code->block = NULL;
7893   if (!ns->code)
7894     ns->code = new_st;
7895   else
7896     ns->code->next = new_st;
7897   code = new_st;
7898   code->op = EXEC_SELECT;
7899   gfc_add_vptr_component (code->expr1);
7900   gfc_add_hash_component (code->expr1);
7901
7902   /* Loop over TYPE IS / CLASS IS cases.  */
7903   for (body = code->block; body; body = body->block)
7904     {
7905       c = body->ext.block.case_list;
7906
7907       if (c->ts.type == BT_DERIVED)
7908         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
7909                                              c->ts.u.derived->hash_value);
7910
7911       else if (c->ts.type == BT_UNKNOWN)
7912         continue;
7913
7914       /* Associate temporary to selector.  This should only be done
7915          when this case is actually true, so build a new ASSOCIATE
7916          that does precisely this here (instead of using the
7917          'global' one).  */
7918
7919       if (c->ts.type == BT_CLASS)
7920         sprintf (name, "__tmp_class_%s", c->ts.u.derived->name);
7921       else
7922         sprintf (name, "__tmp_type_%s", c->ts.u.derived->name);
7923       st = gfc_find_symtree (ns->sym_root, name);
7924       gcc_assert (st->n.sym->assoc);
7925       st->n.sym->assoc->target = gfc_get_variable_expr (code->expr1->symtree);
7926       if (c->ts.type == BT_DERIVED)
7927         gfc_add_data_component (st->n.sym->assoc->target);
7928
7929       new_st = gfc_get_code ();
7930       new_st->op = EXEC_BLOCK;
7931       new_st->ext.block.ns = gfc_build_block_ns (ns);
7932       new_st->ext.block.ns->code = body->next;
7933       body->next = new_st;
7934
7935       /* Chain in the new list only if it is marked as dangling.  Otherwise
7936          there is a CASE label overlap and this is already used.  Just ignore,
7937          the error is diagonsed elsewhere.  */
7938       if (st->n.sym->assoc->dangling)
7939         {
7940           new_st->ext.block.assoc = st->n.sym->assoc;
7941           st->n.sym->assoc->dangling = 0;
7942         }
7943
7944       resolve_assoc_var (st->n.sym, false);
7945     }
7946     
7947   /* Take out CLASS IS cases for separate treatment.  */
7948   body = code;
7949   while (body && body->block)
7950     {
7951       if (body->block->ext.block.case_list->ts.type == BT_CLASS)
7952         {
7953           /* Add to class_is list.  */
7954           if (class_is == NULL)
7955             { 
7956               class_is = body->block;
7957               tail = class_is;
7958             }
7959           else
7960             {
7961               for (tail = class_is; tail->block; tail = tail->block) ;
7962               tail->block = body->block;
7963               tail = tail->block;
7964             }
7965           /* Remove from EXEC_SELECT list.  */
7966           body->block = body->block->block;
7967           tail->block = NULL;
7968         }
7969       else
7970         body = body->block;
7971     }
7972
7973   if (class_is)
7974     {
7975       gfc_symbol *vtab;
7976       
7977       if (!default_case)
7978         {
7979           /* Add a default case to hold the CLASS IS cases.  */
7980           for (tail = code; tail->block; tail = tail->block) ;
7981           tail->block = gfc_get_code ();
7982           tail = tail->block;
7983           tail->op = EXEC_SELECT_TYPE;
7984           tail->ext.block.case_list = gfc_get_case ();
7985           tail->ext.block.case_list->ts.type = BT_UNKNOWN;
7986           tail->next = NULL;
7987           default_case = tail;
7988         }
7989
7990       /* More than one CLASS IS block?  */
7991       if (class_is->block)
7992         {
7993           gfc_code **c1,*c2;
7994           bool swapped;
7995           /* Sort CLASS IS blocks by extension level.  */
7996           do
7997             {
7998               swapped = false;
7999               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
8000                 {
8001                   c2 = (*c1)->block;
8002                   /* F03:C817 (check for doubles).  */
8003                   if ((*c1)->ext.block.case_list->ts.u.derived->hash_value
8004                       == c2->ext.block.case_list->ts.u.derived->hash_value)
8005                     {
8006                       gfc_error ("Double CLASS IS block in SELECT TYPE "
8007                                  "statement at %L",
8008                                  &c2->ext.block.case_list->where);
8009                       return;
8010                     }
8011                   if ((*c1)->ext.block.case_list->ts.u.derived->attr.extension
8012                       < c2->ext.block.case_list->ts.u.derived->attr.extension)
8013                     {
8014                       /* Swap.  */
8015                       (*c1)->block = c2->block;
8016                       c2->block = *c1;
8017                       *c1 = c2;
8018                       swapped = true;
8019                     }
8020                 }
8021             }
8022           while (swapped);
8023         }
8024         
8025       /* Generate IF chain.  */
8026       if_st = gfc_get_code ();
8027       if_st->op = EXEC_IF;
8028       new_st = if_st;
8029       for (body = class_is; body; body = body->block)
8030         {
8031           new_st->block = gfc_get_code ();
8032           new_st = new_st->block;
8033           new_st->op = EXEC_IF;
8034           /* Set up IF condition: Call _gfortran_is_extension_of.  */
8035           new_st->expr1 = gfc_get_expr ();
8036           new_st->expr1->expr_type = EXPR_FUNCTION;
8037           new_st->expr1->ts.type = BT_LOGICAL;
8038           new_st->expr1->ts.kind = 4;
8039           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
8040           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
8041           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
8042           /* Set up arguments.  */
8043           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
8044           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
8045           new_st->expr1->value.function.actual->expr->where = code->loc;
8046           gfc_add_vptr_component (new_st->expr1->value.function.actual->expr);
8047           vtab = gfc_find_derived_vtab (body->ext.block.case_list->ts.u.derived);
8048           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
8049           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
8050           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
8051           new_st->next = body->next;
8052         }
8053         if (default_case->next)
8054           {
8055             new_st->block = gfc_get_code ();
8056             new_st = new_st->block;
8057             new_st->op = EXEC_IF;
8058             new_st->next = default_case->next;
8059           }
8060           
8061         /* Replace CLASS DEFAULT code by the IF chain.  */
8062         default_case->next = if_st;
8063     }
8064
8065   /* Resolve the internal code.  This can not be done earlier because
8066      it requires that the sym->assoc of selectors is set already.  */
8067   gfc_current_ns = ns;
8068   gfc_resolve_blocks (code->block, gfc_current_ns);
8069   gfc_current_ns = old_ns;
8070
8071   resolve_select (code);
8072 }
8073
8074
8075 /* Resolve a transfer statement. This is making sure that:
8076    -- a derived type being transferred has only non-pointer components
8077    -- a derived type being transferred doesn't have private components, unless 
8078       it's being transferred from the module where the type was defined
8079    -- we're not trying to transfer a whole assumed size array.  */
8080
8081 static void
8082 resolve_transfer (gfc_code *code)
8083 {
8084   gfc_typespec *ts;
8085   gfc_symbol *sym;
8086   gfc_ref *ref;
8087   gfc_expr *exp;
8088
8089   exp = code->expr1;
8090
8091   while (exp != NULL && exp->expr_type == EXPR_OP
8092          && exp->value.op.op == INTRINSIC_PARENTHESES)
8093     exp = exp->value.op.op1;
8094
8095   if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
8096                       && exp->expr_type != EXPR_FUNCTION))
8097     return;
8098
8099   /* If we are reading, the variable will be changed.  Note that
8100      code->ext.dt may be NULL if the TRANSFER is related to
8101      an INQUIRE statement -- but in this case, we are not reading, either.  */
8102   if (code->ext.dt && code->ext.dt->dt_io_kind->value.iokind == M_READ
8103       && gfc_check_vardef_context (exp, false, _("item in READ")) == FAILURE)
8104     return;
8105
8106   sym = exp->symtree->n.sym;
8107   ts = &sym->ts;
8108
8109   /* Go to actual component transferred.  */
8110   for (ref = exp->ref; ref; ref = ref->next)
8111     if (ref->type == REF_COMPONENT)
8112       ts = &ref->u.c.component->ts;
8113
8114   if (ts->type == BT_CLASS)
8115     {
8116       /* FIXME: Test for defined input/output.  */
8117       gfc_error ("Data transfer element at %L cannot be polymorphic unless "
8118                 "it is processed by a defined input/output procedure",
8119                 &code->loc);
8120       return;
8121     }
8122
8123   if (ts->type == BT_DERIVED)
8124     {
8125       /* Check that transferred derived type doesn't contain POINTER
8126          components.  */
8127       if (ts->u.derived->attr.pointer_comp)
8128         {
8129           gfc_error ("Data transfer element at %L cannot have "
8130                      "POINTER components", &code->loc);
8131           return;
8132         }
8133
8134       /* F08:C935.  */
8135       if (ts->u.derived->attr.proc_pointer_comp)
8136         {
8137           gfc_error ("Data transfer element at %L cannot have "
8138                      "procedure pointer components", &code->loc);
8139           return;
8140         }
8141
8142       if (ts->u.derived->attr.alloc_comp)
8143         {
8144           gfc_error ("Data transfer element at %L cannot have "
8145                      "ALLOCATABLE components", &code->loc);
8146           return;
8147         }
8148
8149       if (derived_inaccessible (ts->u.derived))
8150         {
8151           gfc_error ("Data transfer element at %L cannot have "
8152                      "PRIVATE components",&code->loc);
8153           return;
8154         }
8155     }
8156
8157   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
8158       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
8159     {
8160       gfc_error ("Data transfer element at %L cannot be a full reference to "
8161                  "an assumed-size array", &code->loc);
8162       return;
8163     }
8164 }
8165
8166
8167 /*********** Toplevel code resolution subroutines ***********/
8168
8169 /* Find the set of labels that are reachable from this block.  We also
8170    record the last statement in each block.  */
8171      
8172 static void
8173 find_reachable_labels (gfc_code *block)
8174 {
8175   gfc_code *c;
8176
8177   if (!block)
8178     return;
8179
8180   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
8181
8182   /* Collect labels in this block.  We don't keep those corresponding
8183      to END {IF|SELECT}, these are checked in resolve_branch by going
8184      up through the code_stack.  */
8185   for (c = block; c; c = c->next)
8186     {
8187       if (c->here && c->op != EXEC_END_BLOCK)
8188         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
8189     }
8190
8191   /* Merge with labels from parent block.  */
8192   if (cs_base->prev)
8193     {
8194       gcc_assert (cs_base->prev->reachable_labels);
8195       bitmap_ior_into (cs_base->reachable_labels,
8196                        cs_base->prev->reachable_labels);
8197     }
8198 }
8199
8200
8201 static void
8202 resolve_lock_unlock (gfc_code *code)
8203 {
8204   /* FIXME: Add more lock-variable checks. For now, always reject it.
8205      Note that ISO_FORTRAN_ENV's LOCK_TYPE is not yet available.  */
8206   /* if (code->expr2->ts.type != BT_DERIVED
8207          || code->expr2->rank != 0
8208          || code->expr2->expr_type != EXPR_VARIABLE)  */
8209   gfc_error ("Lock variable at %L must be a scalar of type LOCK_TYPE",
8210              &code->expr1->where);
8211
8212   /* Check STAT.  */
8213   if (code->expr2
8214       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8215           || code->expr2->expr_type != EXPR_VARIABLE))
8216     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8217                &code->expr2->where);
8218
8219   /* Check ERRMSG.  */
8220   if (code->expr3
8221       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8222           || code->expr3->expr_type != EXPR_VARIABLE))
8223     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8224                &code->expr3->where);
8225
8226   /* Check ACQUIRED_LOCK.  */
8227   if (code->expr4
8228       && (code->expr4->ts.type != BT_LOGICAL || code->expr4->rank != 0
8229           || code->expr4->expr_type != EXPR_VARIABLE))
8230     gfc_error ("ACQUIRED_LOCK= argument at %L must be a scalar LOGICAL "
8231                "variable", &code->expr4->where);
8232 }
8233
8234
8235 static void
8236 resolve_sync (gfc_code *code)
8237 {
8238   /* Check imageset. The * case matches expr1 == NULL.  */
8239   if (code->expr1)
8240     {
8241       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
8242         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
8243                    "INTEGER expression", &code->expr1->where);
8244       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
8245           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
8246         gfc_error ("Imageset argument at %L must between 1 and num_images()",
8247                    &code->expr1->where);
8248       else if (code->expr1->expr_type == EXPR_ARRAY
8249                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
8250         {
8251            gfc_constructor *cons;
8252            cons = gfc_constructor_first (code->expr1->value.constructor);
8253            for (; cons; cons = gfc_constructor_next (cons))
8254              if (cons->expr->expr_type == EXPR_CONSTANT
8255                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
8256                gfc_error ("Imageset argument at %L must between 1 and "
8257                           "num_images()", &cons->expr->where);
8258         }
8259     }
8260
8261   /* Check STAT.  */
8262   if (code->expr2
8263       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8264           || code->expr2->expr_type != EXPR_VARIABLE))
8265     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8266                &code->expr2->where);
8267
8268   /* Check ERRMSG.  */
8269   if (code->expr3
8270       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8271           || code->expr3->expr_type != EXPR_VARIABLE))
8272     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8273                &code->expr3->where);
8274 }
8275
8276
8277 /* Given a branch to a label, see if the branch is conforming.
8278    The code node describes where the branch is located.  */
8279
8280 static void
8281 resolve_branch (gfc_st_label *label, gfc_code *code)
8282 {
8283   code_stack *stack;
8284
8285   if (label == NULL)
8286     return;
8287
8288   /* Step one: is this a valid branching target?  */
8289
8290   if (label->defined == ST_LABEL_UNKNOWN)
8291     {
8292       gfc_error ("Label %d referenced at %L is never defined", label->value,
8293                  &label->where);
8294       return;
8295     }
8296
8297   if (label->defined != ST_LABEL_TARGET)
8298     {
8299       gfc_error ("Statement at %L is not a valid branch target statement "
8300                  "for the branch statement at %L", &label->where, &code->loc);
8301       return;
8302     }
8303
8304   /* Step two: make sure this branch is not a branch to itself ;-)  */
8305
8306   if (code->here == label)
8307     {
8308       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
8309       return;
8310     }
8311
8312   /* Step three:  See if the label is in the same block as the
8313      branching statement.  The hard work has been done by setting up
8314      the bitmap reachable_labels.  */
8315
8316   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8317     {
8318       /* Check now whether there is a CRITICAL construct; if so, check
8319          whether the label is still visible outside of the CRITICAL block,
8320          which is invalid.  */
8321       for (stack = cs_base; stack; stack = stack->prev)
8322         if (stack->current->op == EXEC_CRITICAL
8323             && bitmap_bit_p (stack->reachable_labels, label->value))
8324           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8325                       " at %L", &code->loc, &label->where);
8326
8327       return;
8328     }
8329
8330   /* Step four:  If we haven't found the label in the bitmap, it may
8331     still be the label of the END of the enclosing block, in which
8332     case we find it by going up the code_stack.  */
8333
8334   for (stack = cs_base; stack; stack = stack->prev)
8335     {
8336       if (stack->current->next && stack->current->next->here == label)
8337         break;
8338       if (stack->current->op == EXEC_CRITICAL)
8339         {
8340           /* Note: A label at END CRITICAL does not leave the CRITICAL
8341              construct as END CRITICAL is still part of it.  */
8342           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8343                       " at %L", &code->loc, &label->where);
8344           return;
8345         }
8346     }
8347
8348   if (stack)
8349     {
8350       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
8351       return;
8352     }
8353
8354   /* The label is not in an enclosing block, so illegal.  This was
8355      allowed in Fortran 66, so we allow it as extension.  No
8356      further checks are necessary in this case.  */
8357   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
8358                   "as the GOTO statement at %L", &label->where,
8359                   &code->loc);
8360   return;
8361 }
8362
8363
8364 /* Check whether EXPR1 has the same shape as EXPR2.  */
8365
8366 static gfc_try
8367 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8368 {
8369   mpz_t shape[GFC_MAX_DIMENSIONS];
8370   mpz_t shape2[GFC_MAX_DIMENSIONS];
8371   gfc_try result = FAILURE;
8372   int i;
8373
8374   /* Compare the rank.  */
8375   if (expr1->rank != expr2->rank)
8376     return result;
8377
8378   /* Compare the size of each dimension.  */
8379   for (i=0; i<expr1->rank; i++)
8380     {
8381       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
8382         goto ignore;
8383
8384       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
8385         goto ignore;
8386
8387       if (mpz_cmp (shape[i], shape2[i]))
8388         goto over;
8389     }
8390
8391   /* When either of the two expression is an assumed size array, we
8392      ignore the comparison of dimension sizes.  */
8393 ignore:
8394   result = SUCCESS;
8395
8396 over:
8397   for (i--; i >= 0; i--)
8398     {
8399       mpz_clear (shape[i]);
8400       mpz_clear (shape2[i]);
8401     }
8402   return result;
8403 }
8404
8405
8406 /* Check whether a WHERE assignment target or a WHERE mask expression
8407    has the same shape as the outmost WHERE mask expression.  */
8408
8409 static void
8410 resolve_where (gfc_code *code, gfc_expr *mask)
8411 {
8412   gfc_code *cblock;
8413   gfc_code *cnext;
8414   gfc_expr *e = NULL;
8415
8416   cblock = code->block;
8417
8418   /* Store the first WHERE mask-expr of the WHERE statement or construct.
8419      In case of nested WHERE, only the outmost one is stored.  */
8420   if (mask == NULL) /* outmost WHERE */
8421     e = cblock->expr1;
8422   else /* inner WHERE */
8423     e = mask;
8424
8425   while (cblock)
8426     {
8427       if (cblock->expr1)
8428         {
8429           /* Check if the mask-expr has a consistent shape with the
8430              outmost WHERE mask-expr.  */
8431           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
8432             gfc_error ("WHERE mask at %L has inconsistent shape",
8433                        &cblock->expr1->where);
8434          }
8435
8436       /* the assignment statement of a WHERE statement, or the first
8437          statement in where-body-construct of a WHERE construct */
8438       cnext = cblock->next;
8439       while (cnext)
8440         {
8441           switch (cnext->op)
8442             {
8443             /* WHERE assignment statement */
8444             case EXEC_ASSIGN:
8445
8446               /* Check shape consistent for WHERE assignment target.  */
8447               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
8448                gfc_error ("WHERE assignment target at %L has "
8449                           "inconsistent shape", &cnext->expr1->where);
8450               break;
8451
8452   
8453             case EXEC_ASSIGN_CALL:
8454               resolve_call (cnext);
8455               if (!cnext->resolved_sym->attr.elemental)
8456                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8457                           &cnext->ext.actual->expr->where);
8458               break;
8459
8460             /* WHERE or WHERE construct is part of a where-body-construct */
8461             case EXEC_WHERE:
8462               resolve_where (cnext, e);
8463               break;
8464
8465             default:
8466               gfc_error ("Unsupported statement inside WHERE at %L",
8467                          &cnext->loc);
8468             }
8469          /* the next statement within the same where-body-construct */
8470          cnext = cnext->next;
8471        }
8472     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8473     cblock = cblock->block;
8474   }
8475 }
8476
8477
8478 /* Resolve assignment in FORALL construct.
8479    NVAR is the number of FORALL index variables, and VAR_EXPR records the
8480    FORALL index variables.  */
8481
8482 static void
8483 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8484 {
8485   int n;
8486
8487   for (n = 0; n < nvar; n++)
8488     {
8489       gfc_symbol *forall_index;
8490
8491       forall_index = var_expr[n]->symtree->n.sym;
8492
8493       /* Check whether the assignment target is one of the FORALL index
8494          variable.  */
8495       if ((code->expr1->expr_type == EXPR_VARIABLE)
8496           && (code->expr1->symtree->n.sym == forall_index))
8497         gfc_error ("Assignment to a FORALL index variable at %L",
8498                    &code->expr1->where);
8499       else
8500         {
8501           /* If one of the FORALL index variables doesn't appear in the
8502              assignment variable, then there could be a many-to-one
8503              assignment.  Emit a warning rather than an error because the
8504              mask could be resolving this problem.  */
8505           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
8506             gfc_warning ("The FORALL with index '%s' is not used on the "
8507                          "left side of the assignment at %L and so might "
8508                          "cause multiple assignment to this object",
8509                          var_expr[n]->symtree->name, &code->expr1->where);
8510         }
8511     }
8512 }
8513
8514
8515 /* Resolve WHERE statement in FORALL construct.  */
8516
8517 static void
8518 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
8519                                   gfc_expr **var_expr)
8520 {
8521   gfc_code *cblock;
8522   gfc_code *cnext;
8523
8524   cblock = code->block;
8525   while (cblock)
8526     {
8527       /* the assignment statement of a WHERE statement, or the first
8528          statement in where-body-construct of a WHERE construct */
8529       cnext = cblock->next;
8530       while (cnext)
8531         {
8532           switch (cnext->op)
8533             {
8534             /* WHERE assignment statement */
8535             case EXEC_ASSIGN:
8536               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
8537               break;
8538   
8539             /* WHERE operator assignment statement */
8540             case EXEC_ASSIGN_CALL:
8541               resolve_call (cnext);
8542               if (!cnext->resolved_sym->attr.elemental)
8543                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8544                           &cnext->ext.actual->expr->where);
8545               break;
8546
8547             /* WHERE or WHERE construct is part of a where-body-construct */
8548             case EXEC_WHERE:
8549               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
8550               break;
8551
8552             default:
8553               gfc_error ("Unsupported statement inside WHERE at %L",
8554                          &cnext->loc);
8555             }
8556           /* the next statement within the same where-body-construct */
8557           cnext = cnext->next;
8558         }
8559       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8560       cblock = cblock->block;
8561     }
8562 }
8563
8564
8565 /* Traverse the FORALL body to check whether the following errors exist:
8566    1. For assignment, check if a many-to-one assignment happens.
8567    2. For WHERE statement, check the WHERE body to see if there is any
8568       many-to-one assignment.  */
8569
8570 static void
8571 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
8572 {
8573   gfc_code *c;
8574
8575   c = code->block->next;
8576   while (c)
8577     {
8578       switch (c->op)
8579         {
8580         case EXEC_ASSIGN:
8581         case EXEC_POINTER_ASSIGN:
8582           gfc_resolve_assign_in_forall (c, nvar, var_expr);
8583           break;
8584
8585         case EXEC_ASSIGN_CALL:
8586           resolve_call (c);
8587           break;
8588
8589         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
8590            there is no need to handle it here.  */
8591         case EXEC_FORALL:
8592           break;
8593         case EXEC_WHERE:
8594           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
8595           break;
8596         default:
8597           break;
8598         }
8599       /* The next statement in the FORALL body.  */
8600       c = c->next;
8601     }
8602 }
8603
8604
8605 /* Counts the number of iterators needed inside a forall construct, including
8606    nested forall constructs. This is used to allocate the needed memory 
8607    in gfc_resolve_forall.  */
8608
8609 static int 
8610 gfc_count_forall_iterators (gfc_code *code)
8611 {
8612   int max_iters, sub_iters, current_iters;
8613   gfc_forall_iterator *fa;
8614
8615   gcc_assert(code->op == EXEC_FORALL);
8616   max_iters = 0;
8617   current_iters = 0;
8618
8619   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8620     current_iters ++;
8621   
8622   code = code->block->next;
8623
8624   while (code)
8625     {          
8626       if (code->op == EXEC_FORALL)
8627         {
8628           sub_iters = gfc_count_forall_iterators (code);
8629           if (sub_iters > max_iters)
8630             max_iters = sub_iters;
8631         }
8632       code = code->next;
8633     }
8634
8635   return current_iters + max_iters;
8636 }
8637
8638
8639 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8640    gfc_resolve_forall_body to resolve the FORALL body.  */
8641
8642 static void
8643 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8644 {
8645   static gfc_expr **var_expr;
8646   static int total_var = 0;
8647   static int nvar = 0;
8648   int old_nvar, tmp;
8649   gfc_forall_iterator *fa;
8650   int i;
8651
8652   old_nvar = nvar;
8653
8654   /* Start to resolve a FORALL construct   */
8655   if (forall_save == 0)
8656     {
8657       /* Count the total number of FORALL index in the nested FORALL
8658          construct in order to allocate the VAR_EXPR with proper size.  */
8659       total_var = gfc_count_forall_iterators (code);
8660
8661       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8662       var_expr = XCNEWVEC (gfc_expr *, total_var);
8663     }
8664
8665   /* The information about FORALL iterator, including FORALL index start, end
8666      and stride. The FORALL index can not appear in start, end or stride.  */
8667   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8668     {
8669       /* Check if any outer FORALL index name is the same as the current
8670          one.  */
8671       for (i = 0; i < nvar; i++)
8672         {
8673           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8674             {
8675               gfc_error ("An outer FORALL construct already has an index "
8676                          "with this name %L", &fa->var->where);
8677             }
8678         }
8679
8680       /* Record the current FORALL index.  */
8681       var_expr[nvar] = gfc_copy_expr (fa->var);
8682
8683       nvar++;
8684
8685       /* No memory leak.  */
8686       gcc_assert (nvar <= total_var);
8687     }
8688
8689   /* Resolve the FORALL body.  */
8690   gfc_resolve_forall_body (code, nvar, var_expr);
8691
8692   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8693   gfc_resolve_blocks (code->block, ns);
8694
8695   tmp = nvar;
8696   nvar = old_nvar;
8697   /* Free only the VAR_EXPRs allocated in this frame.  */
8698   for (i = nvar; i < tmp; i++)
8699      gfc_free_expr (var_expr[i]);
8700
8701   if (nvar == 0)
8702     {
8703       /* We are in the outermost FORALL construct.  */
8704       gcc_assert (forall_save == 0);
8705
8706       /* VAR_EXPR is not needed any more.  */
8707       free (var_expr);
8708       total_var = 0;
8709     }
8710 }
8711
8712
8713 /* Resolve a BLOCK construct statement.  */
8714
8715 static void
8716 resolve_block_construct (gfc_code* code)
8717 {
8718   /* Resolve the BLOCK's namespace.  */
8719   gfc_resolve (code->ext.block.ns);
8720
8721   /* For an ASSOCIATE block, the associations (and their targets) are already
8722      resolved during resolve_symbol.  */
8723 }
8724
8725
8726 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
8727    DO code nodes.  */
8728
8729 static void resolve_code (gfc_code *, gfc_namespace *);
8730
8731 void
8732 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8733 {
8734   gfc_try t;
8735
8736   for (; b; b = b->block)
8737     {
8738       t = gfc_resolve_expr (b->expr1);
8739       if (gfc_resolve_expr (b->expr2) == FAILURE)
8740         t = FAILURE;
8741
8742       switch (b->op)
8743         {
8744         case EXEC_IF:
8745           if (t == SUCCESS && b->expr1 != NULL
8746               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8747             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8748                        &b->expr1->where);
8749           break;
8750
8751         case EXEC_WHERE:
8752           if (t == SUCCESS
8753               && b->expr1 != NULL
8754               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8755             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8756                        &b->expr1->where);
8757           break;
8758
8759         case EXEC_GOTO:
8760           resolve_branch (b->label1, b);
8761           break;
8762
8763         case EXEC_BLOCK:
8764           resolve_block_construct (b);
8765           break;
8766
8767         case EXEC_SELECT:
8768         case EXEC_SELECT_TYPE:
8769         case EXEC_FORALL:
8770         case EXEC_DO:
8771         case EXEC_DO_WHILE:
8772         case EXEC_CRITICAL:
8773         case EXEC_READ:
8774         case EXEC_WRITE:
8775         case EXEC_IOLENGTH:
8776         case EXEC_WAIT:
8777           break;
8778
8779         case EXEC_OMP_ATOMIC:
8780         case EXEC_OMP_CRITICAL:
8781         case EXEC_OMP_DO:
8782         case EXEC_OMP_MASTER:
8783         case EXEC_OMP_ORDERED:
8784         case EXEC_OMP_PARALLEL:
8785         case EXEC_OMP_PARALLEL_DO:
8786         case EXEC_OMP_PARALLEL_SECTIONS:
8787         case EXEC_OMP_PARALLEL_WORKSHARE:
8788         case EXEC_OMP_SECTIONS:
8789         case EXEC_OMP_SINGLE:
8790         case EXEC_OMP_TASK:
8791         case EXEC_OMP_TASKWAIT:
8792         case EXEC_OMP_WORKSHARE:
8793           break;
8794
8795         default:
8796           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
8797         }
8798
8799       resolve_code (b->next, ns);
8800     }
8801 }
8802
8803
8804 /* Does everything to resolve an ordinary assignment.  Returns true
8805    if this is an interface assignment.  */
8806 static bool
8807 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
8808 {
8809   bool rval = false;
8810   gfc_expr *lhs;
8811   gfc_expr *rhs;
8812   int llen = 0;
8813   int rlen = 0;
8814   int n;
8815   gfc_ref *ref;
8816
8817   if (gfc_extend_assign (code, ns) == SUCCESS)
8818     {
8819       gfc_expr** rhsptr;
8820
8821       if (code->op == EXEC_ASSIGN_CALL)
8822         {
8823           lhs = code->ext.actual->expr;
8824           rhsptr = &code->ext.actual->next->expr;
8825         }
8826       else
8827         {
8828           gfc_actual_arglist* args;
8829           gfc_typebound_proc* tbp;
8830
8831           gcc_assert (code->op == EXEC_COMPCALL);
8832
8833           args = code->expr1->value.compcall.actual;
8834           lhs = args->expr;
8835           rhsptr = &args->next->expr;
8836
8837           tbp = code->expr1->value.compcall.tbp;
8838           gcc_assert (!tbp->is_generic);
8839         }
8840
8841       /* Make a temporary rhs when there is a default initializer
8842          and rhs is the same symbol as the lhs.  */
8843       if ((*rhsptr)->expr_type == EXPR_VARIABLE
8844             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
8845             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
8846             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
8847         *rhsptr = gfc_get_parentheses (*rhsptr);
8848
8849       return true;
8850     }
8851
8852   lhs = code->expr1;
8853   rhs = code->expr2;
8854
8855   if (rhs->is_boz
8856       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
8857                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
8858                          &code->loc) == FAILURE)
8859     return false;
8860
8861   /* Handle the case of a BOZ literal on the RHS.  */
8862   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
8863     {
8864       int rc;
8865       if (gfc_option.warn_surprising)
8866         gfc_warning ("BOZ literal at %L is bitwise transferred "
8867                      "non-integer symbol '%s'", &code->loc,
8868                      lhs->symtree->n.sym->name);
8869
8870       if (!gfc_convert_boz (rhs, &lhs->ts))
8871         return false;
8872       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
8873         {
8874           if (rc == ARITH_UNDERFLOW)
8875             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
8876                        ". This check can be disabled with the option "
8877                        "-fno-range-check", &rhs->where);
8878           else if (rc == ARITH_OVERFLOW)
8879             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
8880                        ". This check can be disabled with the option "
8881                        "-fno-range-check", &rhs->where);
8882           else if (rc == ARITH_NAN)
8883             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
8884                        ". This check can be disabled with the option "
8885                        "-fno-range-check", &rhs->where);
8886           return false;
8887         }
8888     }
8889
8890   if (lhs->ts.type == BT_CHARACTER
8891         && gfc_option.warn_character_truncation)
8892     {
8893       if (lhs->ts.u.cl != NULL
8894             && lhs->ts.u.cl->length != NULL
8895             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8896         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
8897
8898       if (rhs->expr_type == EXPR_CONSTANT)
8899         rlen = rhs->value.character.length;
8900
8901       else if (rhs->ts.u.cl != NULL
8902                  && rhs->ts.u.cl->length != NULL
8903                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8904         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
8905
8906       if (rlen && llen && rlen > llen)
8907         gfc_warning_now ("CHARACTER expression will be truncated "
8908                          "in assignment (%d/%d) at %L",
8909                          llen, rlen, &code->loc);
8910     }
8911
8912   /* Ensure that a vector index expression for the lvalue is evaluated
8913      to a temporary if the lvalue symbol is referenced in it.  */
8914   if (lhs->rank)
8915     {
8916       for (ref = lhs->ref; ref; ref= ref->next)
8917         if (ref->type == REF_ARRAY)
8918           {
8919             for (n = 0; n < ref->u.ar.dimen; n++)
8920               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
8921                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
8922                                            ref->u.ar.start[n]))
8923                 ref->u.ar.start[n]
8924                         = gfc_get_parentheses (ref->u.ar.start[n]);
8925           }
8926     }
8927
8928   if (gfc_pure (NULL))
8929     {
8930       if (lhs->ts.type == BT_DERIVED
8931             && lhs->expr_type == EXPR_VARIABLE
8932             && lhs->ts.u.derived->attr.pointer_comp
8933             && rhs->expr_type == EXPR_VARIABLE
8934             && (gfc_impure_variable (rhs->symtree->n.sym)
8935                 || gfc_is_coindexed (rhs)))
8936         {
8937           /* F2008, C1283.  */
8938           if (gfc_is_coindexed (rhs))
8939             gfc_error ("Coindexed expression at %L is assigned to "
8940                         "a derived type variable with a POINTER "
8941                         "component in a PURE procedure",
8942                         &rhs->where);
8943           else
8944             gfc_error ("The impure variable at %L is assigned to "
8945                         "a derived type variable with a POINTER "
8946                         "component in a PURE procedure (12.6)",
8947                         &rhs->where);
8948           return rval;
8949         }
8950
8951       /* Fortran 2008, C1283.  */
8952       if (gfc_is_coindexed (lhs))
8953         {
8954           gfc_error ("Assignment to coindexed variable at %L in a PURE "
8955                      "procedure", &rhs->where);
8956           return rval;
8957         }
8958     }
8959
8960   if (gfc_implicit_pure (NULL))
8961     {
8962       if (lhs->expr_type == EXPR_VARIABLE
8963             && lhs->symtree->n.sym != gfc_current_ns->proc_name
8964             && lhs->symtree->n.sym->ns != gfc_current_ns)
8965         gfc_current_ns->proc_name->attr.implicit_pure = 0;
8966
8967       if (lhs->ts.type == BT_DERIVED
8968             && lhs->expr_type == EXPR_VARIABLE
8969             && lhs->ts.u.derived->attr.pointer_comp
8970             && rhs->expr_type == EXPR_VARIABLE
8971             && (gfc_impure_variable (rhs->symtree->n.sym)
8972                 || gfc_is_coindexed (rhs)))
8973         gfc_current_ns->proc_name->attr.implicit_pure = 0;
8974
8975       /* Fortran 2008, C1283.  */
8976       if (gfc_is_coindexed (lhs))
8977         gfc_current_ns->proc_name->attr.implicit_pure = 0;
8978     }
8979
8980   /* F03:7.4.1.2.  */
8981   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
8982      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
8983   if (lhs->ts.type == BT_CLASS)
8984     {
8985       gfc_error ("Variable must not be polymorphic in assignment at %L",
8986                  &lhs->where);
8987       return false;
8988     }
8989
8990   /* F2008, Section 7.2.1.2.  */
8991   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
8992     {
8993       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
8994                  "component in assignment at %L", &lhs->where);
8995       return false;
8996     }
8997
8998   gfc_check_assign (lhs, rhs, 1);
8999   return false;
9000 }
9001
9002
9003 /* Given a block of code, recursively resolve everything pointed to by this
9004    code block.  */
9005
9006 static void
9007 resolve_code (gfc_code *code, gfc_namespace *ns)
9008 {
9009   int omp_workshare_save;
9010   int forall_save;
9011   code_stack frame;
9012   gfc_try t;
9013
9014   frame.prev = cs_base;
9015   frame.head = code;
9016   cs_base = &frame;
9017
9018   find_reachable_labels (code);
9019
9020   for (; code; code = code->next)
9021     {
9022       frame.current = code;
9023       forall_save = forall_flag;
9024
9025       if (code->op == EXEC_FORALL)
9026         {
9027           forall_flag = 1;
9028           gfc_resolve_forall (code, ns, forall_save);
9029           forall_flag = 2;
9030         }
9031       else if (code->block)
9032         {
9033           omp_workshare_save = -1;
9034           switch (code->op)
9035             {
9036             case EXEC_OMP_PARALLEL_WORKSHARE:
9037               omp_workshare_save = omp_workshare_flag;
9038               omp_workshare_flag = 1;
9039               gfc_resolve_omp_parallel_blocks (code, ns);
9040               break;
9041             case EXEC_OMP_PARALLEL:
9042             case EXEC_OMP_PARALLEL_DO:
9043             case EXEC_OMP_PARALLEL_SECTIONS:
9044             case EXEC_OMP_TASK:
9045               omp_workshare_save = omp_workshare_flag;
9046               omp_workshare_flag = 0;
9047               gfc_resolve_omp_parallel_blocks (code, ns);
9048               break;
9049             case EXEC_OMP_DO:
9050               gfc_resolve_omp_do_blocks (code, ns);
9051               break;
9052             case EXEC_SELECT_TYPE:
9053               /* Blocks are handled in resolve_select_type because we have
9054                  to transform the SELECT TYPE into ASSOCIATE first.  */
9055               break;
9056             case EXEC_OMP_WORKSHARE:
9057               omp_workshare_save = omp_workshare_flag;
9058               omp_workshare_flag = 1;
9059               /* FALLTHROUGH */
9060             default:
9061               gfc_resolve_blocks (code->block, ns);
9062               break;
9063             }
9064
9065           if (omp_workshare_save != -1)
9066             omp_workshare_flag = omp_workshare_save;
9067         }
9068
9069       t = SUCCESS;
9070       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
9071         t = gfc_resolve_expr (code->expr1);
9072       forall_flag = forall_save;
9073
9074       if (gfc_resolve_expr (code->expr2) == FAILURE)
9075         t = FAILURE;
9076
9077       if (code->op == EXEC_ALLOCATE
9078           && gfc_resolve_expr (code->expr3) == FAILURE)
9079         t = FAILURE;
9080
9081       switch (code->op)
9082         {
9083         case EXEC_NOP:
9084         case EXEC_END_BLOCK:
9085         case EXEC_CYCLE:
9086         case EXEC_PAUSE:
9087         case EXEC_STOP:
9088         case EXEC_ERROR_STOP:
9089         case EXEC_EXIT:
9090         case EXEC_CONTINUE:
9091         case EXEC_DT_END:
9092         case EXEC_ASSIGN_CALL:
9093         case EXEC_CRITICAL:
9094           break;
9095
9096         case EXEC_SYNC_ALL:
9097         case EXEC_SYNC_IMAGES:
9098         case EXEC_SYNC_MEMORY:
9099           resolve_sync (code);
9100           break;
9101
9102         case EXEC_LOCK:
9103         case EXEC_UNLOCK:
9104           resolve_lock_unlock (code);
9105           break;
9106
9107         case EXEC_ENTRY:
9108           /* Keep track of which entry we are up to.  */
9109           current_entry_id = code->ext.entry->id;
9110           break;
9111
9112         case EXEC_WHERE:
9113           resolve_where (code, NULL);
9114           break;
9115
9116         case EXEC_GOTO:
9117           if (code->expr1 != NULL)
9118             {
9119               if (code->expr1->ts.type != BT_INTEGER)
9120                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
9121                            "INTEGER variable", &code->expr1->where);
9122               else if (code->expr1->symtree->n.sym->attr.assign != 1)
9123                 gfc_error ("Variable '%s' has not been assigned a target "
9124                            "label at %L", code->expr1->symtree->n.sym->name,
9125                            &code->expr1->where);
9126             }
9127           else
9128             resolve_branch (code->label1, code);
9129           break;
9130
9131         case EXEC_RETURN:
9132           if (code->expr1 != NULL
9133                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
9134             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
9135                        "INTEGER return specifier", &code->expr1->where);
9136           break;
9137
9138         case EXEC_INIT_ASSIGN:
9139         case EXEC_END_PROCEDURE:
9140           break;
9141
9142         case EXEC_ASSIGN:
9143           if (t == FAILURE)
9144             break;
9145
9146           if (gfc_check_vardef_context (code->expr1, false, _("assignment"))
9147                 == FAILURE)
9148             break;
9149
9150           if (resolve_ordinary_assign (code, ns))
9151             {
9152               if (code->op == EXEC_COMPCALL)
9153                 goto compcall;
9154               else
9155                 goto call;
9156             }
9157           break;
9158
9159         case EXEC_LABEL_ASSIGN:
9160           if (code->label1->defined == ST_LABEL_UNKNOWN)
9161             gfc_error ("Label %d referenced at %L is never defined",
9162                        code->label1->value, &code->label1->where);
9163           if (t == SUCCESS
9164               && (code->expr1->expr_type != EXPR_VARIABLE
9165                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
9166                   || code->expr1->symtree->n.sym->ts.kind
9167                      != gfc_default_integer_kind
9168                   || code->expr1->symtree->n.sym->as != NULL))
9169             gfc_error ("ASSIGN statement at %L requires a scalar "
9170                        "default INTEGER variable", &code->expr1->where);
9171           break;
9172
9173         case EXEC_POINTER_ASSIGN:
9174           {
9175             gfc_expr* e;
9176
9177             if (t == FAILURE)
9178               break;
9179
9180             /* This is both a variable definition and pointer assignment
9181                context, so check both of them.  For rank remapping, a final
9182                array ref may be present on the LHS and fool gfc_expr_attr
9183                used in gfc_check_vardef_context.  Remove it.  */
9184             e = remove_last_array_ref (code->expr1);
9185             t = gfc_check_vardef_context (e, true, _("pointer assignment"));
9186             if (t == SUCCESS)
9187               t = gfc_check_vardef_context (e, false, _("pointer assignment"));
9188             gfc_free_expr (e);
9189             if (t == FAILURE)
9190               break;
9191
9192             gfc_check_pointer_assign (code->expr1, code->expr2);
9193             break;
9194           }
9195
9196         case EXEC_ARITHMETIC_IF:
9197           if (t == SUCCESS
9198               && code->expr1->ts.type != BT_INTEGER
9199               && code->expr1->ts.type != BT_REAL)
9200             gfc_error ("Arithmetic IF statement at %L requires a numeric "
9201                        "expression", &code->expr1->where);
9202
9203           resolve_branch (code->label1, code);
9204           resolve_branch (code->label2, code);
9205           resolve_branch (code->label3, code);
9206           break;
9207
9208         case EXEC_IF:
9209           if (t == SUCCESS && code->expr1 != NULL
9210               && (code->expr1->ts.type != BT_LOGICAL
9211                   || code->expr1->rank != 0))
9212             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9213                        &code->expr1->where);
9214           break;
9215
9216         case EXEC_CALL:
9217         call:
9218           resolve_call (code);
9219           break;
9220
9221         case EXEC_COMPCALL:
9222         compcall:
9223           resolve_typebound_subroutine (code);
9224           break;
9225
9226         case EXEC_CALL_PPC:
9227           resolve_ppc_call (code);
9228           break;
9229
9230         case EXEC_SELECT:
9231           /* Select is complicated. Also, a SELECT construct could be
9232              a transformed computed GOTO.  */
9233           resolve_select (code);
9234           break;
9235
9236         case EXEC_SELECT_TYPE:
9237           resolve_select_type (code, ns);
9238           break;
9239
9240         case EXEC_BLOCK:
9241           resolve_block_construct (code);
9242           break;
9243
9244         case EXEC_DO:
9245           if (code->ext.iterator != NULL)
9246             {
9247               gfc_iterator *iter = code->ext.iterator;
9248               if (gfc_resolve_iterator (iter, true) != FAILURE)
9249                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
9250             }
9251           break;
9252
9253         case EXEC_DO_WHILE:
9254           if (code->expr1 == NULL)
9255             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
9256           if (t == SUCCESS
9257               && (code->expr1->rank != 0
9258                   || code->expr1->ts.type != BT_LOGICAL))
9259             gfc_error ("Exit condition of DO WHILE loop at %L must be "
9260                        "a scalar LOGICAL expression", &code->expr1->where);
9261           break;
9262
9263         case EXEC_ALLOCATE:
9264           if (t == SUCCESS)
9265             resolve_allocate_deallocate (code, "ALLOCATE");
9266
9267           break;
9268
9269         case EXEC_DEALLOCATE:
9270           if (t == SUCCESS)
9271             resolve_allocate_deallocate (code, "DEALLOCATE");
9272
9273           break;
9274
9275         case EXEC_OPEN:
9276           if (gfc_resolve_open (code->ext.open) == FAILURE)
9277             break;
9278
9279           resolve_branch (code->ext.open->err, code);
9280           break;
9281
9282         case EXEC_CLOSE:
9283           if (gfc_resolve_close (code->ext.close) == FAILURE)
9284             break;
9285
9286           resolve_branch (code->ext.close->err, code);
9287           break;
9288
9289         case EXEC_BACKSPACE:
9290         case EXEC_ENDFILE:
9291         case EXEC_REWIND:
9292         case EXEC_FLUSH:
9293           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
9294             break;
9295
9296           resolve_branch (code->ext.filepos->err, code);
9297           break;
9298
9299         case EXEC_INQUIRE:
9300           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9301               break;
9302
9303           resolve_branch (code->ext.inquire->err, code);
9304           break;
9305
9306         case EXEC_IOLENGTH:
9307           gcc_assert (code->ext.inquire != NULL);
9308           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9309             break;
9310
9311           resolve_branch (code->ext.inquire->err, code);
9312           break;
9313
9314         case EXEC_WAIT:
9315           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
9316             break;
9317
9318           resolve_branch (code->ext.wait->err, code);
9319           resolve_branch (code->ext.wait->end, code);
9320           resolve_branch (code->ext.wait->eor, code);
9321           break;
9322
9323         case EXEC_READ:
9324         case EXEC_WRITE:
9325           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
9326             break;
9327
9328           resolve_branch (code->ext.dt->err, code);
9329           resolve_branch (code->ext.dt->end, code);
9330           resolve_branch (code->ext.dt->eor, code);
9331           break;
9332
9333         case EXEC_TRANSFER:
9334           resolve_transfer (code);
9335           break;
9336
9337         case EXEC_FORALL:
9338           resolve_forall_iterators (code->ext.forall_iterator);
9339
9340           if (code->expr1 != NULL
9341               && (code->expr1->ts.type != BT_LOGICAL || code->expr1->rank))
9342             gfc_error ("FORALL mask clause at %L requires a scalar LOGICAL "
9343                        "expression", &code->expr1->where);
9344           break;
9345
9346         case EXEC_OMP_ATOMIC:
9347         case EXEC_OMP_BARRIER:
9348         case EXEC_OMP_CRITICAL:
9349         case EXEC_OMP_FLUSH:
9350         case EXEC_OMP_DO:
9351         case EXEC_OMP_MASTER:
9352         case EXEC_OMP_ORDERED:
9353         case EXEC_OMP_SECTIONS:
9354         case EXEC_OMP_SINGLE:
9355         case EXEC_OMP_TASKWAIT:
9356         case EXEC_OMP_WORKSHARE:
9357           gfc_resolve_omp_directive (code, ns);
9358           break;
9359
9360         case EXEC_OMP_PARALLEL:
9361         case EXEC_OMP_PARALLEL_DO:
9362         case EXEC_OMP_PARALLEL_SECTIONS:
9363         case EXEC_OMP_PARALLEL_WORKSHARE:
9364         case EXEC_OMP_TASK:
9365           omp_workshare_save = omp_workshare_flag;
9366           omp_workshare_flag = 0;
9367           gfc_resolve_omp_directive (code, ns);
9368           omp_workshare_flag = omp_workshare_save;
9369           break;
9370
9371         default:
9372           gfc_internal_error ("resolve_code(): Bad statement code");
9373         }
9374     }
9375
9376   cs_base = frame.prev;
9377 }
9378
9379
9380 /* Resolve initial values and make sure they are compatible with
9381    the variable.  */
9382
9383 static void
9384 resolve_values (gfc_symbol *sym)
9385 {
9386   gfc_try t;
9387
9388   if (sym->value == NULL)
9389     return;
9390
9391   if (sym->value->expr_type == EXPR_STRUCTURE)
9392     t= resolve_structure_cons (sym->value, 1);
9393   else 
9394     t = gfc_resolve_expr (sym->value);
9395
9396   if (t == FAILURE)
9397     return;
9398
9399   gfc_check_assign_symbol (sym, sym->value);
9400 }
9401
9402
9403 /* Verify the binding labels for common blocks that are BIND(C).  The label
9404    for a BIND(C) common block must be identical in all scoping units in which
9405    the common block is declared.  Further, the binding label can not collide
9406    with any other global entity in the program.  */
9407
9408 static void
9409 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
9410 {
9411   if (comm_block_tree->n.common->is_bind_c == 1)
9412     {
9413       gfc_gsymbol *binding_label_gsym;
9414       gfc_gsymbol *comm_name_gsym;
9415
9416       /* See if a global symbol exists by the common block's name.  It may
9417          be NULL if the common block is use-associated.  */
9418       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
9419                                          comm_block_tree->n.common->name);
9420       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
9421         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
9422                    "with the global entity '%s' at %L",
9423                    comm_block_tree->n.common->binding_label,
9424                    comm_block_tree->n.common->name,
9425                    &(comm_block_tree->n.common->where),
9426                    comm_name_gsym->name, &(comm_name_gsym->where));
9427       else if (comm_name_gsym != NULL
9428                && strcmp (comm_name_gsym->name,
9429                           comm_block_tree->n.common->name) == 0)
9430         {
9431           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
9432              as expected.  */
9433           if (comm_name_gsym->binding_label == NULL)
9434             /* No binding label for common block stored yet; save this one.  */
9435             comm_name_gsym->binding_label =
9436               comm_block_tree->n.common->binding_label;
9437           else
9438             if (strcmp (comm_name_gsym->binding_label,
9439                         comm_block_tree->n.common->binding_label) != 0)
9440               {
9441                 /* Common block names match but binding labels do not.  */
9442                 gfc_error ("Binding label '%s' for common block '%s' at %L "
9443                            "does not match the binding label '%s' for common "
9444                            "block '%s' at %L",
9445                            comm_block_tree->n.common->binding_label,
9446                            comm_block_tree->n.common->name,
9447                            &(comm_block_tree->n.common->where),
9448                            comm_name_gsym->binding_label,
9449                            comm_name_gsym->name,
9450                            &(comm_name_gsym->where));
9451                 return;
9452               }
9453         }
9454
9455       /* There is no binding label (NAME="") so we have nothing further to
9456          check and nothing to add as a global symbol for the label.  */
9457       if (comm_block_tree->n.common->binding_label[0] == '\0' )
9458         return;
9459       
9460       binding_label_gsym =
9461         gfc_find_gsymbol (gfc_gsym_root,
9462                           comm_block_tree->n.common->binding_label);
9463       if (binding_label_gsym == NULL)
9464         {
9465           /* Need to make a global symbol for the binding label to prevent
9466              it from colliding with another.  */
9467           binding_label_gsym =
9468             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
9469           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
9470           binding_label_gsym->type = GSYM_COMMON;
9471         }
9472       else
9473         {
9474           /* If comm_name_gsym is NULL, the name common block is use
9475              associated and the name could be colliding.  */
9476           if (binding_label_gsym->type != GSYM_COMMON)
9477             gfc_error ("Binding label '%s' for common block '%s' at %L "
9478                        "collides with the global entity '%s' at %L",
9479                        comm_block_tree->n.common->binding_label,
9480                        comm_block_tree->n.common->name,
9481                        &(comm_block_tree->n.common->where),
9482                        binding_label_gsym->name,
9483                        &(binding_label_gsym->where));
9484           else if (comm_name_gsym != NULL
9485                    && (strcmp (binding_label_gsym->name,
9486                                comm_name_gsym->binding_label) != 0)
9487                    && (strcmp (binding_label_gsym->sym_name,
9488                                comm_name_gsym->name) != 0))
9489             gfc_error ("Binding label '%s' for common block '%s' at %L "
9490                        "collides with global entity '%s' at %L",
9491                        binding_label_gsym->name, binding_label_gsym->sym_name,
9492                        &(comm_block_tree->n.common->where),
9493                        comm_name_gsym->name, &(comm_name_gsym->where));
9494         }
9495     }
9496   
9497   return;
9498 }
9499
9500
9501 /* Verify any BIND(C) derived types in the namespace so we can report errors
9502    for them once, rather than for each variable declared of that type.  */
9503
9504 static void
9505 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
9506 {
9507   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
9508       && derived_sym->attr.is_bind_c == 1)
9509     verify_bind_c_derived_type (derived_sym);
9510   
9511   return;
9512 }
9513
9514
9515 /* Verify that any binding labels used in a given namespace do not collide 
9516    with the names or binding labels of any global symbols.  */
9517
9518 static void
9519 gfc_verify_binding_labels (gfc_symbol *sym)
9520 {
9521   int has_error = 0;
9522   
9523   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
9524       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
9525     {
9526       gfc_gsymbol *bind_c_sym;
9527
9528       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
9529       if (bind_c_sym != NULL 
9530           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
9531         {
9532           if (sym->attr.if_source == IFSRC_DECL 
9533               && (bind_c_sym->type != GSYM_SUBROUTINE 
9534                   && bind_c_sym->type != GSYM_FUNCTION) 
9535               && ((sym->attr.contained == 1 
9536                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
9537                   || (sym->attr.use_assoc == 1 
9538                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
9539             {
9540               /* Make sure global procedures don't collide with anything.  */
9541               gfc_error ("Binding label '%s' at %L collides with the global "
9542                          "entity '%s' at %L", sym->binding_label,
9543                          &(sym->declared_at), bind_c_sym->name,
9544                          &(bind_c_sym->where));
9545               has_error = 1;
9546             }
9547           else if (sym->attr.contained == 0 
9548                    && (sym->attr.if_source == IFSRC_IFBODY 
9549                        && sym->attr.flavor == FL_PROCEDURE) 
9550                    && (bind_c_sym->sym_name != NULL 
9551                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
9552             {
9553               /* Make sure procedures in interface bodies don't collide.  */
9554               gfc_error ("Binding label '%s' in interface body at %L collides "
9555                          "with the global entity '%s' at %L",
9556                          sym->binding_label,
9557                          &(sym->declared_at), bind_c_sym->name,
9558                          &(bind_c_sym->where));
9559               has_error = 1;
9560             }
9561           else if (sym->attr.contained == 0 
9562                    && sym->attr.if_source == IFSRC_UNKNOWN)
9563             if ((sym->attr.use_assoc && bind_c_sym->mod_name
9564                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
9565                 || sym->attr.use_assoc == 0)
9566               {
9567                 gfc_error ("Binding label '%s' at %L collides with global "
9568                            "entity '%s' at %L", sym->binding_label,
9569                            &(sym->declared_at), bind_c_sym->name,
9570                            &(bind_c_sym->where));
9571                 has_error = 1;
9572               }
9573
9574           if (has_error != 0)
9575             /* Clear the binding label to prevent checking multiple times.  */
9576             sym->binding_label[0] = '\0';
9577         }
9578       else if (bind_c_sym == NULL)
9579         {
9580           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
9581           bind_c_sym->where = sym->declared_at;
9582           bind_c_sym->sym_name = sym->name;
9583
9584           if (sym->attr.use_assoc == 1)
9585             bind_c_sym->mod_name = sym->module;
9586           else
9587             if (sym->ns->proc_name != NULL)
9588               bind_c_sym->mod_name = sym->ns->proc_name->name;
9589
9590           if (sym->attr.contained == 0)
9591             {
9592               if (sym->attr.subroutine)
9593                 bind_c_sym->type = GSYM_SUBROUTINE;
9594               else if (sym->attr.function)
9595                 bind_c_sym->type = GSYM_FUNCTION;
9596             }
9597         }
9598     }
9599   return;
9600 }
9601
9602
9603 /* Resolve an index expression.  */
9604
9605 static gfc_try
9606 resolve_index_expr (gfc_expr *e)
9607 {
9608   if (gfc_resolve_expr (e) == FAILURE)
9609     return FAILURE;
9610
9611   if (gfc_simplify_expr (e, 0) == FAILURE)
9612     return FAILURE;
9613
9614   if (gfc_specification_expr (e) == FAILURE)
9615     return FAILURE;
9616
9617   return SUCCESS;
9618 }
9619
9620
9621 /* Resolve a charlen structure.  */
9622
9623 static gfc_try
9624 resolve_charlen (gfc_charlen *cl)
9625 {
9626   int i, k;
9627
9628   if (cl->resolved)
9629     return SUCCESS;
9630
9631   cl->resolved = 1;
9632
9633   specification_expr = 1;
9634
9635   if (resolve_index_expr (cl->length) == FAILURE)
9636     {
9637       specification_expr = 0;
9638       return FAILURE;
9639     }
9640
9641   /* "If the character length parameter value evaluates to a negative
9642      value, the length of character entities declared is zero."  */
9643   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
9644     {
9645       if (gfc_option.warn_surprising)
9646         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
9647                          " the length has been set to zero",
9648                          &cl->length->where, i);
9649       gfc_replace_expr (cl->length,
9650                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
9651     }
9652
9653   /* Check that the character length is not too large.  */
9654   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
9655   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
9656       && cl->length->ts.type == BT_INTEGER
9657       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
9658     {
9659       gfc_error ("String length at %L is too large", &cl->length->where);
9660       return FAILURE;
9661     }
9662
9663   return SUCCESS;
9664 }
9665
9666
9667 /* Test for non-constant shape arrays.  */
9668
9669 static bool
9670 is_non_constant_shape_array (gfc_symbol *sym)
9671 {
9672   gfc_expr *e;
9673   int i;
9674   bool not_constant;
9675
9676   not_constant = false;
9677   if (sym->as != NULL)
9678     {
9679       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
9680          has not been simplified; parameter array references.  Do the
9681          simplification now.  */
9682       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
9683         {
9684           e = sym->as->lower[i];
9685           if (e && (resolve_index_expr (e) == FAILURE
9686                     || !gfc_is_constant_expr (e)))
9687             not_constant = true;
9688           e = sym->as->upper[i];
9689           if (e && (resolve_index_expr (e) == FAILURE
9690                     || !gfc_is_constant_expr (e)))
9691             not_constant = true;
9692         }
9693     }
9694   return not_constant;
9695 }
9696
9697 /* Given a symbol and an initialization expression, add code to initialize
9698    the symbol to the function entry.  */
9699 static void
9700 build_init_assign (gfc_symbol *sym, gfc_expr *init)
9701 {
9702   gfc_expr *lval;
9703   gfc_code *init_st;
9704   gfc_namespace *ns = sym->ns;
9705
9706   /* Search for the function namespace if this is a contained
9707      function without an explicit result.  */
9708   if (sym->attr.function && sym == sym->result
9709       && sym->name != sym->ns->proc_name->name)
9710     {
9711       ns = ns->contained;
9712       for (;ns; ns = ns->sibling)
9713         if (strcmp (ns->proc_name->name, sym->name) == 0)
9714           break;
9715     }
9716
9717   if (ns == NULL)
9718     {
9719       gfc_free_expr (init);
9720       return;
9721     }
9722
9723   /* Build an l-value expression for the result.  */
9724   lval = gfc_lval_expr_from_sym (sym);
9725
9726   /* Add the code at scope entry.  */
9727   init_st = gfc_get_code ();
9728   init_st->next = ns->code;
9729   ns->code = init_st;
9730
9731   /* Assign the default initializer to the l-value.  */
9732   init_st->loc = sym->declared_at;
9733   init_st->op = EXEC_INIT_ASSIGN;
9734   init_st->expr1 = lval;
9735   init_st->expr2 = init;
9736 }
9737
9738 /* Assign the default initializer to a derived type variable or result.  */
9739
9740 static void
9741 apply_default_init (gfc_symbol *sym)
9742 {
9743   gfc_expr *init = NULL;
9744
9745   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9746     return;
9747
9748   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
9749     init = gfc_default_initializer (&sym->ts);
9750
9751   if (init == NULL && sym->ts.type != BT_CLASS)
9752     return;
9753
9754   build_init_assign (sym, init);
9755   sym->attr.referenced = 1;
9756 }
9757
9758 /* Build an initializer for a local integer, real, complex, logical, or
9759    character variable, based on the command line flags finit-local-zero,
9760    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
9761    null if the symbol should not have a default initialization.  */
9762 static gfc_expr *
9763 build_default_init_expr (gfc_symbol *sym)
9764 {
9765   int char_len;
9766   gfc_expr *init_expr;
9767   int i;
9768
9769   /* These symbols should never have a default initialization.  */
9770   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
9771       || sym->attr.external
9772       || sym->attr.dummy
9773       || sym->attr.pointer
9774       || sym->attr.in_equivalence
9775       || sym->attr.in_common
9776       || sym->attr.data
9777       || sym->module
9778       || sym->attr.cray_pointee
9779       || sym->attr.cray_pointer)
9780     return NULL;
9781
9782   /* Now we'll try to build an initializer expression.  */
9783   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
9784                                      &sym->declared_at);
9785
9786   /* We will only initialize integers, reals, complex, logicals, and
9787      characters, and only if the corresponding command-line flags
9788      were set.  Otherwise, we free init_expr and return null.  */
9789   switch (sym->ts.type)
9790     {    
9791     case BT_INTEGER:
9792       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
9793         mpz_set_si (init_expr->value.integer, 
9794                          gfc_option.flag_init_integer_value);
9795       else
9796         {
9797           gfc_free_expr (init_expr);
9798           init_expr = NULL;
9799         }
9800       break;
9801
9802     case BT_REAL:
9803       switch (gfc_option.flag_init_real)
9804         {
9805         case GFC_INIT_REAL_SNAN:
9806           init_expr->is_snan = 1;
9807           /* Fall through.  */
9808         case GFC_INIT_REAL_NAN:
9809           mpfr_set_nan (init_expr->value.real);
9810           break;
9811
9812         case GFC_INIT_REAL_INF:
9813           mpfr_set_inf (init_expr->value.real, 1);
9814           break;
9815
9816         case GFC_INIT_REAL_NEG_INF:
9817           mpfr_set_inf (init_expr->value.real, -1);
9818           break;
9819
9820         case GFC_INIT_REAL_ZERO:
9821           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
9822           break;
9823
9824         default:
9825           gfc_free_expr (init_expr);
9826           init_expr = NULL;
9827           break;
9828         }
9829       break;
9830           
9831     case BT_COMPLEX:
9832       switch (gfc_option.flag_init_real)
9833         {
9834         case GFC_INIT_REAL_SNAN:
9835           init_expr->is_snan = 1;
9836           /* Fall through.  */
9837         case GFC_INIT_REAL_NAN:
9838           mpfr_set_nan (mpc_realref (init_expr->value.complex));
9839           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
9840           break;
9841
9842         case GFC_INIT_REAL_INF:
9843           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
9844           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
9845           break;
9846
9847         case GFC_INIT_REAL_NEG_INF:
9848           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
9849           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
9850           break;
9851
9852         case GFC_INIT_REAL_ZERO:
9853           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
9854           break;
9855
9856         default:
9857           gfc_free_expr (init_expr);
9858           init_expr = NULL;
9859           break;
9860         }
9861       break;
9862           
9863     case BT_LOGICAL:
9864       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
9865         init_expr->value.logical = 0;
9866       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
9867         init_expr->value.logical = 1;
9868       else
9869         {
9870           gfc_free_expr (init_expr);
9871           init_expr = NULL;
9872         }
9873       break;
9874           
9875     case BT_CHARACTER:
9876       /* For characters, the length must be constant in order to 
9877          create a default initializer.  */
9878       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
9879           && sym->ts.u.cl->length
9880           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9881         {
9882           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
9883           init_expr->value.character.length = char_len;
9884           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
9885           for (i = 0; i < char_len; i++)
9886             init_expr->value.character.string[i]
9887               = (unsigned char) gfc_option.flag_init_character_value;
9888         }
9889       else
9890         {
9891           gfc_free_expr (init_expr);
9892           init_expr = NULL;
9893         }
9894       break;
9895           
9896     default:
9897      gfc_free_expr (init_expr);
9898      init_expr = NULL;
9899     }
9900   return init_expr;
9901 }
9902
9903 /* Add an initialization expression to a local variable.  */
9904 static void
9905 apply_default_init_local (gfc_symbol *sym)
9906 {
9907   gfc_expr *init = NULL;
9908
9909   /* The symbol should be a variable or a function return value.  */
9910   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9911       || (sym->attr.function && sym->result != sym))
9912     return;
9913
9914   /* Try to build the initializer expression.  If we can't initialize
9915      this symbol, then init will be NULL.  */
9916   init = build_default_init_expr (sym);
9917   if (init == NULL)
9918     return;
9919
9920   /* For saved variables, we don't want to add an initializer at 
9921      function entry, so we just add a static initializer.  */
9922   if (sym->attr.save || sym->ns->save_all 
9923       || gfc_option.flag_max_stack_var_size == 0)
9924     {
9925       /* Don't clobber an existing initializer!  */
9926       gcc_assert (sym->value == NULL);
9927       sym->value = init;
9928       return;
9929     }
9930
9931   build_init_assign (sym, init);
9932 }
9933
9934
9935 /* Resolution of common features of flavors variable and procedure.  */
9936
9937 static gfc_try
9938 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
9939 {
9940   /* Avoid double diagnostics for function result symbols.  */
9941   if ((sym->result || sym->attr.result) && !sym->attr.dummy
9942       && (sym->ns != gfc_current_ns))
9943     return SUCCESS;
9944
9945   /* Constraints on deferred shape variable.  */
9946   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
9947     {
9948       if (sym->attr.allocatable)
9949         {
9950           if (sym->attr.dimension)
9951             {
9952               gfc_error ("Allocatable array '%s' at %L must have "
9953                          "a deferred shape", sym->name, &sym->declared_at);
9954               return FAILURE;
9955             }
9956           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
9957                                    "may not be ALLOCATABLE", sym->name,
9958                                    &sym->declared_at) == FAILURE)
9959             return FAILURE;
9960         }
9961
9962       if (sym->attr.pointer && sym->attr.dimension)
9963         {
9964           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
9965                      sym->name, &sym->declared_at);
9966           return FAILURE;
9967         }
9968     }
9969   else
9970     {
9971       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
9972           && sym->ts.type != BT_CLASS && !sym->assoc)
9973         {
9974           gfc_error ("Array '%s' at %L cannot have a deferred shape",
9975                      sym->name, &sym->declared_at);
9976           return FAILURE;
9977          }
9978     }
9979
9980   /* Constraints on polymorphic variables.  */
9981   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
9982     {
9983       /* F03:C502.  */
9984       if (sym->attr.class_ok
9985           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
9986         {
9987           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
9988                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
9989                      &sym->declared_at);
9990           return FAILURE;
9991         }
9992
9993       /* F03:C509.  */
9994       /* Assume that use associated symbols were checked in the module ns.
9995          Class-variables that are associate-names are also something special
9996          and excepted from the test.  */
9997       if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
9998         {
9999           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
10000                      "or pointer", sym->name, &sym->declared_at);
10001           return FAILURE;
10002         }
10003     }
10004     
10005   return SUCCESS;
10006 }
10007
10008
10009 /* Additional checks for symbols with flavor variable and derived
10010    type.  To be called from resolve_fl_variable.  */
10011
10012 static gfc_try
10013 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
10014 {
10015   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
10016
10017   /* Check to see if a derived type is blocked from being host
10018      associated by the presence of another class I symbol in the same
10019      namespace.  14.6.1.3 of the standard and the discussion on
10020      comp.lang.fortran.  */
10021   if (sym->ns != sym->ts.u.derived->ns
10022       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
10023     {
10024       gfc_symbol *s;
10025       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
10026       if (s && s->attr.flavor != FL_DERIVED)
10027         {
10028           gfc_error ("The type '%s' cannot be host associated at %L "
10029                      "because it is blocked by an incompatible object "
10030                      "of the same name declared at %L",
10031                      sym->ts.u.derived->name, &sym->declared_at,
10032                      &s->declared_at);
10033           return FAILURE;
10034         }
10035     }
10036
10037   /* 4th constraint in section 11.3: "If an object of a type for which
10038      component-initialization is specified (R429) appears in the
10039      specification-part of a module and does not have the ALLOCATABLE
10040      or POINTER attribute, the object shall have the SAVE attribute."
10041
10042      The check for initializers is performed with
10043      gfc_has_default_initializer because gfc_default_initializer generates
10044      a hidden default for allocatable components.  */
10045   if (!(sym->value || no_init_flag) && sym->ns->proc_name
10046       && sym->ns->proc_name->attr.flavor == FL_MODULE
10047       && !sym->ns->save_all && !sym->attr.save
10048       && !sym->attr.pointer && !sym->attr.allocatable
10049       && gfc_has_default_initializer (sym->ts.u.derived)
10050       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
10051                          "module variable '%s' at %L, needed due to "
10052                          "the default initialization", sym->name,
10053                          &sym->declared_at) == FAILURE)
10054     return FAILURE;
10055
10056   /* Assign default initializer.  */
10057   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
10058       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
10059     {
10060       sym->value = gfc_default_initializer (&sym->ts);
10061     }
10062
10063   return SUCCESS;
10064 }
10065
10066
10067 /* Resolve symbols with flavor variable.  */
10068
10069 static gfc_try
10070 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
10071 {
10072   int no_init_flag, automatic_flag;
10073   gfc_expr *e;
10074   const char *auto_save_msg;
10075
10076   auto_save_msg = "Automatic object '%s' at %L cannot have the "
10077                   "SAVE attribute";
10078
10079   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10080     return FAILURE;
10081
10082   /* Set this flag to check that variables are parameters of all entries.
10083      This check is effected by the call to gfc_resolve_expr through
10084      is_non_constant_shape_array.  */
10085   specification_expr = 1;
10086
10087   if (sym->ns->proc_name
10088       && (sym->ns->proc_name->attr.flavor == FL_MODULE
10089           || sym->ns->proc_name->attr.is_main_program)
10090       && !sym->attr.use_assoc
10091       && !sym->attr.allocatable
10092       && !sym->attr.pointer
10093       && is_non_constant_shape_array (sym))
10094     {
10095       /* The shape of a main program or module array needs to be
10096          constant.  */
10097       gfc_error ("The module or main program array '%s' at %L must "
10098                  "have constant shape", sym->name, &sym->declared_at);
10099       specification_expr = 0;
10100       return FAILURE;
10101     }
10102
10103   /* Constraints on deferred type parameter.  */
10104   if (sym->ts.deferred && !(sym->attr.pointer || sym->attr.allocatable))
10105     {
10106       gfc_error ("Entity '%s' at %L has a deferred type parameter and "
10107                  "requires either the pointer or allocatable attribute",
10108                      sym->name, &sym->declared_at);
10109       return FAILURE;
10110     }
10111
10112   if (sym->ts.type == BT_CHARACTER)
10113     {
10114       /* Make sure that character string variables with assumed length are
10115          dummy arguments.  */
10116       e = sym->ts.u.cl->length;
10117       if (e == NULL && !sym->attr.dummy && !sym->attr.result
10118           && !sym->ts.deferred)
10119         {
10120           gfc_error ("Entity with assumed character length at %L must be a "
10121                      "dummy argument or a PARAMETER", &sym->declared_at);
10122           return FAILURE;
10123         }
10124
10125       if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
10126         {
10127           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10128           return FAILURE;
10129         }
10130
10131       if (!gfc_is_constant_expr (e)
10132           && !(e->expr_type == EXPR_VARIABLE
10133                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
10134           && sym->ns->proc_name
10135           && (sym->ns->proc_name->attr.flavor == FL_MODULE
10136               || sym->ns->proc_name->attr.is_main_program)
10137           && !sym->attr.use_assoc)
10138         {
10139           gfc_error ("'%s' at %L must have constant character length "
10140                      "in this context", sym->name, &sym->declared_at);
10141           return FAILURE;
10142         }
10143     }
10144
10145   if (sym->value == NULL && sym->attr.referenced)
10146     apply_default_init_local (sym); /* Try to apply a default initialization.  */
10147
10148   /* Determine if the symbol may not have an initializer.  */
10149   no_init_flag = automatic_flag = 0;
10150   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
10151       || sym->attr.intrinsic || sym->attr.result)
10152     no_init_flag = 1;
10153   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
10154            && is_non_constant_shape_array (sym))
10155     {
10156       no_init_flag = automatic_flag = 1;
10157
10158       /* Also, they must not have the SAVE attribute.
10159          SAVE_IMPLICIT is checked below.  */
10160       if (sym->as && sym->attr.codimension)
10161         {
10162           int corank = sym->as->corank;
10163           sym->as->corank = 0;
10164           no_init_flag = automatic_flag = is_non_constant_shape_array (sym);
10165           sym->as->corank = corank;
10166         }
10167       if (automatic_flag && sym->attr.save == SAVE_EXPLICIT)
10168         {
10169           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10170           return FAILURE;
10171         }
10172     }
10173
10174   /* Ensure that any initializer is simplified.  */
10175   if (sym->value)
10176     gfc_simplify_expr (sym->value, 1);
10177
10178   /* Reject illegal initializers.  */
10179   if (!sym->mark && sym->value)
10180     {
10181       if (sym->attr.allocatable || (sym->ts.type == BT_CLASS
10182                                     && CLASS_DATA (sym)->attr.allocatable))
10183         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
10184                    sym->name, &sym->declared_at);
10185       else if (sym->attr.external)
10186         gfc_error ("External '%s' at %L cannot have an initializer",
10187                    sym->name, &sym->declared_at);
10188       else if (sym->attr.dummy
10189         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
10190         gfc_error ("Dummy '%s' at %L cannot have an initializer",
10191                    sym->name, &sym->declared_at);
10192       else if (sym->attr.intrinsic)
10193         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
10194                    sym->name, &sym->declared_at);
10195       else if (sym->attr.result)
10196         gfc_error ("Function result '%s' at %L cannot have an initializer",
10197                    sym->name, &sym->declared_at);
10198       else if (automatic_flag)
10199         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
10200                    sym->name, &sym->declared_at);
10201       else
10202         goto no_init_error;
10203       return FAILURE;
10204     }
10205
10206 no_init_error:
10207   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
10208     return resolve_fl_variable_derived (sym, no_init_flag);
10209
10210   return SUCCESS;
10211 }
10212
10213
10214 /* Resolve a procedure.  */
10215
10216 static gfc_try
10217 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
10218 {
10219   gfc_formal_arglist *arg;
10220
10221   if (sym->attr.function
10222       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10223     return FAILURE;
10224
10225   if (sym->ts.type == BT_CHARACTER)
10226     {
10227       gfc_charlen *cl = sym->ts.u.cl;
10228
10229       if (cl && cl->length && gfc_is_constant_expr (cl->length)
10230              && resolve_charlen (cl) == FAILURE)
10231         return FAILURE;
10232
10233       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
10234           && sym->attr.proc == PROC_ST_FUNCTION)
10235         {
10236           gfc_error ("Character-valued statement function '%s' at %L must "
10237                      "have constant length", sym->name, &sym->declared_at);
10238           return FAILURE;
10239         }
10240     }
10241
10242   /* Ensure that derived type for are not of a private type.  Internal
10243      module procedures are excluded by 2.2.3.3 - i.e., they are not
10244      externally accessible and can access all the objects accessible in
10245      the host.  */
10246   if (!(sym->ns->parent
10247         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
10248       && gfc_check_symbol_access (sym))
10249     {
10250       gfc_interface *iface;
10251
10252       for (arg = sym->formal; arg; arg = arg->next)
10253         {
10254           if (arg->sym
10255               && arg->sym->ts.type == BT_DERIVED
10256               && !arg->sym->ts.u.derived->attr.use_assoc
10257               && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10258               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
10259                                  "PRIVATE type and cannot be a dummy argument"
10260                                  " of '%s', which is PUBLIC at %L",
10261                                  arg->sym->name, sym->name, &sym->declared_at)
10262                  == FAILURE)
10263             {
10264               /* Stop this message from recurring.  */
10265               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10266               return FAILURE;
10267             }
10268         }
10269
10270       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10271          PRIVATE to the containing module.  */
10272       for (iface = sym->generic; iface; iface = iface->next)
10273         {
10274           for (arg = iface->sym->formal; arg; arg = arg->next)
10275             {
10276               if (arg->sym
10277                   && arg->sym->ts.type == BT_DERIVED
10278                   && !arg->sym->ts.u.derived->attr.use_assoc
10279                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10280                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10281                                      "'%s' in PUBLIC interface '%s' at %L "
10282                                      "takes dummy arguments of '%s' which is "
10283                                      "PRIVATE", iface->sym->name, sym->name,
10284                                      &iface->sym->declared_at,
10285                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10286                 {
10287                   /* Stop this message from recurring.  */
10288                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10289                   return FAILURE;
10290                 }
10291              }
10292         }
10293
10294       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10295          PRIVATE to the containing module.  */
10296       for (iface = sym->generic; iface; iface = iface->next)
10297         {
10298           for (arg = iface->sym->formal; arg; arg = arg->next)
10299             {
10300               if (arg->sym
10301                   && arg->sym->ts.type == BT_DERIVED
10302                   && !arg->sym->ts.u.derived->attr.use_assoc
10303                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10304                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10305                                      "'%s' in PUBLIC interface '%s' at %L "
10306                                      "takes dummy arguments of '%s' which is "
10307                                      "PRIVATE", iface->sym->name, sym->name,
10308                                      &iface->sym->declared_at,
10309                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10310                 {
10311                   /* Stop this message from recurring.  */
10312                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10313                   return FAILURE;
10314                 }
10315              }
10316         }
10317     }
10318
10319   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
10320       && !sym->attr.proc_pointer)
10321     {
10322       gfc_error ("Function '%s' at %L cannot have an initializer",
10323                  sym->name, &sym->declared_at);
10324       return FAILURE;
10325     }
10326
10327   /* An external symbol may not have an initializer because it is taken to be
10328      a procedure. Exception: Procedure Pointers.  */
10329   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
10330     {
10331       gfc_error ("External object '%s' at %L may not have an initializer",
10332                  sym->name, &sym->declared_at);
10333       return FAILURE;
10334     }
10335
10336   /* An elemental function is required to return a scalar 12.7.1  */
10337   if (sym->attr.elemental && sym->attr.function && sym->as)
10338     {
10339       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
10340                  "result", sym->name, &sym->declared_at);
10341       /* Reset so that the error only occurs once.  */
10342       sym->attr.elemental = 0;
10343       return FAILURE;
10344     }
10345
10346   if (sym->attr.proc == PROC_ST_FUNCTION
10347       && (sym->attr.allocatable || sym->attr.pointer))
10348     {
10349       gfc_error ("Statement function '%s' at %L may not have pointer or "
10350                  "allocatable attribute", sym->name, &sym->declared_at);
10351       return FAILURE;
10352     }
10353
10354   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
10355      char-len-param shall not be array-valued, pointer-valued, recursive
10356      or pure.  ....snip... A character value of * may only be used in the
10357      following ways: (i) Dummy arg of procedure - dummy associates with
10358      actual length; (ii) To declare a named constant; or (iii) External
10359      function - but length must be declared in calling scoping unit.  */
10360   if (sym->attr.function
10361       && sym->ts.type == BT_CHARACTER
10362       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
10363     {
10364       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
10365           || (sym->attr.recursive) || (sym->attr.pure))
10366         {
10367           if (sym->as && sym->as->rank)
10368             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10369                        "array-valued", sym->name, &sym->declared_at);
10370
10371           if (sym->attr.pointer)
10372             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10373                        "pointer-valued", sym->name, &sym->declared_at);
10374
10375           if (sym->attr.pure)
10376             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10377                        "pure", sym->name, &sym->declared_at);
10378
10379           if (sym->attr.recursive)
10380             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10381                        "recursive", sym->name, &sym->declared_at);
10382
10383           return FAILURE;
10384         }
10385
10386       /* Appendix B.2 of the standard.  Contained functions give an
10387          error anyway.  Fixed-form is likely to be F77/legacy. Deferred
10388          character length is an F2003 feature.  */
10389       if (!sym->attr.contained
10390             && gfc_current_form != FORM_FIXED
10391             && !sym->ts.deferred)
10392         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
10393                         "CHARACTER(*) function '%s' at %L",
10394                         sym->name, &sym->declared_at);
10395     }
10396
10397   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
10398     {
10399       gfc_formal_arglist *curr_arg;
10400       int has_non_interop_arg = 0;
10401
10402       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10403                              sym->common_block) == FAILURE)
10404         {
10405           /* Clear these to prevent looking at them again if there was an
10406              error.  */
10407           sym->attr.is_bind_c = 0;
10408           sym->attr.is_c_interop = 0;
10409           sym->ts.is_c_interop = 0;
10410         }
10411       else
10412         {
10413           /* So far, no errors have been found.  */
10414           sym->attr.is_c_interop = 1;
10415           sym->ts.is_c_interop = 1;
10416         }
10417       
10418       curr_arg = sym->formal;
10419       while (curr_arg != NULL)
10420         {
10421           /* Skip implicitly typed dummy args here.  */
10422           if (curr_arg->sym->attr.implicit_type == 0)
10423             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
10424               /* If something is found to fail, record the fact so we
10425                  can mark the symbol for the procedure as not being
10426                  BIND(C) to try and prevent multiple errors being
10427                  reported.  */
10428               has_non_interop_arg = 1;
10429           
10430           curr_arg = curr_arg->next;
10431         }
10432
10433       /* See if any of the arguments were not interoperable and if so, clear
10434          the procedure symbol to prevent duplicate error messages.  */
10435       if (has_non_interop_arg != 0)
10436         {
10437           sym->attr.is_c_interop = 0;
10438           sym->ts.is_c_interop = 0;
10439           sym->attr.is_bind_c = 0;
10440         }
10441     }
10442   
10443   if (!sym->attr.proc_pointer)
10444     {
10445       if (sym->attr.save == SAVE_EXPLICIT)
10446         {
10447           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
10448                      "in '%s' at %L", sym->name, &sym->declared_at);
10449           return FAILURE;
10450         }
10451       if (sym->attr.intent)
10452         {
10453           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
10454                      "in '%s' at %L", sym->name, &sym->declared_at);
10455           return FAILURE;
10456         }
10457       if (sym->attr.subroutine && sym->attr.result)
10458         {
10459           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
10460                      "in '%s' at %L", sym->name, &sym->declared_at);
10461           return FAILURE;
10462         }
10463       if (sym->attr.external && sym->attr.function
10464           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
10465               || sym->attr.contained))
10466         {
10467           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
10468                      "in '%s' at %L", sym->name, &sym->declared_at);
10469           return FAILURE;
10470         }
10471       if (strcmp ("ppr@", sym->name) == 0)
10472         {
10473           gfc_error ("Procedure pointer result '%s' at %L "
10474                      "is missing the pointer attribute",
10475                      sym->ns->proc_name->name, &sym->declared_at);
10476           return FAILURE;
10477         }
10478     }
10479
10480   return SUCCESS;
10481 }
10482
10483
10484 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
10485    been defined and we now know their defined arguments, check that they fulfill
10486    the requirements of the standard for procedures used as finalizers.  */
10487
10488 static gfc_try
10489 gfc_resolve_finalizers (gfc_symbol* derived)
10490 {
10491   gfc_finalizer* list;
10492   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
10493   gfc_try result = SUCCESS;
10494   bool seen_scalar = false;
10495
10496   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
10497     return SUCCESS;
10498
10499   /* Walk over the list of finalizer-procedures, check them, and if any one
10500      does not fit in with the standard's definition, print an error and remove
10501      it from the list.  */
10502   prev_link = &derived->f2k_derived->finalizers;
10503   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
10504     {
10505       gfc_symbol* arg;
10506       gfc_finalizer* i;
10507       int my_rank;
10508
10509       /* Skip this finalizer if we already resolved it.  */
10510       if (list->proc_tree)
10511         {
10512           prev_link = &(list->next);
10513           continue;
10514         }
10515
10516       /* Check this exists and is a SUBROUTINE.  */
10517       if (!list->proc_sym->attr.subroutine)
10518         {
10519           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
10520                      list->proc_sym->name, &list->where);
10521           goto error;
10522         }
10523
10524       /* We should have exactly one argument.  */
10525       if (!list->proc_sym->formal || list->proc_sym->formal->next)
10526         {
10527           gfc_error ("FINAL procedure at %L must have exactly one argument",
10528                      &list->where);
10529           goto error;
10530         }
10531       arg = list->proc_sym->formal->sym;
10532
10533       /* This argument must be of our type.  */
10534       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
10535         {
10536           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
10537                      &arg->declared_at, derived->name);
10538           goto error;
10539         }
10540
10541       /* It must neither be a pointer nor allocatable nor optional.  */
10542       if (arg->attr.pointer)
10543         {
10544           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
10545                      &arg->declared_at);
10546           goto error;
10547         }
10548       if (arg->attr.allocatable)
10549         {
10550           gfc_error ("Argument of FINAL procedure at %L must not be"
10551                      " ALLOCATABLE", &arg->declared_at);
10552           goto error;
10553         }
10554       if (arg->attr.optional)
10555         {
10556           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
10557                      &arg->declared_at);
10558           goto error;
10559         }
10560
10561       /* It must not be INTENT(OUT).  */
10562       if (arg->attr.intent == INTENT_OUT)
10563         {
10564           gfc_error ("Argument of FINAL procedure at %L must not be"
10565                      " INTENT(OUT)", &arg->declared_at);
10566           goto error;
10567         }
10568
10569       /* Warn if the procedure is non-scalar and not assumed shape.  */
10570       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
10571           && arg->as->type != AS_ASSUMED_SHAPE)
10572         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
10573                      " shape argument", &arg->declared_at);
10574
10575       /* Check that it does not match in kind and rank with a FINAL procedure
10576          defined earlier.  To really loop over the *earlier* declarations,
10577          we need to walk the tail of the list as new ones were pushed at the
10578          front.  */
10579       /* TODO: Handle kind parameters once they are implemented.  */
10580       my_rank = (arg->as ? arg->as->rank : 0);
10581       for (i = list->next; i; i = i->next)
10582         {
10583           /* Argument list might be empty; that is an error signalled earlier,
10584              but we nevertheless continued resolving.  */
10585           if (i->proc_sym->formal)
10586             {
10587               gfc_symbol* i_arg = i->proc_sym->formal->sym;
10588               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
10589               if (i_rank == my_rank)
10590                 {
10591                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
10592                              " rank (%d) as '%s'",
10593                              list->proc_sym->name, &list->where, my_rank, 
10594                              i->proc_sym->name);
10595                   goto error;
10596                 }
10597             }
10598         }
10599
10600         /* Is this the/a scalar finalizer procedure?  */
10601         if (!arg->as || arg->as->rank == 0)
10602           seen_scalar = true;
10603
10604         /* Find the symtree for this procedure.  */
10605         gcc_assert (!list->proc_tree);
10606         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
10607
10608         prev_link = &list->next;
10609         continue;
10610
10611         /* Remove wrong nodes immediately from the list so we don't risk any
10612            troubles in the future when they might fail later expectations.  */
10613 error:
10614         result = FAILURE;
10615         i = list;
10616         *prev_link = list->next;
10617         gfc_free_finalizer (i);
10618     }
10619
10620   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
10621      were nodes in the list, must have been for arrays.  It is surely a good
10622      idea to have a scalar version there if there's something to finalize.  */
10623   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
10624     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
10625                  " defined at %L, suggest also scalar one",
10626                  derived->name, &derived->declared_at);
10627
10628   /* TODO:  Remove this error when finalization is finished.  */
10629   gfc_error ("Finalization at %L is not yet implemented",
10630              &derived->declared_at);
10631
10632   return result;
10633 }
10634
10635
10636 /* Check that it is ok for the typebound procedure proc to override the
10637    procedure old.  */
10638
10639 static gfc_try
10640 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
10641 {
10642   locus where;
10643   const gfc_symbol* proc_target;
10644   const gfc_symbol* old_target;
10645   unsigned proc_pass_arg, old_pass_arg, argpos;
10646   gfc_formal_arglist* proc_formal;
10647   gfc_formal_arglist* old_formal;
10648
10649   /* This procedure should only be called for non-GENERIC proc.  */
10650   gcc_assert (!proc->n.tb->is_generic);
10651
10652   /* If the overwritten procedure is GENERIC, this is an error.  */
10653   if (old->n.tb->is_generic)
10654     {
10655       gfc_error ("Can't overwrite GENERIC '%s' at %L",
10656                  old->name, &proc->n.tb->where);
10657       return FAILURE;
10658     }
10659
10660   where = proc->n.tb->where;
10661   proc_target = proc->n.tb->u.specific->n.sym;
10662   old_target = old->n.tb->u.specific->n.sym;
10663
10664   /* Check that overridden binding is not NON_OVERRIDABLE.  */
10665   if (old->n.tb->non_overridable)
10666     {
10667       gfc_error ("'%s' at %L overrides a procedure binding declared"
10668                  " NON_OVERRIDABLE", proc->name, &where);
10669       return FAILURE;
10670     }
10671
10672   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
10673   if (!old->n.tb->deferred && proc->n.tb->deferred)
10674     {
10675       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
10676                  " non-DEFERRED binding", proc->name, &where);
10677       return FAILURE;
10678     }
10679
10680   /* If the overridden binding is PURE, the overriding must be, too.  */
10681   if (old_target->attr.pure && !proc_target->attr.pure)
10682     {
10683       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
10684                  proc->name, &where);
10685       return FAILURE;
10686     }
10687
10688   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
10689      is not, the overriding must not be either.  */
10690   if (old_target->attr.elemental && !proc_target->attr.elemental)
10691     {
10692       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
10693                  " ELEMENTAL", proc->name, &where);
10694       return FAILURE;
10695     }
10696   if (!old_target->attr.elemental && proc_target->attr.elemental)
10697     {
10698       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
10699                  " be ELEMENTAL, either", proc->name, &where);
10700       return FAILURE;
10701     }
10702
10703   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
10704      SUBROUTINE.  */
10705   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
10706     {
10707       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
10708                  " SUBROUTINE", proc->name, &where);
10709       return FAILURE;
10710     }
10711
10712   /* If the overridden binding is a FUNCTION, the overriding must also be a
10713      FUNCTION and have the same characteristics.  */
10714   if (old_target->attr.function)
10715     {
10716       if (!proc_target->attr.function)
10717         {
10718           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
10719                      " FUNCTION", proc->name, &where);
10720           return FAILURE;
10721         }
10722
10723       /* FIXME:  Do more comprehensive checking (including, for instance, the
10724          rank and array-shape).  */
10725       gcc_assert (proc_target->result && old_target->result);
10726       if (!gfc_compare_types (&proc_target->result->ts,
10727                               &old_target->result->ts))
10728         {
10729           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
10730                      " matching result types", proc->name, &where);
10731           return FAILURE;
10732         }
10733     }
10734
10735   /* If the overridden binding is PUBLIC, the overriding one must not be
10736      PRIVATE.  */
10737   if (old->n.tb->access == ACCESS_PUBLIC
10738       && proc->n.tb->access == ACCESS_PRIVATE)
10739     {
10740       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
10741                  " PRIVATE", proc->name, &where);
10742       return FAILURE;
10743     }
10744
10745   /* Compare the formal argument lists of both procedures.  This is also abused
10746      to find the position of the passed-object dummy arguments of both
10747      bindings as at least the overridden one might not yet be resolved and we
10748      need those positions in the check below.  */
10749   proc_pass_arg = old_pass_arg = 0;
10750   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
10751     proc_pass_arg = 1;
10752   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
10753     old_pass_arg = 1;
10754   argpos = 1;
10755   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
10756        proc_formal && old_formal;
10757        proc_formal = proc_formal->next, old_formal = old_formal->next)
10758     {
10759       if (proc->n.tb->pass_arg
10760           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
10761         proc_pass_arg = argpos;
10762       if (old->n.tb->pass_arg
10763           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
10764         old_pass_arg = argpos;
10765
10766       /* Check that the names correspond.  */
10767       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
10768         {
10769           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
10770                      " to match the corresponding argument of the overridden"
10771                      " procedure", proc_formal->sym->name, proc->name, &where,
10772                      old_formal->sym->name);
10773           return FAILURE;
10774         }
10775
10776       /* Check that the types correspond if neither is the passed-object
10777          argument.  */
10778       /* FIXME:  Do more comprehensive testing here.  */
10779       if (proc_pass_arg != argpos && old_pass_arg != argpos
10780           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
10781         {
10782           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L "
10783                      "in respect to the overridden procedure",
10784                      proc_formal->sym->name, proc->name, &where);
10785           return FAILURE;
10786         }
10787
10788       ++argpos;
10789     }
10790   if (proc_formal || old_formal)
10791     {
10792       gfc_error ("'%s' at %L must have the same number of formal arguments as"
10793                  " the overridden procedure", proc->name, &where);
10794       return FAILURE;
10795     }
10796
10797   /* If the overridden binding is NOPASS, the overriding one must also be
10798      NOPASS.  */
10799   if (old->n.tb->nopass && !proc->n.tb->nopass)
10800     {
10801       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
10802                  " NOPASS", proc->name, &where);
10803       return FAILURE;
10804     }
10805
10806   /* If the overridden binding is PASS(x), the overriding one must also be
10807      PASS and the passed-object dummy arguments must correspond.  */
10808   if (!old->n.tb->nopass)
10809     {
10810       if (proc->n.tb->nopass)
10811         {
10812           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
10813                      " PASS", proc->name, &where);
10814           return FAILURE;
10815         }
10816
10817       if (proc_pass_arg != old_pass_arg)
10818         {
10819           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
10820                      " the same position as the passed-object dummy argument of"
10821                      " the overridden procedure", proc->name, &where);
10822           return FAILURE;
10823         }
10824     }
10825
10826   return SUCCESS;
10827 }
10828
10829
10830 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10831
10832 static gfc_try
10833 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10834                              const char* generic_name, locus where)
10835 {
10836   gfc_symbol* sym1;
10837   gfc_symbol* sym2;
10838
10839   gcc_assert (t1->specific && t2->specific);
10840   gcc_assert (!t1->specific->is_generic);
10841   gcc_assert (!t2->specific->is_generic);
10842
10843   sym1 = t1->specific->u.specific->n.sym;
10844   sym2 = t2->specific->u.specific->n.sym;
10845
10846   if (sym1 == sym2)
10847     return SUCCESS;
10848
10849   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10850   if (sym1->attr.subroutine != sym2->attr.subroutine
10851       || sym1->attr.function != sym2->attr.function)
10852     {
10853       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10854                  " GENERIC '%s' at %L",
10855                  sym1->name, sym2->name, generic_name, &where);
10856       return FAILURE;
10857     }
10858
10859   /* Compare the interfaces.  */
10860   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10861     {
10862       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10863                  sym1->name, sym2->name, generic_name, &where);
10864       return FAILURE;
10865     }
10866
10867   return SUCCESS;
10868 }
10869
10870
10871 /* Worker function for resolving a generic procedure binding; this is used to
10872    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10873
10874    The difference between those cases is finding possible inherited bindings
10875    that are overridden, as one has to look for them in tb_sym_root,
10876    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10877    the super-type and set p->overridden correctly.  */
10878
10879 static gfc_try
10880 resolve_tb_generic_targets (gfc_symbol* super_type,
10881                             gfc_typebound_proc* p, const char* name)
10882 {
10883   gfc_tbp_generic* target;
10884   gfc_symtree* first_target;
10885   gfc_symtree* inherited;
10886
10887   gcc_assert (p && p->is_generic);
10888
10889   /* Try to find the specific bindings for the symtrees in our target-list.  */
10890   gcc_assert (p->u.generic);
10891   for (target = p->u.generic; target; target = target->next)
10892     if (!target->specific)
10893       {
10894         gfc_typebound_proc* overridden_tbp;
10895         gfc_tbp_generic* g;
10896         const char* target_name;
10897
10898         target_name = target->specific_st->name;
10899
10900         /* Defined for this type directly.  */
10901         if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
10902           {
10903             target->specific = target->specific_st->n.tb;
10904             goto specific_found;
10905           }
10906
10907         /* Look for an inherited specific binding.  */
10908         if (super_type)
10909           {
10910             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10911                                                  true, NULL);
10912
10913             if (inherited)
10914               {
10915                 gcc_assert (inherited->n.tb);
10916                 target->specific = inherited->n.tb;
10917                 goto specific_found;
10918               }
10919           }
10920
10921         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10922                    " at %L", target_name, name, &p->where);
10923         return FAILURE;
10924
10925         /* Once we've found the specific binding, check it is not ambiguous with
10926            other specifics already found or inherited for the same GENERIC.  */
10927 specific_found:
10928         gcc_assert (target->specific);
10929
10930         /* This must really be a specific binding!  */
10931         if (target->specific->is_generic)
10932           {
10933             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
10934                        " '%s' is GENERIC, too", name, &p->where, target_name);
10935             return FAILURE;
10936           }
10937
10938         /* Check those already resolved on this type directly.  */
10939         for (g = p->u.generic; g; g = g->next)
10940           if (g != target && g->specific
10941               && check_generic_tbp_ambiguity (target, g, name, p->where)
10942                   == FAILURE)
10943             return FAILURE;
10944
10945         /* Check for ambiguity with inherited specific targets.  */
10946         for (overridden_tbp = p->overridden; overridden_tbp;
10947              overridden_tbp = overridden_tbp->overridden)
10948           if (overridden_tbp->is_generic)
10949             {
10950               for (g = overridden_tbp->u.generic; g; g = g->next)
10951                 {
10952                   gcc_assert (g->specific);
10953                   if (check_generic_tbp_ambiguity (target, g,
10954                                                    name, p->where) == FAILURE)
10955                     return FAILURE;
10956                 }
10957             }
10958       }
10959
10960   /* If we attempt to "overwrite" a specific binding, this is an error.  */
10961   if (p->overridden && !p->overridden->is_generic)
10962     {
10963       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
10964                  " the same name", name, &p->where);
10965       return FAILURE;
10966     }
10967
10968   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
10969      all must have the same attributes here.  */
10970   first_target = p->u.generic->specific->u.specific;
10971   gcc_assert (first_target);
10972   p->subroutine = first_target->n.sym->attr.subroutine;
10973   p->function = first_target->n.sym->attr.function;
10974
10975   return SUCCESS;
10976 }
10977
10978
10979 /* Resolve a GENERIC procedure binding for a derived type.  */
10980
10981 static gfc_try
10982 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
10983 {
10984   gfc_symbol* super_type;
10985
10986   /* Find the overridden binding if any.  */
10987   st->n.tb->overridden = NULL;
10988   super_type = gfc_get_derived_super_type (derived);
10989   if (super_type)
10990     {
10991       gfc_symtree* overridden;
10992       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
10993                                             true, NULL);
10994
10995       if (overridden && overridden->n.tb)
10996         st->n.tb->overridden = overridden->n.tb;
10997     }
10998
10999   /* Resolve using worker function.  */
11000   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
11001 }
11002
11003
11004 /* Retrieve the target-procedure of an operator binding and do some checks in
11005    common for intrinsic and user-defined type-bound operators.  */
11006
11007 static gfc_symbol*
11008 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
11009 {
11010   gfc_symbol* target_proc;
11011
11012   gcc_assert (target->specific && !target->specific->is_generic);
11013   target_proc = target->specific->u.specific->n.sym;
11014   gcc_assert (target_proc);
11015
11016   /* All operator bindings must have a passed-object dummy argument.  */
11017   if (target->specific->nopass)
11018     {
11019       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
11020       return NULL;
11021     }
11022
11023   return target_proc;
11024 }
11025
11026
11027 /* Resolve a type-bound intrinsic operator.  */
11028
11029 static gfc_try
11030 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
11031                                 gfc_typebound_proc* p)
11032 {
11033   gfc_symbol* super_type;
11034   gfc_tbp_generic* target;
11035   
11036   /* If there's already an error here, do nothing (but don't fail again).  */
11037   if (p->error)
11038     return SUCCESS;
11039
11040   /* Operators should always be GENERIC bindings.  */
11041   gcc_assert (p->is_generic);
11042
11043   /* Look for an overridden binding.  */
11044   super_type = gfc_get_derived_super_type (derived);
11045   if (super_type && super_type->f2k_derived)
11046     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
11047                                                      op, true, NULL);
11048   else
11049     p->overridden = NULL;
11050
11051   /* Resolve general GENERIC properties using worker function.  */
11052   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
11053     goto error;
11054
11055   /* Check the targets to be procedures of correct interface.  */
11056   for (target = p->u.generic; target; target = target->next)
11057     {
11058       gfc_symbol* target_proc;
11059
11060       target_proc = get_checked_tb_operator_target (target, p->where);
11061       if (!target_proc)
11062         goto error;
11063
11064       if (!gfc_check_operator_interface (target_proc, op, p->where))
11065         goto error;
11066     }
11067
11068   return SUCCESS;
11069
11070 error:
11071   p->error = 1;
11072   return FAILURE;
11073 }
11074
11075
11076 /* Resolve a type-bound user operator (tree-walker callback).  */
11077
11078 static gfc_symbol* resolve_bindings_derived;
11079 static gfc_try resolve_bindings_result;
11080
11081 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
11082
11083 static void
11084 resolve_typebound_user_op (gfc_symtree* stree)
11085 {
11086   gfc_symbol* super_type;
11087   gfc_tbp_generic* target;
11088
11089   gcc_assert (stree && stree->n.tb);
11090
11091   if (stree->n.tb->error)
11092     return;
11093
11094   /* Operators should always be GENERIC bindings.  */
11095   gcc_assert (stree->n.tb->is_generic);
11096
11097   /* Find overridden procedure, if any.  */
11098   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11099   if (super_type && super_type->f2k_derived)
11100     {
11101       gfc_symtree* overridden;
11102       overridden = gfc_find_typebound_user_op (super_type, NULL,
11103                                                stree->name, true, NULL);
11104
11105       if (overridden && overridden->n.tb)
11106         stree->n.tb->overridden = overridden->n.tb;
11107     }
11108   else
11109     stree->n.tb->overridden = NULL;
11110
11111   /* Resolve basically using worker function.  */
11112   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
11113         == FAILURE)
11114     goto error;
11115
11116   /* Check the targets to be functions of correct interface.  */
11117   for (target = stree->n.tb->u.generic; target; target = target->next)
11118     {
11119       gfc_symbol* target_proc;
11120
11121       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
11122       if (!target_proc)
11123         goto error;
11124
11125       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
11126         goto error;
11127     }
11128
11129   return;
11130
11131 error:
11132   resolve_bindings_result = FAILURE;
11133   stree->n.tb->error = 1;
11134 }
11135
11136
11137 /* Resolve the type-bound procedures for a derived type.  */
11138
11139 static void
11140 resolve_typebound_procedure (gfc_symtree* stree)
11141 {
11142   gfc_symbol* proc;
11143   locus where;
11144   gfc_symbol* me_arg;
11145   gfc_symbol* super_type;
11146   gfc_component* comp;
11147
11148   gcc_assert (stree);
11149
11150   /* Undefined specific symbol from GENERIC target definition.  */
11151   if (!stree->n.tb)
11152     return;
11153
11154   if (stree->n.tb->error)
11155     return;
11156
11157   /* If this is a GENERIC binding, use that routine.  */
11158   if (stree->n.tb->is_generic)
11159     {
11160       if (resolve_typebound_generic (resolve_bindings_derived, stree)
11161             == FAILURE)
11162         goto error;
11163       return;
11164     }
11165
11166   /* Get the target-procedure to check it.  */
11167   gcc_assert (!stree->n.tb->is_generic);
11168   gcc_assert (stree->n.tb->u.specific);
11169   proc = stree->n.tb->u.specific->n.sym;
11170   where = stree->n.tb->where;
11171
11172   /* Default access should already be resolved from the parser.  */
11173   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
11174
11175   /* It should be a module procedure or an external procedure with explicit
11176      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
11177   if ((!proc->attr.subroutine && !proc->attr.function)
11178       || (proc->attr.proc != PROC_MODULE
11179           && proc->attr.if_source != IFSRC_IFBODY)
11180       || (proc->attr.abstract && !stree->n.tb->deferred))
11181     {
11182       gfc_error ("'%s' must be a module procedure or an external procedure with"
11183                  " an explicit interface at %L", proc->name, &where);
11184       goto error;
11185     }
11186   stree->n.tb->subroutine = proc->attr.subroutine;
11187   stree->n.tb->function = proc->attr.function;
11188
11189   /* Find the super-type of the current derived type.  We could do this once and
11190      store in a global if speed is needed, but as long as not I believe this is
11191      more readable and clearer.  */
11192   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11193
11194   /* If PASS, resolve and check arguments if not already resolved / loaded
11195      from a .mod file.  */
11196   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
11197     {
11198       if (stree->n.tb->pass_arg)
11199         {
11200           gfc_formal_arglist* i;
11201
11202           /* If an explicit passing argument name is given, walk the arg-list
11203              and look for it.  */
11204
11205           me_arg = NULL;
11206           stree->n.tb->pass_arg_num = 1;
11207           for (i = proc->formal; i; i = i->next)
11208             {
11209               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
11210                 {
11211                   me_arg = i->sym;
11212                   break;
11213                 }
11214               ++stree->n.tb->pass_arg_num;
11215             }
11216
11217           if (!me_arg)
11218             {
11219               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
11220                          " argument '%s'",
11221                          proc->name, stree->n.tb->pass_arg, &where,
11222                          stree->n.tb->pass_arg);
11223               goto error;
11224             }
11225         }
11226       else
11227         {
11228           /* Otherwise, take the first one; there should in fact be at least
11229              one.  */
11230           stree->n.tb->pass_arg_num = 1;
11231           if (!proc->formal)
11232             {
11233               gfc_error ("Procedure '%s' with PASS at %L must have at"
11234                          " least one argument", proc->name, &where);
11235               goto error;
11236             }
11237           me_arg = proc->formal->sym;
11238         }
11239
11240       /* Now check that the argument-type matches and the passed-object
11241          dummy argument is generally fine.  */
11242
11243       gcc_assert (me_arg);
11244
11245       if (me_arg->ts.type != BT_CLASS)
11246         {
11247           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11248                      " at %L", proc->name, &where);
11249           goto error;
11250         }
11251
11252       if (CLASS_DATA (me_arg)->ts.u.derived
11253           != resolve_bindings_derived)
11254         {
11255           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11256                      " the derived-type '%s'", me_arg->name, proc->name,
11257                      me_arg->name, &where, resolve_bindings_derived->name);
11258           goto error;
11259         }
11260   
11261       gcc_assert (me_arg->ts.type == BT_CLASS);
11262       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
11263         {
11264           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
11265                      " scalar", proc->name, &where);
11266           goto error;
11267         }
11268       if (CLASS_DATA (me_arg)->attr.allocatable)
11269         {
11270           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11271                      " be ALLOCATABLE", proc->name, &where);
11272           goto error;
11273         }
11274       if (CLASS_DATA (me_arg)->attr.class_pointer)
11275         {
11276           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11277                      " be POINTER", proc->name, &where);
11278           goto error;
11279         }
11280     }
11281
11282   /* If we are extending some type, check that we don't override a procedure
11283      flagged NON_OVERRIDABLE.  */
11284   stree->n.tb->overridden = NULL;
11285   if (super_type)
11286     {
11287       gfc_symtree* overridden;
11288       overridden = gfc_find_typebound_proc (super_type, NULL,
11289                                             stree->name, true, NULL);
11290
11291       if (overridden && overridden->n.tb)
11292         stree->n.tb->overridden = overridden->n.tb;
11293
11294       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
11295         goto error;
11296     }
11297
11298   /* See if there's a name collision with a component directly in this type.  */
11299   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
11300     if (!strcmp (comp->name, stree->name))
11301       {
11302         gfc_error ("Procedure '%s' at %L has the same name as a component of"
11303                    " '%s'",
11304                    stree->name, &where, resolve_bindings_derived->name);
11305         goto error;
11306       }
11307
11308   /* Try to find a name collision with an inherited component.  */
11309   if (super_type && gfc_find_component (super_type, stree->name, true, true))
11310     {
11311       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
11312                  " component of '%s'",
11313                  stree->name, &where, resolve_bindings_derived->name);
11314       goto error;
11315     }
11316
11317   stree->n.tb->error = 0;
11318   return;
11319
11320 error:
11321   resolve_bindings_result = FAILURE;
11322   stree->n.tb->error = 1;
11323 }
11324
11325
11326 static gfc_try
11327 resolve_typebound_procedures (gfc_symbol* derived)
11328 {
11329   int op;
11330
11331   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
11332     return SUCCESS;
11333
11334   resolve_bindings_derived = derived;
11335   resolve_bindings_result = SUCCESS;
11336
11337   /* Make sure the vtab has been generated.  */
11338   gfc_find_derived_vtab (derived);
11339
11340   if (derived->f2k_derived->tb_sym_root)
11341     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
11342                           &resolve_typebound_procedure);
11343
11344   if (derived->f2k_derived->tb_uop_root)
11345     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
11346                           &resolve_typebound_user_op);
11347
11348   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
11349     {
11350       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
11351       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
11352                                                p) == FAILURE)
11353         resolve_bindings_result = FAILURE;
11354     }
11355
11356   return resolve_bindings_result;
11357 }
11358
11359
11360 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
11361    to give all identical derived types the same backend_decl.  */
11362 static void
11363 add_dt_to_dt_list (gfc_symbol *derived)
11364 {
11365   gfc_dt_list *dt_list;
11366
11367   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
11368     if (derived == dt_list->derived)
11369       return;
11370
11371   dt_list = gfc_get_dt_list ();
11372   dt_list->next = gfc_derived_types;
11373   dt_list->derived = derived;
11374   gfc_derived_types = dt_list;
11375 }
11376
11377
11378 /* Ensure that a derived-type is really not abstract, meaning that every
11379    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
11380
11381 static gfc_try
11382 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
11383 {
11384   if (!st)
11385     return SUCCESS;
11386
11387   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
11388     return FAILURE;
11389   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
11390     return FAILURE;
11391
11392   if (st->n.tb && st->n.tb->deferred)
11393     {
11394       gfc_symtree* overriding;
11395       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
11396       if (!overriding)
11397         return FAILURE;
11398       gcc_assert (overriding->n.tb);
11399       if (overriding->n.tb->deferred)
11400         {
11401           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
11402                      " '%s' is DEFERRED and not overridden",
11403                      sub->name, &sub->declared_at, st->name);
11404           return FAILURE;
11405         }
11406     }
11407
11408   return SUCCESS;
11409 }
11410
11411 static gfc_try
11412 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
11413 {
11414   /* The algorithm used here is to recursively travel up the ancestry of sub
11415      and for each ancestor-type, check all bindings.  If any of them is
11416      DEFERRED, look it up starting from sub and see if the found (overriding)
11417      binding is not DEFERRED.
11418      This is not the most efficient way to do this, but it should be ok and is
11419      clearer than something sophisticated.  */
11420
11421   gcc_assert (ancestor && !sub->attr.abstract);
11422   
11423   if (!ancestor->attr.abstract)
11424     return SUCCESS;
11425
11426   /* Walk bindings of this ancestor.  */
11427   if (ancestor->f2k_derived)
11428     {
11429       gfc_try t;
11430       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
11431       if (t == FAILURE)
11432         return FAILURE;
11433     }
11434
11435   /* Find next ancestor type and recurse on it.  */
11436   ancestor = gfc_get_derived_super_type (ancestor);
11437   if (ancestor)
11438     return ensure_not_abstract (sub, ancestor);
11439
11440   return SUCCESS;
11441 }
11442
11443
11444 /* Resolve the components of a derived type.  */
11445
11446 static gfc_try
11447 resolve_fl_derived (gfc_symbol *sym)
11448 {
11449   gfc_symbol* super_type;
11450   gfc_component *c;
11451
11452   super_type = gfc_get_derived_super_type (sym);
11453   
11454   if (sym->attr.is_class && sym->ts.u.derived == NULL)
11455     {
11456       /* Fix up incomplete CLASS symbols.  */
11457       gfc_component *data = gfc_find_component (sym, "_data", true, true);
11458       gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true);
11459       if (vptr->ts.u.derived == NULL)
11460         {
11461           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
11462           gcc_assert (vtab);
11463           vptr->ts.u.derived = vtab->ts.u.derived;
11464         }
11465     }
11466
11467   /* F2008, C432. */
11468   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
11469     {
11470       gfc_error ("As extending type '%s' at %L has a coarray component, "
11471                  "parent type '%s' shall also have one", sym->name,
11472                  &sym->declared_at, super_type->name);
11473       return FAILURE;
11474     }
11475
11476   /* Ensure the extended type gets resolved before we do.  */
11477   if (super_type && resolve_fl_derived (super_type) == FAILURE)
11478     return FAILURE;
11479
11480   /* An ABSTRACT type must be extensible.  */
11481   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
11482     {
11483       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
11484                  sym->name, &sym->declared_at);
11485       return FAILURE;
11486     }
11487
11488   for (c = sym->components; c != NULL; c = c->next)
11489     {
11490       /* F2008, C442.  */
11491       if (c->attr.codimension /* FIXME: c->as check due to PR 43412.  */
11492           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
11493         {
11494           gfc_error ("Coarray component '%s' at %L must be allocatable with "
11495                      "deferred shape", c->name, &c->loc);
11496           return FAILURE;
11497         }
11498
11499       /* F2008, C443.  */
11500       if (c->attr.codimension && c->ts.type == BT_DERIVED
11501           && c->ts.u.derived->ts.is_iso_c)
11502         {
11503           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11504                      "shall not be a coarray", c->name, &c->loc);
11505           return FAILURE;
11506         }
11507
11508       /* F2008, C444.  */
11509       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
11510           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
11511               || c->attr.allocatable))
11512         {
11513           gfc_error ("Component '%s' at %L with coarray component "
11514                      "shall be a nonpointer, nonallocatable scalar",
11515                      c->name, &c->loc);
11516           return FAILURE;
11517         }
11518
11519       /* F2008, C448.  */
11520       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
11521         {
11522           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
11523                      "is not an array pointer", c->name, &c->loc);
11524           return FAILURE;
11525         }
11526
11527       if (c->attr.proc_pointer && c->ts.interface)
11528         {
11529           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
11530             gfc_error ("Interface '%s', used by procedure pointer component "
11531                        "'%s' at %L, is declared in a later PROCEDURE statement",
11532                        c->ts.interface->name, c->name, &c->loc);
11533
11534           /* Get the attributes from the interface (now resolved).  */
11535           if (c->ts.interface->attr.if_source
11536               || c->ts.interface->attr.intrinsic)
11537             {
11538               gfc_symbol *ifc = c->ts.interface;
11539
11540               if (ifc->formal && !ifc->formal_ns)
11541                 resolve_symbol (ifc);
11542
11543               if (ifc->attr.intrinsic)
11544                 resolve_intrinsic (ifc, &ifc->declared_at);
11545
11546               if (ifc->result)
11547                 {
11548                   c->ts = ifc->result->ts;
11549                   c->attr.allocatable = ifc->result->attr.allocatable;
11550                   c->attr.pointer = ifc->result->attr.pointer;
11551                   c->attr.dimension = ifc->result->attr.dimension;
11552                   c->as = gfc_copy_array_spec (ifc->result->as);
11553                 }
11554               else
11555                 {   
11556                   c->ts = ifc->ts;
11557                   c->attr.allocatable = ifc->attr.allocatable;
11558                   c->attr.pointer = ifc->attr.pointer;
11559                   c->attr.dimension = ifc->attr.dimension;
11560                   c->as = gfc_copy_array_spec (ifc->as);
11561                 }
11562               c->ts.interface = ifc;
11563               c->attr.function = ifc->attr.function;
11564               c->attr.subroutine = ifc->attr.subroutine;
11565               gfc_copy_formal_args_ppc (c, ifc);
11566
11567               c->attr.pure = ifc->attr.pure;
11568               c->attr.elemental = ifc->attr.elemental;
11569               c->attr.recursive = ifc->attr.recursive;
11570               c->attr.always_explicit = ifc->attr.always_explicit;
11571               c->attr.ext_attr |= ifc->attr.ext_attr;
11572               /* Replace symbols in array spec.  */
11573               if (c->as)
11574                 {
11575                   int i;
11576                   for (i = 0; i < c->as->rank; i++)
11577                     {
11578                       gfc_expr_replace_comp (c->as->lower[i], c);
11579                       gfc_expr_replace_comp (c->as->upper[i], c);
11580                     }
11581                 }
11582               /* Copy char length.  */
11583               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11584                 {
11585                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11586                   gfc_expr_replace_comp (cl->length, c);
11587                   if (cl->length && !cl->resolved
11588                         && gfc_resolve_expr (cl->length) == FAILURE)
11589                     return FAILURE;
11590                   c->ts.u.cl = cl;
11591                 }
11592             }
11593           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
11594             {
11595               gfc_error ("Interface '%s' of procedure pointer component "
11596                          "'%s' at %L must be explicit", c->ts.interface->name,
11597                          c->name, &c->loc);
11598               return FAILURE;
11599             }
11600         }
11601       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
11602         {
11603           /* Since PPCs are not implicitly typed, a PPC without an explicit
11604              interface must be a subroutine.  */
11605           gfc_add_subroutine (&c->attr, c->name, &c->loc);
11606         }
11607
11608       /* Procedure pointer components: Check PASS arg.  */
11609       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
11610           && !sym->attr.vtype)
11611         {
11612           gfc_symbol* me_arg;
11613
11614           if (c->tb->pass_arg)
11615             {
11616               gfc_formal_arglist* i;
11617
11618               /* If an explicit passing argument name is given, walk the arg-list
11619                 and look for it.  */
11620
11621               me_arg = NULL;
11622               c->tb->pass_arg_num = 1;
11623               for (i = c->formal; i; i = i->next)
11624                 {
11625                   if (!strcmp (i->sym->name, c->tb->pass_arg))
11626                     {
11627                       me_arg = i->sym;
11628                       break;
11629                     }
11630                   c->tb->pass_arg_num++;
11631                 }
11632
11633               if (!me_arg)
11634                 {
11635                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
11636                              "at %L has no argument '%s'", c->name,
11637                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
11638                   c->tb->error = 1;
11639                   return FAILURE;
11640                 }
11641             }
11642           else
11643             {
11644               /* Otherwise, take the first one; there should in fact be at least
11645                 one.  */
11646               c->tb->pass_arg_num = 1;
11647               if (!c->formal)
11648                 {
11649                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
11650                              "must have at least one argument",
11651                              c->name, &c->loc);
11652                   c->tb->error = 1;
11653                   return FAILURE;
11654                 }
11655               me_arg = c->formal->sym;
11656             }
11657
11658           /* Now check that the argument-type matches.  */
11659           gcc_assert (me_arg);
11660           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
11661               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
11662               || (me_arg->ts.type == BT_CLASS
11663                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
11664             {
11665               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11666                          " the derived type '%s'", me_arg->name, c->name,
11667                          me_arg->name, &c->loc, sym->name);
11668               c->tb->error = 1;
11669               return FAILURE;
11670             }
11671
11672           /* Check for C453.  */
11673           if (me_arg->attr.dimension)
11674             {
11675               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11676                          "must be scalar", me_arg->name, c->name, me_arg->name,
11677                          &c->loc);
11678               c->tb->error = 1;
11679               return FAILURE;
11680             }
11681
11682           if (me_arg->attr.pointer)
11683             {
11684               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11685                          "may not have the POINTER attribute", me_arg->name,
11686                          c->name, me_arg->name, &c->loc);
11687               c->tb->error = 1;
11688               return FAILURE;
11689             }
11690
11691           if (me_arg->attr.allocatable)
11692             {
11693               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11694                          "may not be ALLOCATABLE", me_arg->name, c->name,
11695                          me_arg->name, &c->loc);
11696               c->tb->error = 1;
11697               return FAILURE;
11698             }
11699
11700           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11701             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11702                        " at %L", c->name, &c->loc);
11703
11704         }
11705
11706       /* Check type-spec if this is not the parent-type component.  */
11707       if ((!sym->attr.extension || c != sym->components) && !sym->attr.vtype
11708           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11709         return FAILURE;
11710
11711       /* If this type is an extension, set the accessibility of the parent
11712          component.  */
11713       if (super_type && c == sym->components
11714           && strcmp (super_type->name, c->name) == 0)
11715         c->attr.access = super_type->attr.access;
11716       
11717       /* If this type is an extension, see if this component has the same name
11718          as an inherited type-bound procedure.  */
11719       if (super_type && !sym->attr.is_class
11720           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11721         {
11722           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11723                      " inherited type-bound procedure",
11724                      c->name, sym->name, &c->loc);
11725           return FAILURE;
11726         }
11727
11728       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer
11729             && !c->ts.deferred)
11730         {
11731          if (c->ts.u.cl->length == NULL
11732              || (resolve_charlen (c->ts.u.cl) == FAILURE)
11733              || !gfc_is_constant_expr (c->ts.u.cl->length))
11734            {
11735              gfc_error ("Character length of component '%s' needs to "
11736                         "be a constant specification expression at %L",
11737                         c->name,
11738                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
11739              return FAILURE;
11740            }
11741         }
11742
11743       if (c->ts.type == BT_CHARACTER && c->ts.deferred
11744           && !c->attr.pointer && !c->attr.allocatable)
11745         {
11746           gfc_error ("Character component '%s' of '%s' at %L with deferred "
11747                      "length must be a POINTER or ALLOCATABLE",
11748                      c->name, sym->name, &c->loc);
11749           return FAILURE;
11750         }
11751
11752       if (c->ts.type == BT_DERIVED
11753           && sym->component_access != ACCESS_PRIVATE
11754           && gfc_check_symbol_access (sym)
11755           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11756           && !c->ts.u.derived->attr.use_assoc
11757           && !gfc_check_symbol_access (c->ts.u.derived)
11758           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11759                              "is a PRIVATE type and cannot be a component of "
11760                              "'%s', which is PUBLIC at %L", c->name,
11761                              sym->name, &sym->declared_at) == FAILURE)
11762         return FAILURE;
11763
11764       if ((sym->attr.sequence || sym->attr.is_bind_c) && c->ts.type == BT_CLASS)
11765         {
11766           gfc_error ("Polymorphic component %s at %L in SEQUENCE or BIND(C) "
11767                      "type %s", c->name, &c->loc, sym->name);
11768           return FAILURE;
11769         }
11770
11771       if (sym->attr.sequence)
11772         {
11773           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
11774             {
11775               gfc_error ("Component %s of SEQUENCE type declared at %L does "
11776                          "not have the SEQUENCE attribute",
11777                          c->ts.u.derived->name, &sym->declared_at);
11778               return FAILURE;
11779             }
11780         }
11781
11782       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && !sym->attr.vtype
11783           && c->attr.pointer && c->ts.u.derived->components == NULL
11784           && !c->ts.u.derived->attr.zero_comp)
11785         {
11786           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11787                      "that has not been declared", c->name, sym->name,
11788                      &c->loc);
11789           return FAILURE;
11790         }
11791
11792       if (c->ts.type == BT_CLASS && c->attr.class_ok
11793           && CLASS_DATA (c)->attr.class_pointer
11794           && CLASS_DATA (c)->ts.u.derived->components == NULL
11795           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
11796         {
11797           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11798                      "that has not been declared", c->name, sym->name,
11799                      &c->loc);
11800           return FAILURE;
11801         }
11802
11803       /* C437.  */
11804       if (c->ts.type == BT_CLASS && c->attr.flavor != FL_PROCEDURE
11805           && (!c->attr.class_ok
11806               || !(CLASS_DATA (c)->attr.class_pointer
11807                    || CLASS_DATA (c)->attr.allocatable)))
11808         {
11809           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
11810                      "or pointer", c->name, &c->loc);
11811           return FAILURE;
11812         }
11813
11814       /* Ensure that all the derived type components are put on the
11815          derived type list; even in formal namespaces, where derived type
11816          pointer components might not have been declared.  */
11817       if (c->ts.type == BT_DERIVED
11818             && c->ts.u.derived
11819             && c->ts.u.derived->components
11820             && c->attr.pointer
11821             && sym != c->ts.u.derived)
11822         add_dt_to_dt_list (c->ts.u.derived);
11823
11824       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
11825                                            || c->attr.proc_pointer
11826                                            || c->attr.allocatable)) == FAILURE)
11827         return FAILURE;
11828     }
11829
11830   /* Resolve the type-bound procedures.  */
11831   if (resolve_typebound_procedures (sym) == FAILURE)
11832     return FAILURE;
11833
11834   /* Resolve the finalizer procedures.  */
11835   if (gfc_resolve_finalizers (sym) == FAILURE)
11836     return FAILURE;
11837
11838   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11839      all DEFERRED bindings are overridden.  */
11840   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11841       && !sym->attr.is_class
11842       && ensure_not_abstract (sym, super_type) == FAILURE)
11843     return FAILURE;
11844
11845   /* Add derived type to the derived type list.  */
11846   add_dt_to_dt_list (sym);
11847
11848   return SUCCESS;
11849 }
11850
11851
11852 static gfc_try
11853 resolve_fl_namelist (gfc_symbol *sym)
11854 {
11855   gfc_namelist *nl;
11856   gfc_symbol *nlsym;
11857
11858   for (nl = sym->namelist; nl; nl = nl->next)
11859     {
11860       /* Check again, the check in match only works if NAMELIST comes
11861          after the decl.  */
11862       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SIZE)
11863         {
11864           gfc_error ("Assumed size array '%s' in namelist '%s' at %L is not "
11865                      "allowed", nl->sym->name, sym->name, &sym->declared_at);
11866           return FAILURE;
11867         }
11868
11869       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
11870           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: NAMELIST array "
11871                              "object '%s' with assumed shape in namelist "
11872                              "'%s' at %L", nl->sym->name, sym->name,
11873                              &sym->declared_at) == FAILURE)
11874         return FAILURE;
11875
11876       if (is_non_constant_shape_array (nl->sym)
11877           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST array "
11878                              "object '%s' with nonconstant shape in namelist "
11879                              "'%s' at %L", nl->sym->name, sym->name,
11880                              &sym->declared_at) == FAILURE)
11881         return FAILURE;
11882
11883       if (nl->sym->ts.type == BT_CHARACTER
11884           && (nl->sym->ts.u.cl->length == NULL
11885               || !gfc_is_constant_expr (nl->sym->ts.u.cl->length))
11886           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
11887                              "'%s' with nonconstant character length in "
11888                              "namelist '%s' at %L", nl->sym->name, sym->name,
11889                              &sym->declared_at) == FAILURE)
11890         return FAILURE;
11891
11892       /* FIXME: Once UDDTIO is implemented, the following can be
11893          removed.  */
11894       if (nl->sym->ts.type == BT_CLASS)
11895         {
11896           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L is "
11897                      "polymorphic and requires a defined input/output "
11898                      "procedure", nl->sym->name, sym->name, &sym->declared_at);
11899           return FAILURE;
11900         }
11901
11902       if (nl->sym->ts.type == BT_DERIVED
11903           && (nl->sym->ts.u.derived->attr.alloc_comp
11904               || nl->sym->ts.u.derived->attr.pointer_comp))
11905         {
11906           if (gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
11907                               "'%s' in namelist '%s' at %L with ALLOCATABLE "
11908                               "or POINTER components", nl->sym->name,
11909                               sym->name, &sym->declared_at) == FAILURE)
11910             return FAILURE;
11911
11912          /* FIXME: Once UDDTIO is implemented, the following can be
11913             removed.  */
11914           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L has "
11915                      "ALLOCATABLE or POINTER components and thus requires "
11916                      "a defined input/output procedure", nl->sym->name,
11917                      sym->name, &sym->declared_at);
11918           return FAILURE;
11919         }
11920     }
11921
11922   /* Reject PRIVATE objects in a PUBLIC namelist.  */
11923   if (gfc_check_symbol_access (sym))
11924     {
11925       for (nl = sym->namelist; nl; nl = nl->next)
11926         {
11927           if (!nl->sym->attr.use_assoc
11928               && !is_sym_host_assoc (nl->sym, sym->ns)
11929               && !gfc_check_symbol_access (nl->sym))
11930             {
11931               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
11932                          "cannot be member of PUBLIC namelist '%s' at %L",
11933                          nl->sym->name, sym->name, &sym->declared_at);
11934               return FAILURE;
11935             }
11936
11937           /* Types with private components that came here by USE-association.  */
11938           if (nl->sym->ts.type == BT_DERIVED
11939               && derived_inaccessible (nl->sym->ts.u.derived))
11940             {
11941               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
11942                          "components and cannot be member of namelist '%s' at %L",
11943                          nl->sym->name, sym->name, &sym->declared_at);
11944               return FAILURE;
11945             }
11946
11947           /* Types with private components that are defined in the same module.  */
11948           if (nl->sym->ts.type == BT_DERIVED
11949               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
11950               && nl->sym->ts.u.derived->attr.private_comp)
11951             {
11952               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
11953                          "cannot be a member of PUBLIC namelist '%s' at %L",
11954                          nl->sym->name, sym->name, &sym->declared_at);
11955               return FAILURE;
11956             }
11957         }
11958     }
11959
11960
11961   /* 14.1.2 A module or internal procedure represent local entities
11962      of the same type as a namelist member and so are not allowed.  */
11963   for (nl = sym->namelist; nl; nl = nl->next)
11964     {
11965       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
11966         continue;
11967
11968       if (nl->sym->attr.function && nl->sym == nl->sym->result)
11969         if ((nl->sym == sym->ns->proc_name)
11970                ||
11971             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
11972           continue;
11973
11974       nlsym = NULL;
11975       if (nl->sym && nl->sym->name)
11976         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
11977       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
11978         {
11979           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
11980                      "attribute in '%s' at %L", nlsym->name,
11981                      &sym->declared_at);
11982           return FAILURE;
11983         }
11984     }
11985
11986   return SUCCESS;
11987 }
11988
11989
11990 static gfc_try
11991 resolve_fl_parameter (gfc_symbol *sym)
11992 {
11993   /* A parameter array's shape needs to be constant.  */
11994   if (sym->as != NULL 
11995       && (sym->as->type == AS_DEFERRED
11996           || is_non_constant_shape_array (sym)))
11997     {
11998       gfc_error ("Parameter array '%s' at %L cannot be automatic "
11999                  "or of deferred shape", sym->name, &sym->declared_at);
12000       return FAILURE;
12001     }
12002
12003   /* Make sure a parameter that has been implicitly typed still
12004      matches the implicit type, since PARAMETER statements can precede
12005      IMPLICIT statements.  */
12006   if (sym->attr.implicit_type
12007       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
12008                                                              sym->ns)))
12009     {
12010       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
12011                  "later IMPLICIT type", sym->name, &sym->declared_at);
12012       return FAILURE;
12013     }
12014
12015   /* Make sure the types of derived parameters are consistent.  This
12016      type checking is deferred until resolution because the type may
12017      refer to a derived type from the host.  */
12018   if (sym->ts.type == BT_DERIVED
12019       && !gfc_compare_types (&sym->ts, &sym->value->ts))
12020     {
12021       gfc_error ("Incompatible derived type in PARAMETER at %L",
12022                  &sym->value->where);
12023       return FAILURE;
12024     }
12025   return SUCCESS;
12026 }
12027
12028
12029 /* Do anything necessary to resolve a symbol.  Right now, we just
12030    assume that an otherwise unknown symbol is a variable.  This sort
12031    of thing commonly happens for symbols in module.  */
12032
12033 static void
12034 resolve_symbol (gfc_symbol *sym)
12035 {
12036   int check_constant, mp_flag;
12037   gfc_symtree *symtree;
12038   gfc_symtree *this_symtree;
12039   gfc_namespace *ns;
12040   gfc_component *c;
12041
12042   if (sym->attr.flavor == FL_UNKNOWN)
12043     {
12044
12045     /* If we find that a flavorless symbol is an interface in one of the
12046        parent namespaces, find its symtree in this namespace, free the
12047        symbol and set the symtree to point to the interface symbol.  */
12048       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
12049         {
12050           symtree = gfc_find_symtree (ns->sym_root, sym->name);
12051           if (symtree && (symtree->n.sym->generic ||
12052                           (symtree->n.sym->attr.flavor == FL_PROCEDURE
12053                            && sym->ns->construct_entities)))
12054             {
12055               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
12056                                                sym->name);
12057               gfc_release_symbol (sym);
12058               symtree->n.sym->refs++;
12059               this_symtree->n.sym = symtree->n.sym;
12060               return;
12061             }
12062         }
12063
12064       /* Otherwise give it a flavor according to such attributes as
12065          it has.  */
12066       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
12067         sym->attr.flavor = FL_VARIABLE;
12068       else
12069         {
12070           sym->attr.flavor = FL_PROCEDURE;
12071           if (sym->attr.dimension)
12072             sym->attr.function = 1;
12073         }
12074     }
12075
12076   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
12077     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
12078
12079   if (sym->attr.procedure && sym->ts.interface
12080       && sym->attr.if_source != IFSRC_DECL
12081       && resolve_procedure_interface (sym) == FAILURE)
12082     return;
12083
12084   if (sym->attr.is_protected && !sym->attr.proc_pointer
12085       && (sym->attr.procedure || sym->attr.external))
12086     {
12087       if (sym->attr.external)
12088         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
12089                    "at %L", &sym->declared_at);
12090       else
12091         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
12092                    "at %L", &sym->declared_at);
12093
12094       return;
12095     }
12096
12097
12098   /* F2008, C530. */
12099   if (sym->attr.contiguous
12100       && (!sym->attr.dimension || (sym->as->type != AS_ASSUMED_SHAPE
12101                                    && !sym->attr.pointer)))
12102     {
12103       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
12104                   "array pointer or an assumed-shape array", sym->name,
12105                   &sym->declared_at);
12106       return;
12107     }
12108
12109   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
12110     return;
12111
12112   /* Symbols that are module procedures with results (functions) have
12113      the types and array specification copied for type checking in
12114      procedures that call them, as well as for saving to a module
12115      file.  These symbols can't stand the scrutiny that their results
12116      can.  */
12117   mp_flag = (sym->result != NULL && sym->result != sym);
12118
12119   /* Make sure that the intrinsic is consistent with its internal 
12120      representation. This needs to be done before assigning a default 
12121      type to avoid spurious warnings.  */
12122   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
12123       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
12124     return;
12125
12126   /* Resolve associate names.  */
12127   if (sym->assoc)
12128     resolve_assoc_var (sym, true);
12129
12130   /* Assign default type to symbols that need one and don't have one.  */
12131   if (sym->ts.type == BT_UNKNOWN)
12132     {
12133       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
12134         gfc_set_default_type (sym, 1, NULL);
12135
12136       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
12137           && !sym->attr.function && !sym->attr.subroutine
12138           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
12139         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
12140
12141       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12142         {
12143           /* The specific case of an external procedure should emit an error
12144              in the case that there is no implicit type.  */
12145           if (!mp_flag)
12146             gfc_set_default_type (sym, sym->attr.external, NULL);
12147           else
12148             {
12149               /* Result may be in another namespace.  */
12150               resolve_symbol (sym->result);
12151
12152               if (!sym->result->attr.proc_pointer)
12153                 {
12154                   sym->ts = sym->result->ts;
12155                   sym->as = gfc_copy_array_spec (sym->result->as);
12156                   sym->attr.dimension = sym->result->attr.dimension;
12157                   sym->attr.pointer = sym->result->attr.pointer;
12158                   sym->attr.allocatable = sym->result->attr.allocatable;
12159                   sym->attr.contiguous = sym->result->attr.contiguous;
12160                 }
12161             }
12162         }
12163     }
12164
12165   /* Assumed size arrays and assumed shape arrays must be dummy
12166      arguments.  Array-spec's of implied-shape should have been resolved to
12167      AS_EXPLICIT already.  */
12168
12169   if (sym->as)
12170     {
12171       gcc_assert (sym->as->type != AS_IMPLIED_SHAPE);
12172       if (((sym->as->type == AS_ASSUMED_SIZE && !sym->as->cp_was_assumed)
12173            || sym->as->type == AS_ASSUMED_SHAPE)
12174           && sym->attr.dummy == 0)
12175         {
12176           if (sym->as->type == AS_ASSUMED_SIZE)
12177             gfc_error ("Assumed size array at %L must be a dummy argument",
12178                        &sym->declared_at);
12179           else
12180             gfc_error ("Assumed shape array at %L must be a dummy argument",
12181                        &sym->declared_at);
12182           return;
12183         }
12184     }
12185
12186   /* Make sure symbols with known intent or optional are really dummy
12187      variable.  Because of ENTRY statement, this has to be deferred
12188      until resolution time.  */
12189
12190   if (!sym->attr.dummy
12191       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
12192     {
12193       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
12194       return;
12195     }
12196
12197   if (sym->attr.value && !sym->attr.dummy)
12198     {
12199       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
12200                  "it is not a dummy argument", sym->name, &sym->declared_at);
12201       return;
12202     }
12203
12204   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
12205     {
12206       gfc_charlen *cl = sym->ts.u.cl;
12207       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
12208         {
12209           gfc_error ("Character dummy variable '%s' at %L with VALUE "
12210                      "attribute must have constant length",
12211                      sym->name, &sym->declared_at);
12212           return;
12213         }
12214
12215       if (sym->ts.is_c_interop
12216           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
12217         {
12218           gfc_error ("C interoperable character dummy variable '%s' at %L "
12219                      "with VALUE attribute must have length one",
12220                      sym->name, &sym->declared_at);
12221           return;
12222         }
12223     }
12224
12225   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
12226      do this for something that was implicitly typed because that is handled
12227      in gfc_set_default_type.  Handle dummy arguments and procedure
12228      definitions separately.  Also, anything that is use associated is not
12229      handled here but instead is handled in the module it is declared in.
12230      Finally, derived type definitions are allowed to be BIND(C) since that
12231      only implies that they're interoperable, and they are checked fully for
12232      interoperability when a variable is declared of that type.  */
12233   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
12234       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
12235       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
12236     {
12237       gfc_try t = SUCCESS;
12238       
12239       /* First, make sure the variable is declared at the
12240          module-level scope (J3/04-007, Section 15.3).  */
12241       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
12242           sym->attr.in_common == 0)
12243         {
12244           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
12245                      "is neither a COMMON block nor declared at the "
12246                      "module level scope", sym->name, &(sym->declared_at));
12247           t = FAILURE;
12248         }
12249       else if (sym->common_head != NULL)
12250         {
12251           t = verify_com_block_vars_c_interop (sym->common_head);
12252         }
12253       else
12254         {
12255           /* If type() declaration, we need to verify that the components
12256              of the given type are all C interoperable, etc.  */
12257           if (sym->ts.type == BT_DERIVED &&
12258               sym->ts.u.derived->attr.is_c_interop != 1)
12259             {
12260               /* Make sure the user marked the derived type as BIND(C).  If
12261                  not, call the verify routine.  This could print an error
12262                  for the derived type more than once if multiple variables
12263                  of that type are declared.  */
12264               if (sym->ts.u.derived->attr.is_bind_c != 1)
12265                 verify_bind_c_derived_type (sym->ts.u.derived);
12266               t = FAILURE;
12267             }
12268           
12269           /* Verify the variable itself as C interoperable if it
12270              is BIND(C).  It is not possible for this to succeed if
12271              the verify_bind_c_derived_type failed, so don't have to handle
12272              any error returned by verify_bind_c_derived_type.  */
12273           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
12274                                  sym->common_block);
12275         }
12276
12277       if (t == FAILURE)
12278         {
12279           /* clear the is_bind_c flag to prevent reporting errors more than
12280              once if something failed.  */
12281           sym->attr.is_bind_c = 0;
12282           return;
12283         }
12284     }
12285
12286   /* If a derived type symbol has reached this point, without its
12287      type being declared, we have an error.  Notice that most
12288      conditions that produce undefined derived types have already
12289      been dealt with.  However, the likes of:
12290      implicit type(t) (t) ..... call foo (t) will get us here if
12291      the type is not declared in the scope of the implicit
12292      statement. Change the type to BT_UNKNOWN, both because it is so
12293      and to prevent an ICE.  */
12294   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
12295       && !sym->ts.u.derived->attr.zero_comp)
12296     {
12297       gfc_error ("The derived type '%s' at %L is of type '%s', "
12298                  "which has not been defined", sym->name,
12299                   &sym->declared_at, sym->ts.u.derived->name);
12300       sym->ts.type = BT_UNKNOWN;
12301       return;
12302     }
12303
12304   /* Make sure that the derived type has been resolved and that the
12305      derived type is visible in the symbol's namespace, if it is a
12306      module function and is not PRIVATE.  */
12307   if (sym->ts.type == BT_DERIVED
12308         && sym->ts.u.derived->attr.use_assoc
12309         && sym->ns->proc_name
12310         && sym->ns->proc_name->attr.flavor == FL_MODULE)
12311     {
12312       gfc_symbol *ds;
12313
12314       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
12315         return;
12316
12317       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
12318       if (!ds && sym->attr.function && gfc_check_symbol_access (sym))
12319         {
12320           symtree = gfc_new_symtree (&sym->ns->sym_root,
12321                                      sym->ts.u.derived->name);
12322           symtree->n.sym = sym->ts.u.derived;
12323           sym->ts.u.derived->refs++;
12324         }
12325     }
12326
12327   /* Unless the derived-type declaration is use associated, Fortran 95
12328      does not allow public entries of private derived types.
12329      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
12330      161 in 95-006r3.  */
12331   if (sym->ts.type == BT_DERIVED
12332       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
12333       && !sym->ts.u.derived->attr.use_assoc
12334       && gfc_check_symbol_access (sym)
12335       && !gfc_check_symbol_access (sym->ts.u.derived)
12336       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
12337                          "of PRIVATE derived type '%s'",
12338                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
12339                          : "variable", sym->name, &sym->declared_at,
12340                          sym->ts.u.derived->name) == FAILURE)
12341     return;
12342
12343   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
12344      default initialization is defined (5.1.2.4.4).  */
12345   if (sym->ts.type == BT_DERIVED
12346       && sym->attr.dummy
12347       && sym->attr.intent == INTENT_OUT
12348       && sym->as
12349       && sym->as->type == AS_ASSUMED_SIZE)
12350     {
12351       for (c = sym->ts.u.derived->components; c; c = c->next)
12352         {
12353           if (c->initializer)
12354             {
12355               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
12356                          "ASSUMED SIZE and so cannot have a default initializer",
12357                          sym->name, &sym->declared_at);
12358               return;
12359             }
12360         }
12361     }
12362
12363   /* F2008, C526.  */
12364   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12365        || sym->attr.codimension)
12366       && sym->attr.result)
12367     gfc_error ("Function result '%s' at %L shall not be a coarray or have "
12368                "a coarray component", sym->name, &sym->declared_at);
12369
12370   /* F2008, C524.  */
12371   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
12372       && sym->ts.u.derived->ts.is_iso_c)
12373     gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12374                "shall not be a coarray", sym->name, &sym->declared_at);
12375
12376   /* F2008, C525.  */
12377   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp
12378       && (sym->attr.codimension || sym->attr.pointer || sym->attr.dimension
12379           || sym->attr.allocatable))
12380     gfc_error ("Variable '%s' at %L with coarray component "
12381                "shall be a nonpointer, nonallocatable scalar",
12382                sym->name, &sym->declared_at);
12383
12384   /* F2008, C526.  The function-result case was handled above.  */
12385   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12386        || sym->attr.codimension)
12387       && !(sym->attr.allocatable || sym->attr.dummy || sym->attr.save
12388            || sym->ns->save_all
12389            || sym->ns->proc_name->attr.flavor == FL_MODULE
12390            || sym->ns->proc_name->attr.is_main_program
12391            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
12392     gfc_error ("Variable '%s' at %L is a coarray or has a coarray "
12393                "component and is not ALLOCATABLE, SAVE nor a "
12394                "dummy argument", sym->name, &sym->declared_at);
12395   /* F2008, C528.  */  /* FIXME: sym->as check due to PR 43412.  */
12396   else if (sym->attr.codimension && !sym->attr.allocatable
12397       && sym->as && sym->as->cotype == AS_DEFERRED)
12398     gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
12399                 "deferred shape", sym->name, &sym->declared_at);
12400   else if (sym->attr.codimension && sym->attr.allocatable
12401       && (sym->as->type != AS_DEFERRED || sym->as->cotype != AS_DEFERRED))
12402     gfc_error ("Allocatable coarray variable '%s' at %L must have "
12403                "deferred shape", sym->name, &sym->declared_at);
12404
12405
12406   /* F2008, C541.  */
12407   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12408        || (sym->attr.codimension && sym->attr.allocatable))
12409       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
12410     gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
12411                "allocatable coarray or have coarray components",
12412                sym->name, &sym->declared_at);
12413
12414   if (sym->attr.codimension && sym->attr.dummy
12415       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
12416     gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
12417                "procedure '%s'", sym->name, &sym->declared_at,
12418                sym->ns->proc_name->name);
12419
12420   switch (sym->attr.flavor)
12421     {
12422     case FL_VARIABLE:
12423       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
12424         return;
12425       break;
12426
12427     case FL_PROCEDURE:
12428       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
12429         return;
12430       break;
12431
12432     case FL_NAMELIST:
12433       if (resolve_fl_namelist (sym) == FAILURE)
12434         return;
12435       break;
12436
12437     case FL_PARAMETER:
12438       if (resolve_fl_parameter (sym) == FAILURE)
12439         return;
12440       break;
12441
12442     default:
12443       break;
12444     }
12445
12446   /* Resolve array specifier. Check as well some constraints
12447      on COMMON blocks.  */
12448
12449   check_constant = sym->attr.in_common && !sym->attr.pointer;
12450
12451   /* Set the formal_arg_flag so that check_conflict will not throw
12452      an error for host associated variables in the specification
12453      expression for an array_valued function.  */
12454   if (sym->attr.function && sym->as)
12455     formal_arg_flag = 1;
12456
12457   gfc_resolve_array_spec (sym->as, check_constant);
12458
12459   formal_arg_flag = 0;
12460
12461   /* Resolve formal namespaces.  */
12462   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
12463       && !sym->attr.contained && !sym->attr.intrinsic)
12464     gfc_resolve (sym->formal_ns);
12465
12466   /* Make sure the formal namespace is present.  */
12467   if (sym->formal && !sym->formal_ns)
12468     {
12469       gfc_formal_arglist *formal = sym->formal;
12470       while (formal && !formal->sym)
12471         formal = formal->next;
12472
12473       if (formal)
12474         {
12475           sym->formal_ns = formal->sym->ns;
12476           sym->formal_ns->refs++;
12477         }
12478     }
12479
12480   /* Check threadprivate restrictions.  */
12481   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
12482       && (!sym->attr.in_common
12483           && sym->module == NULL
12484           && (sym->ns->proc_name == NULL
12485               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
12486     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
12487
12488   /* If we have come this far we can apply default-initializers, as
12489      described in 14.7.5, to those variables that have not already
12490      been assigned one.  */
12491   if (sym->ts.type == BT_DERIVED
12492       && sym->ns == gfc_current_ns
12493       && !sym->value
12494       && !sym->attr.allocatable
12495       && !sym->attr.alloc_comp)
12496     {
12497       symbol_attribute *a = &sym->attr;
12498
12499       if ((!a->save && !a->dummy && !a->pointer
12500            && !a->in_common && !a->use_assoc
12501            && (a->referenced || a->result)
12502            && !(a->function && sym != sym->result))
12503           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
12504         apply_default_init (sym);
12505     }
12506
12507   if (sym->ts.type == BT_CLASS && sym->ns == gfc_current_ns
12508       && sym->attr.dummy && sym->attr.intent == INTENT_OUT
12509       && !CLASS_DATA (sym)->attr.class_pointer
12510       && !CLASS_DATA (sym)->attr.allocatable)
12511     apply_default_init (sym);
12512
12513   /* If this symbol has a type-spec, check it.  */
12514   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
12515       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
12516     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
12517           == FAILURE)
12518       return;
12519 }
12520
12521
12522 /************* Resolve DATA statements *************/
12523
12524 static struct
12525 {
12526   gfc_data_value *vnode;
12527   mpz_t left;
12528 }
12529 values;
12530
12531
12532 /* Advance the values structure to point to the next value in the data list.  */
12533
12534 static gfc_try
12535 next_data_value (void)
12536 {
12537   while (mpz_cmp_ui (values.left, 0) == 0)
12538     {
12539
12540       if (values.vnode->next == NULL)
12541         return FAILURE;
12542
12543       values.vnode = values.vnode->next;
12544       mpz_set (values.left, values.vnode->repeat);
12545     }
12546
12547   return SUCCESS;
12548 }
12549
12550
12551 static gfc_try
12552 check_data_variable (gfc_data_variable *var, locus *where)
12553 {
12554   gfc_expr *e;
12555   mpz_t size;
12556   mpz_t offset;
12557   gfc_try t;
12558   ar_type mark = AR_UNKNOWN;
12559   int i;
12560   mpz_t section_index[GFC_MAX_DIMENSIONS];
12561   gfc_ref *ref;
12562   gfc_array_ref *ar;
12563   gfc_symbol *sym;
12564   int has_pointer;
12565
12566   if (gfc_resolve_expr (var->expr) == FAILURE)
12567     return FAILURE;
12568
12569   ar = NULL;
12570   mpz_init_set_si (offset, 0);
12571   e = var->expr;
12572
12573   if (e->expr_type != EXPR_VARIABLE)
12574     gfc_internal_error ("check_data_variable(): Bad expression");
12575
12576   sym = e->symtree->n.sym;
12577
12578   if (sym->ns->is_block_data && !sym->attr.in_common)
12579     {
12580       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
12581                  sym->name, &sym->declared_at);
12582     }
12583
12584   if (e->ref == NULL && sym->as)
12585     {
12586       gfc_error ("DATA array '%s' at %L must be specified in a previous"
12587                  " declaration", sym->name, where);
12588       return FAILURE;
12589     }
12590
12591   has_pointer = sym->attr.pointer;
12592
12593   if (gfc_is_coindexed (e))
12594     {
12595       gfc_error ("DATA element '%s' at %L cannot have a coindex", sym->name,
12596                  where);
12597       return FAILURE;
12598     }
12599
12600   for (ref = e->ref; ref; ref = ref->next)
12601     {
12602       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
12603         has_pointer = 1;
12604
12605       if (has_pointer
12606             && ref->type == REF_ARRAY
12607             && ref->u.ar.type != AR_FULL)
12608           {
12609             gfc_error ("DATA element '%s' at %L is a pointer and so must "
12610                         "be a full array", sym->name, where);
12611             return FAILURE;
12612           }
12613     }
12614
12615   if (e->rank == 0 || has_pointer)
12616     {
12617       mpz_init_set_ui (size, 1);
12618       ref = NULL;
12619     }
12620   else
12621     {
12622       ref = e->ref;
12623
12624       /* Find the array section reference.  */
12625       for (ref = e->ref; ref; ref = ref->next)
12626         {
12627           if (ref->type != REF_ARRAY)
12628             continue;
12629           if (ref->u.ar.type == AR_ELEMENT)
12630             continue;
12631           break;
12632         }
12633       gcc_assert (ref);
12634
12635       /* Set marks according to the reference pattern.  */
12636       switch (ref->u.ar.type)
12637         {
12638         case AR_FULL:
12639           mark = AR_FULL;
12640           break;
12641
12642         case AR_SECTION:
12643           ar = &ref->u.ar;
12644           /* Get the start position of array section.  */
12645           gfc_get_section_index (ar, section_index, &offset);
12646           mark = AR_SECTION;
12647           break;
12648
12649         default:
12650           gcc_unreachable ();
12651         }
12652
12653       if (gfc_array_size (e, &size) == FAILURE)
12654         {
12655           gfc_error ("Nonconstant array section at %L in DATA statement",
12656                      &e->where);
12657           mpz_clear (offset);
12658           return FAILURE;
12659         }
12660     }
12661
12662   t = SUCCESS;
12663
12664   while (mpz_cmp_ui (size, 0) > 0)
12665     {
12666       if (next_data_value () == FAILURE)
12667         {
12668           gfc_error ("DATA statement at %L has more variables than values",
12669                      where);
12670           t = FAILURE;
12671           break;
12672         }
12673
12674       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
12675       if (t == FAILURE)
12676         break;
12677
12678       /* If we have more than one element left in the repeat count,
12679          and we have more than one element left in the target variable,
12680          then create a range assignment.  */
12681       /* FIXME: Only done for full arrays for now, since array sections
12682          seem tricky.  */
12683       if (mark == AR_FULL && ref && ref->next == NULL
12684           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
12685         {
12686           mpz_t range;
12687
12688           if (mpz_cmp (size, values.left) >= 0)
12689             {
12690               mpz_init_set (range, values.left);
12691               mpz_sub (size, size, values.left);
12692               mpz_set_ui (values.left, 0);
12693             }
12694           else
12695             {
12696               mpz_init_set (range, size);
12697               mpz_sub (values.left, values.left, size);
12698               mpz_set_ui (size, 0);
12699             }
12700
12701           t = gfc_assign_data_value_range (var->expr, values.vnode->expr,
12702                                            offset, range);
12703
12704           mpz_add (offset, offset, range);
12705           mpz_clear (range);
12706
12707           if (t == FAILURE)
12708             break;
12709         }
12710
12711       /* Assign initial value to symbol.  */
12712       else
12713         {
12714           mpz_sub_ui (values.left, values.left, 1);
12715           mpz_sub_ui (size, size, 1);
12716
12717           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
12718           if (t == FAILURE)
12719             break;
12720
12721           if (mark == AR_FULL)
12722             mpz_add_ui (offset, offset, 1);
12723
12724           /* Modify the array section indexes and recalculate the offset
12725              for next element.  */
12726           else if (mark == AR_SECTION)
12727             gfc_advance_section (section_index, ar, &offset);
12728         }
12729     }
12730
12731   if (mark == AR_SECTION)
12732     {
12733       for (i = 0; i < ar->dimen; i++)
12734         mpz_clear (section_index[i]);
12735     }
12736
12737   mpz_clear (size);
12738   mpz_clear (offset);
12739
12740   return t;
12741 }
12742
12743
12744 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
12745
12746 /* Iterate over a list of elements in a DATA statement.  */
12747
12748 static gfc_try
12749 traverse_data_list (gfc_data_variable *var, locus *where)
12750 {
12751   mpz_t trip;
12752   iterator_stack frame;
12753   gfc_expr *e, *start, *end, *step;
12754   gfc_try retval = SUCCESS;
12755
12756   mpz_init (frame.value);
12757   mpz_init (trip);
12758
12759   start = gfc_copy_expr (var->iter.start);
12760   end = gfc_copy_expr (var->iter.end);
12761   step = gfc_copy_expr (var->iter.step);
12762
12763   if (gfc_simplify_expr (start, 1) == FAILURE
12764       || start->expr_type != EXPR_CONSTANT)
12765     {
12766       gfc_error ("start of implied-do loop at %L could not be "
12767                  "simplified to a constant value", &start->where);
12768       retval = FAILURE;
12769       goto cleanup;
12770     }
12771   if (gfc_simplify_expr (end, 1) == FAILURE
12772       || end->expr_type != EXPR_CONSTANT)
12773     {
12774       gfc_error ("end of implied-do loop at %L could not be "
12775                  "simplified to a constant value", &start->where);
12776       retval = FAILURE;
12777       goto cleanup;
12778     }
12779   if (gfc_simplify_expr (step, 1) == FAILURE
12780       || step->expr_type != EXPR_CONSTANT)
12781     {
12782       gfc_error ("step of implied-do loop at %L could not be "
12783                  "simplified to a constant value", &start->where);
12784       retval = FAILURE;
12785       goto cleanup;
12786     }
12787
12788   mpz_set (trip, end->value.integer);
12789   mpz_sub (trip, trip, start->value.integer);
12790   mpz_add (trip, trip, step->value.integer);
12791
12792   mpz_div (trip, trip, step->value.integer);
12793
12794   mpz_set (frame.value, start->value.integer);
12795
12796   frame.prev = iter_stack;
12797   frame.variable = var->iter.var->symtree;
12798   iter_stack = &frame;
12799
12800   while (mpz_cmp_ui (trip, 0) > 0)
12801     {
12802       if (traverse_data_var (var->list, where) == FAILURE)
12803         {
12804           retval = FAILURE;
12805           goto cleanup;
12806         }
12807
12808       e = gfc_copy_expr (var->expr);
12809       if (gfc_simplify_expr (e, 1) == FAILURE)
12810         {
12811           gfc_free_expr (e);
12812           retval = FAILURE;
12813           goto cleanup;
12814         }
12815
12816       mpz_add (frame.value, frame.value, step->value.integer);
12817
12818       mpz_sub_ui (trip, trip, 1);
12819     }
12820
12821 cleanup:
12822   mpz_clear (frame.value);
12823   mpz_clear (trip);
12824
12825   gfc_free_expr (start);
12826   gfc_free_expr (end);
12827   gfc_free_expr (step);
12828
12829   iter_stack = frame.prev;
12830   return retval;
12831 }
12832
12833
12834 /* Type resolve variables in the variable list of a DATA statement.  */
12835
12836 static gfc_try
12837 traverse_data_var (gfc_data_variable *var, locus *where)
12838 {
12839   gfc_try t;
12840
12841   for (; var; var = var->next)
12842     {
12843       if (var->expr == NULL)
12844         t = traverse_data_list (var, where);
12845       else
12846         t = check_data_variable (var, where);
12847
12848       if (t == FAILURE)
12849         return FAILURE;
12850     }
12851
12852   return SUCCESS;
12853 }
12854
12855
12856 /* Resolve the expressions and iterators associated with a data statement.
12857    This is separate from the assignment checking because data lists should
12858    only be resolved once.  */
12859
12860 static gfc_try
12861 resolve_data_variables (gfc_data_variable *d)
12862 {
12863   for (; d; d = d->next)
12864     {
12865       if (d->list == NULL)
12866         {
12867           if (gfc_resolve_expr (d->expr) == FAILURE)
12868             return FAILURE;
12869         }
12870       else
12871         {
12872           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
12873             return FAILURE;
12874
12875           if (resolve_data_variables (d->list) == FAILURE)
12876             return FAILURE;
12877         }
12878     }
12879
12880   return SUCCESS;
12881 }
12882
12883
12884 /* Resolve a single DATA statement.  We implement this by storing a pointer to
12885    the value list into static variables, and then recursively traversing the
12886    variables list, expanding iterators and such.  */
12887
12888 static void
12889 resolve_data (gfc_data *d)
12890 {
12891
12892   if (resolve_data_variables (d->var) == FAILURE)
12893     return;
12894
12895   values.vnode = d->value;
12896   if (d->value == NULL)
12897     mpz_set_ui (values.left, 0);
12898   else
12899     mpz_set (values.left, d->value->repeat);
12900
12901   if (traverse_data_var (d->var, &d->where) == FAILURE)
12902     return;
12903
12904   /* At this point, we better not have any values left.  */
12905
12906   if (next_data_value () == SUCCESS)
12907     gfc_error ("DATA statement at %L has more values than variables",
12908                &d->where);
12909 }
12910
12911
12912 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
12913    accessed by host or use association, is a dummy argument to a pure function,
12914    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
12915    is storage associated with any such variable, shall not be used in the
12916    following contexts: (clients of this function).  */
12917
12918 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
12919    procedure.  Returns zero if assignment is OK, nonzero if there is a
12920    problem.  */
12921 int
12922 gfc_impure_variable (gfc_symbol *sym)
12923 {
12924   gfc_symbol *proc;
12925   gfc_namespace *ns;
12926
12927   if (sym->attr.use_assoc || sym->attr.in_common)
12928     return 1;
12929
12930   /* Check if the symbol's ns is inside the pure procedure.  */
12931   for (ns = gfc_current_ns; ns; ns = ns->parent)
12932     {
12933       if (ns == sym->ns)
12934         break;
12935       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
12936         return 1;
12937     }
12938
12939   proc = sym->ns->proc_name;
12940   if (sym->attr.dummy && gfc_pure (proc)
12941         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
12942                 ||
12943              proc->attr.function))
12944     return 1;
12945
12946   /* TODO: Sort out what can be storage associated, if anything, and include
12947      it here.  In principle equivalences should be scanned but it does not
12948      seem to be possible to storage associate an impure variable this way.  */
12949   return 0;
12950 }
12951
12952
12953 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
12954    current namespace is inside a pure procedure.  */
12955
12956 int
12957 gfc_pure (gfc_symbol *sym)
12958 {
12959   symbol_attribute attr;
12960   gfc_namespace *ns;
12961
12962   if (sym == NULL)
12963     {
12964       /* Check if the current namespace or one of its parents
12965         belongs to a pure procedure.  */
12966       for (ns = gfc_current_ns; ns; ns = ns->parent)
12967         {
12968           sym = ns->proc_name;
12969           if (sym == NULL)
12970             return 0;
12971           attr = sym->attr;
12972           if (attr.flavor == FL_PROCEDURE && attr.pure)
12973             return 1;
12974         }
12975       return 0;
12976     }
12977
12978   attr = sym->attr;
12979
12980   return attr.flavor == FL_PROCEDURE && attr.pure;
12981 }
12982
12983
12984 /* Test whether a symbol is implicitly pure or not.  For a NULL pointer,
12985    checks if the current namespace is implicitly pure.  Note that this
12986    function returns false for a PURE procedure.  */
12987
12988 int
12989 gfc_implicit_pure (gfc_symbol *sym)
12990 {
12991   symbol_attribute attr;
12992
12993   if (sym == NULL)
12994     {
12995       /* Check if the current namespace is implicit_pure.  */
12996       sym = gfc_current_ns->proc_name;
12997       if (sym == NULL)
12998         return 0;
12999       attr = sym->attr;
13000       if (attr.flavor == FL_PROCEDURE
13001             && attr.implicit_pure && !attr.pure)
13002         return 1;
13003       return 0;
13004     }
13005
13006   attr = sym->attr;
13007
13008   return attr.flavor == FL_PROCEDURE && attr.implicit_pure && !attr.pure;
13009 }
13010
13011
13012 /* Test whether the current procedure is elemental or not.  */
13013
13014 int
13015 gfc_elemental (gfc_symbol *sym)
13016 {
13017   symbol_attribute attr;
13018
13019   if (sym == NULL)
13020     sym = gfc_current_ns->proc_name;
13021   if (sym == NULL)
13022     return 0;
13023   attr = sym->attr;
13024
13025   return attr.flavor == FL_PROCEDURE && attr.elemental;
13026 }
13027
13028
13029 /* Warn about unused labels.  */
13030
13031 static void
13032 warn_unused_fortran_label (gfc_st_label *label)
13033 {
13034   if (label == NULL)
13035     return;
13036
13037   warn_unused_fortran_label (label->left);
13038
13039   if (label->defined == ST_LABEL_UNKNOWN)
13040     return;
13041
13042   switch (label->referenced)
13043     {
13044     case ST_LABEL_UNKNOWN:
13045       gfc_warning ("Label %d at %L defined but not used", label->value,
13046                    &label->where);
13047       break;
13048
13049     case ST_LABEL_BAD_TARGET:
13050       gfc_warning ("Label %d at %L defined but cannot be used",
13051                    label->value, &label->where);
13052       break;
13053
13054     default:
13055       break;
13056     }
13057
13058   warn_unused_fortran_label (label->right);
13059 }
13060
13061
13062 /* Returns the sequence type of a symbol or sequence.  */
13063
13064 static seq_type
13065 sequence_type (gfc_typespec ts)
13066 {
13067   seq_type result;
13068   gfc_component *c;
13069
13070   switch (ts.type)
13071   {
13072     case BT_DERIVED:
13073
13074       if (ts.u.derived->components == NULL)
13075         return SEQ_NONDEFAULT;
13076
13077       result = sequence_type (ts.u.derived->components->ts);
13078       for (c = ts.u.derived->components->next; c; c = c->next)
13079         if (sequence_type (c->ts) != result)
13080           return SEQ_MIXED;
13081
13082       return result;
13083
13084     case BT_CHARACTER:
13085       if (ts.kind != gfc_default_character_kind)
13086           return SEQ_NONDEFAULT;
13087
13088       return SEQ_CHARACTER;
13089
13090     case BT_INTEGER:
13091       if (ts.kind != gfc_default_integer_kind)
13092           return SEQ_NONDEFAULT;
13093
13094       return SEQ_NUMERIC;
13095
13096     case BT_REAL:
13097       if (!(ts.kind == gfc_default_real_kind
13098             || ts.kind == gfc_default_double_kind))
13099           return SEQ_NONDEFAULT;
13100
13101       return SEQ_NUMERIC;
13102
13103     case BT_COMPLEX:
13104       if (ts.kind != gfc_default_complex_kind)
13105           return SEQ_NONDEFAULT;
13106
13107       return SEQ_NUMERIC;
13108
13109     case BT_LOGICAL:
13110       if (ts.kind != gfc_default_logical_kind)
13111           return SEQ_NONDEFAULT;
13112
13113       return SEQ_NUMERIC;
13114
13115     default:
13116       return SEQ_NONDEFAULT;
13117   }
13118 }
13119
13120
13121 /* Resolve derived type EQUIVALENCE object.  */
13122
13123 static gfc_try
13124 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
13125 {
13126   gfc_component *c = derived->components;
13127
13128   if (!derived)
13129     return SUCCESS;
13130
13131   /* Shall not be an object of nonsequence derived type.  */
13132   if (!derived->attr.sequence)
13133     {
13134       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
13135                  "attribute to be an EQUIVALENCE object", sym->name,
13136                  &e->where);
13137       return FAILURE;
13138     }
13139
13140   /* Shall not have allocatable components.  */
13141   if (derived->attr.alloc_comp)
13142     {
13143       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
13144                  "components to be an EQUIVALENCE object",sym->name,
13145                  &e->where);
13146       return FAILURE;
13147     }
13148
13149   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
13150     {
13151       gfc_error ("Derived type variable '%s' at %L with default "
13152                  "initialization cannot be in EQUIVALENCE with a variable "
13153                  "in COMMON", sym->name, &e->where);
13154       return FAILURE;
13155     }
13156
13157   for (; c ; c = c->next)
13158     {
13159       if (c->ts.type == BT_DERIVED
13160           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
13161         return FAILURE;
13162
13163       /* Shall not be an object of sequence derived type containing a pointer
13164          in the structure.  */
13165       if (c->attr.pointer)
13166         {
13167           gfc_error ("Derived type variable '%s' at %L with pointer "
13168                      "component(s) cannot be an EQUIVALENCE object",
13169                      sym->name, &e->where);
13170           return FAILURE;
13171         }
13172     }
13173   return SUCCESS;
13174 }
13175
13176
13177 /* Resolve equivalence object. 
13178    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
13179    an allocatable array, an object of nonsequence derived type, an object of
13180    sequence derived type containing a pointer at any level of component
13181    selection, an automatic object, a function name, an entry name, a result
13182    name, a named constant, a structure component, or a subobject of any of
13183    the preceding objects.  A substring shall not have length zero.  A
13184    derived type shall not have components with default initialization nor
13185    shall two objects of an equivalence group be initialized.
13186    Either all or none of the objects shall have an protected attribute.
13187    The simple constraints are done in symbol.c(check_conflict) and the rest
13188    are implemented here.  */
13189
13190 static void
13191 resolve_equivalence (gfc_equiv *eq)
13192 {
13193   gfc_symbol *sym;
13194   gfc_symbol *first_sym;
13195   gfc_expr *e;
13196   gfc_ref *r;
13197   locus *last_where = NULL;
13198   seq_type eq_type, last_eq_type;
13199   gfc_typespec *last_ts;
13200   int object, cnt_protected;
13201   const char *msg;
13202
13203   last_ts = &eq->expr->symtree->n.sym->ts;
13204
13205   first_sym = eq->expr->symtree->n.sym;
13206
13207   cnt_protected = 0;
13208
13209   for (object = 1; eq; eq = eq->eq, object++)
13210     {
13211       e = eq->expr;
13212
13213       e->ts = e->symtree->n.sym->ts;
13214       /* match_varspec might not know yet if it is seeing
13215          array reference or substring reference, as it doesn't
13216          know the types.  */
13217       if (e->ref && e->ref->type == REF_ARRAY)
13218         {
13219           gfc_ref *ref = e->ref;
13220           sym = e->symtree->n.sym;
13221
13222           if (sym->attr.dimension)
13223             {
13224               ref->u.ar.as = sym->as;
13225               ref = ref->next;
13226             }
13227
13228           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
13229           if (e->ts.type == BT_CHARACTER
13230               && ref
13231               && ref->type == REF_ARRAY
13232               && ref->u.ar.dimen == 1
13233               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
13234               && ref->u.ar.stride[0] == NULL)
13235             {
13236               gfc_expr *start = ref->u.ar.start[0];
13237               gfc_expr *end = ref->u.ar.end[0];
13238               void *mem = NULL;
13239
13240               /* Optimize away the (:) reference.  */
13241               if (start == NULL && end == NULL)
13242                 {
13243                   if (e->ref == ref)
13244                     e->ref = ref->next;
13245                   else
13246                     e->ref->next = ref->next;
13247                   mem = ref;
13248                 }
13249               else
13250                 {
13251                   ref->type = REF_SUBSTRING;
13252                   if (start == NULL)
13253                     start = gfc_get_int_expr (gfc_default_integer_kind,
13254                                               NULL, 1);
13255                   ref->u.ss.start = start;
13256                   if (end == NULL && e->ts.u.cl)
13257                     end = gfc_copy_expr (e->ts.u.cl->length);
13258                   ref->u.ss.end = end;
13259                   ref->u.ss.length = e->ts.u.cl;
13260                   e->ts.u.cl = NULL;
13261                 }
13262               ref = ref->next;
13263               free (mem);
13264             }
13265
13266           /* Any further ref is an error.  */
13267           if (ref)
13268             {
13269               gcc_assert (ref->type == REF_ARRAY);
13270               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
13271                          &ref->u.ar.where);
13272               continue;
13273             }
13274         }
13275
13276       if (gfc_resolve_expr (e) == FAILURE)
13277         continue;
13278
13279       sym = e->symtree->n.sym;
13280
13281       if (sym->attr.is_protected)
13282         cnt_protected++;
13283       if (cnt_protected > 0 && cnt_protected != object)
13284         {
13285               gfc_error ("Either all or none of the objects in the "
13286                          "EQUIVALENCE set at %L shall have the "
13287                          "PROTECTED attribute",
13288                          &e->where);
13289               break;
13290         }
13291
13292       /* Shall not equivalence common block variables in a PURE procedure.  */
13293       if (sym->ns->proc_name
13294           && sym->ns->proc_name->attr.pure
13295           && sym->attr.in_common)
13296         {
13297           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
13298                      "object in the pure procedure '%s'",
13299                      sym->name, &e->where, sym->ns->proc_name->name);
13300           break;
13301         }
13302
13303       /* Shall not be a named constant.  */
13304       if (e->expr_type == EXPR_CONSTANT)
13305         {
13306           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
13307                      "object", sym->name, &e->where);
13308           continue;
13309         }
13310
13311       if (e->ts.type == BT_DERIVED
13312           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
13313         continue;
13314
13315       /* Check that the types correspond correctly:
13316          Note 5.28:
13317          A numeric sequence structure may be equivalenced to another sequence
13318          structure, an object of default integer type, default real type, double
13319          precision real type, default logical type such that components of the
13320          structure ultimately only become associated to objects of the same
13321          kind. A character sequence structure may be equivalenced to an object
13322          of default character kind or another character sequence structure.
13323          Other objects may be equivalenced only to objects of the same type and
13324          kind parameters.  */
13325
13326       /* Identical types are unconditionally OK.  */
13327       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
13328         goto identical_types;
13329
13330       last_eq_type = sequence_type (*last_ts);
13331       eq_type = sequence_type (sym->ts);
13332
13333       /* Since the pair of objects is not of the same type, mixed or
13334          non-default sequences can be rejected.  */
13335
13336       msg = "Sequence %s with mixed components in EQUIVALENCE "
13337             "statement at %L with different type objects";
13338       if ((object ==2
13339            && last_eq_type == SEQ_MIXED
13340            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
13341               == FAILURE)
13342           || (eq_type == SEQ_MIXED
13343               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13344                                  &e->where) == FAILURE))
13345         continue;
13346
13347       msg = "Non-default type object or sequence %s in EQUIVALENCE "
13348             "statement at %L with objects of different type";
13349       if ((object ==2
13350            && last_eq_type == SEQ_NONDEFAULT
13351            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
13352                               last_where) == FAILURE)
13353           || (eq_type == SEQ_NONDEFAULT
13354               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13355                                  &e->where) == FAILURE))
13356         continue;
13357
13358       msg ="Non-CHARACTER object '%s' in default CHARACTER "
13359            "EQUIVALENCE statement at %L";
13360       if (last_eq_type == SEQ_CHARACTER
13361           && eq_type != SEQ_CHARACTER
13362           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13363                              &e->where) == FAILURE)
13364                 continue;
13365
13366       msg ="Non-NUMERIC object '%s' in default NUMERIC "
13367            "EQUIVALENCE statement at %L";
13368       if (last_eq_type == SEQ_NUMERIC
13369           && eq_type != SEQ_NUMERIC
13370           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13371                              &e->where) == FAILURE)
13372                 continue;
13373
13374   identical_types:
13375       last_ts =&sym->ts;
13376       last_where = &e->where;
13377
13378       if (!e->ref)
13379         continue;
13380
13381       /* Shall not be an automatic array.  */
13382       if (e->ref->type == REF_ARRAY
13383           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
13384         {
13385           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
13386                      "an EQUIVALENCE object", sym->name, &e->where);
13387           continue;
13388         }
13389
13390       r = e->ref;
13391       while (r)
13392         {
13393           /* Shall not be a structure component.  */
13394           if (r->type == REF_COMPONENT)
13395             {
13396               gfc_error ("Structure component '%s' at %L cannot be an "
13397                          "EQUIVALENCE object",
13398                          r->u.c.component->name, &e->where);
13399               break;
13400             }
13401
13402           /* A substring shall not have length zero.  */
13403           if (r->type == REF_SUBSTRING)
13404             {
13405               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
13406                 {
13407                   gfc_error ("Substring at %L has length zero",
13408                              &r->u.ss.start->where);
13409                   break;
13410                 }
13411             }
13412           r = r->next;
13413         }
13414     }
13415 }
13416
13417
13418 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
13419
13420 static void
13421 resolve_fntype (gfc_namespace *ns)
13422 {
13423   gfc_entry_list *el;
13424   gfc_symbol *sym;
13425
13426   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
13427     return;
13428
13429   /* If there are any entries, ns->proc_name is the entry master
13430      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
13431   if (ns->entries)
13432     sym = ns->entries->sym;
13433   else
13434     sym = ns->proc_name;
13435   if (sym->result == sym
13436       && sym->ts.type == BT_UNKNOWN
13437       && gfc_set_default_type (sym, 0, NULL) == FAILURE
13438       && !sym->attr.untyped)
13439     {
13440       gfc_error ("Function '%s' at %L has no IMPLICIT type",
13441                  sym->name, &sym->declared_at);
13442       sym->attr.untyped = 1;
13443     }
13444
13445   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
13446       && !sym->attr.contained
13447       && !gfc_check_symbol_access (sym->ts.u.derived)
13448       && gfc_check_symbol_access (sym))
13449     {
13450       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
13451                       "%L of PRIVATE type '%s'", sym->name,
13452                       &sym->declared_at, sym->ts.u.derived->name);
13453     }
13454
13455     if (ns->entries)
13456     for (el = ns->entries->next; el; el = el->next)
13457       {
13458         if (el->sym->result == el->sym
13459             && el->sym->ts.type == BT_UNKNOWN
13460             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
13461             && !el->sym->attr.untyped)
13462           {
13463             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
13464                        el->sym->name, &el->sym->declared_at);
13465             el->sym->attr.untyped = 1;
13466           }
13467       }
13468 }
13469
13470
13471 /* 12.3.2.1.1 Defined operators.  */
13472
13473 static gfc_try
13474 check_uop_procedure (gfc_symbol *sym, locus where)
13475 {
13476   gfc_formal_arglist *formal;
13477
13478   if (!sym->attr.function)
13479     {
13480       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
13481                  sym->name, &where);
13482       return FAILURE;
13483     }
13484
13485   if (sym->ts.type == BT_CHARACTER
13486       && !(sym->ts.u.cl && sym->ts.u.cl->length)
13487       && !(sym->result && sym->result->ts.u.cl
13488            && sym->result->ts.u.cl->length))
13489     {
13490       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
13491                  "character length", sym->name, &where);
13492       return FAILURE;
13493     }
13494
13495   formal = sym->formal;
13496   if (!formal || !formal->sym)
13497     {
13498       gfc_error ("User operator procedure '%s' at %L must have at least "
13499                  "one argument", sym->name, &where);
13500       return FAILURE;
13501     }
13502
13503   if (formal->sym->attr.intent != INTENT_IN)
13504     {
13505       gfc_error ("First argument of operator interface at %L must be "
13506                  "INTENT(IN)", &where);
13507       return FAILURE;
13508     }
13509
13510   if (formal->sym->attr.optional)
13511     {
13512       gfc_error ("First argument of operator interface at %L cannot be "
13513                  "optional", &where);
13514       return FAILURE;
13515     }
13516
13517   formal = formal->next;
13518   if (!formal || !formal->sym)
13519     return SUCCESS;
13520
13521   if (formal->sym->attr.intent != INTENT_IN)
13522     {
13523       gfc_error ("Second argument of operator interface at %L must be "
13524                  "INTENT(IN)", &where);
13525       return FAILURE;
13526     }
13527
13528   if (formal->sym->attr.optional)
13529     {
13530       gfc_error ("Second argument of operator interface at %L cannot be "
13531                  "optional", &where);
13532       return FAILURE;
13533     }
13534
13535   if (formal->next)
13536     {
13537       gfc_error ("Operator interface at %L must have, at most, two "
13538                  "arguments", &where);
13539       return FAILURE;
13540     }
13541
13542   return SUCCESS;
13543 }
13544
13545 static void
13546 gfc_resolve_uops (gfc_symtree *symtree)
13547 {
13548   gfc_interface *itr;
13549
13550   if (symtree == NULL)
13551     return;
13552
13553   gfc_resolve_uops (symtree->left);
13554   gfc_resolve_uops (symtree->right);
13555
13556   for (itr = symtree->n.uop->op; itr; itr = itr->next)
13557     check_uop_procedure (itr->sym, itr->sym->declared_at);
13558 }
13559
13560
13561 /* Examine all of the expressions associated with a program unit,
13562    assign types to all intermediate expressions, make sure that all
13563    assignments are to compatible types and figure out which names
13564    refer to which functions or subroutines.  It doesn't check code
13565    block, which is handled by resolve_code.  */
13566
13567 static void
13568 resolve_types (gfc_namespace *ns)
13569 {
13570   gfc_namespace *n;
13571   gfc_charlen *cl;
13572   gfc_data *d;
13573   gfc_equiv *eq;
13574   gfc_namespace* old_ns = gfc_current_ns;
13575
13576   /* Check that all IMPLICIT types are ok.  */
13577   if (!ns->seen_implicit_none)
13578     {
13579       unsigned letter;
13580       for (letter = 0; letter != GFC_LETTERS; ++letter)
13581         if (ns->set_flag[letter]
13582             && resolve_typespec_used (&ns->default_type[letter],
13583                                       &ns->implicit_loc[letter],
13584                                       NULL) == FAILURE)
13585           return;
13586     }
13587
13588   gfc_current_ns = ns;
13589
13590   resolve_entries (ns);
13591
13592   resolve_common_vars (ns->blank_common.head, false);
13593   resolve_common_blocks (ns->common_root);
13594
13595   resolve_contained_functions (ns);
13596
13597   if (ns->proc_name && ns->proc_name->attr.flavor == FL_PROCEDURE
13598       && ns->proc_name->attr.if_source == IFSRC_IFBODY)
13599     resolve_formal_arglist (ns->proc_name);
13600
13601   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
13602
13603   for (cl = ns->cl_list; cl; cl = cl->next)
13604     resolve_charlen (cl);
13605
13606   gfc_traverse_ns (ns, resolve_symbol);
13607
13608   resolve_fntype (ns);
13609
13610   for (n = ns->contained; n; n = n->sibling)
13611     {
13612       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
13613         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
13614                    "also be PURE", n->proc_name->name,
13615                    &n->proc_name->declared_at);
13616
13617       resolve_types (n);
13618     }
13619
13620   forall_flag = 0;
13621   gfc_check_interfaces (ns);
13622
13623   gfc_traverse_ns (ns, resolve_values);
13624
13625   if (ns->save_all)
13626     gfc_save_all (ns);
13627
13628   iter_stack = NULL;
13629   for (d = ns->data; d; d = d->next)
13630     resolve_data (d);
13631
13632   iter_stack = NULL;
13633   gfc_traverse_ns (ns, gfc_formalize_init_value);
13634
13635   gfc_traverse_ns (ns, gfc_verify_binding_labels);
13636
13637   if (ns->common_root != NULL)
13638     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
13639
13640   for (eq = ns->equiv; eq; eq = eq->next)
13641     resolve_equivalence (eq);
13642
13643   /* Warn about unused labels.  */
13644   if (warn_unused_label)
13645     warn_unused_fortran_label (ns->st_labels);
13646
13647   gfc_resolve_uops (ns->uop_root);
13648
13649   gfc_current_ns = old_ns;
13650 }
13651
13652
13653 /* Call resolve_code recursively.  */
13654
13655 static void
13656 resolve_codes (gfc_namespace *ns)
13657 {
13658   gfc_namespace *n;
13659   bitmap_obstack old_obstack;
13660
13661   if (ns->resolved == 1)
13662     return;
13663
13664   for (n = ns->contained; n; n = n->sibling)
13665     resolve_codes (n);
13666
13667   gfc_current_ns = ns;
13668
13669   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
13670   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
13671     cs_base = NULL;
13672
13673   /* Set to an out of range value.  */
13674   current_entry_id = -1;
13675
13676   old_obstack = labels_obstack;
13677   bitmap_obstack_initialize (&labels_obstack);
13678
13679   resolve_code (ns->code, ns);
13680
13681   bitmap_obstack_release (&labels_obstack);
13682   labels_obstack = old_obstack;
13683 }
13684
13685
13686 /* This function is called after a complete program unit has been compiled.
13687    Its purpose is to examine all of the expressions associated with a program
13688    unit, assign types to all intermediate expressions, make sure that all
13689    assignments are to compatible types and figure out which names refer to
13690    which functions or subroutines.  */
13691
13692 void
13693 gfc_resolve (gfc_namespace *ns)
13694 {
13695   gfc_namespace *old_ns;
13696   code_stack *old_cs_base;
13697
13698   if (ns->resolved)
13699     return;
13700
13701   ns->resolved = -1;
13702   old_ns = gfc_current_ns;
13703   old_cs_base = cs_base;
13704
13705   resolve_types (ns);
13706   resolve_codes (ns);
13707
13708   gfc_current_ns = old_ns;
13709   cs_base = old_cs_base;
13710   ns->resolved = 1;
13711
13712   gfc_run_passes (ns);
13713 }