OSDN Git Service

2011-04-04 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009,
3    2010, 2011
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         {
320           sym->as->type = AS_ASSUMED_SHAPE;
321           for (i = 0; i < sym->as->rank; i++)
322             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
323                                                   NULL, 1);
324         }
325
326       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
327           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
328           || sym->attr.optional)
329         {
330           proc->attr.always_explicit = 1;
331           if (proc->result)
332             proc->result->attr.always_explicit = 1;
333         }
334
335       /* If the flavor is unknown at this point, it has to be a variable.
336          A procedure specification would have already set the type.  */
337
338       if (sym->attr.flavor == FL_UNKNOWN)
339         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
340
341       if (gfc_pure (proc) && !sym->attr.pointer
342           && sym->attr.flavor != FL_PROCEDURE)
343         {
344           if (proc->attr.function && sym->attr.intent != INTENT_IN)
345             {
346               if (sym->attr.value)
347                 gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s' "
348                                 "of pure function '%s' at %L with VALUE "
349                                 "attribute but without INTENT(IN)", sym->name,
350                                 proc->name, &sym->declared_at);
351               else
352                 gfc_error ("Argument '%s' of pure function '%s' at %L must be "
353                            "INTENT(IN) or VALUE", sym->name, proc->name,
354                            &sym->declared_at);
355             }
356
357           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
358             {
359               if (sym->attr.value)
360                 gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s' "
361                                 "of pure subroutine '%s' at %L with VALUE "
362                                 "attribute but without INTENT", sym->name,
363                                 proc->name, &sym->declared_at);
364               else
365                 gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
366                        "have its INTENT specified or have the VALUE "
367                        "attribute", sym->name, proc->name, &sym->declared_at);
368             }
369         }
370
371       if (proc->attr.implicit_pure && !sym->attr.pointer
372           && sym->attr.flavor != FL_PROCEDURE)
373         {
374           if (proc->attr.function && sym->attr.intent != INTENT_IN)
375             proc->attr.implicit_pure = 0;
376
377           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
378             proc->attr.implicit_pure = 0;
379         }
380
381       if (gfc_elemental (proc))
382         {
383           /* F2008, C1289.  */
384           if (sym->attr.codimension)
385             {
386               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
387                          "procedure", sym->name, &sym->declared_at);
388               continue;
389             }
390
391           if (sym->as != NULL)
392             {
393               gfc_error ("Argument '%s' of elemental procedure at %L must "
394                          "be scalar", sym->name, &sym->declared_at);
395               continue;
396             }
397
398           if (sym->attr.allocatable)
399             {
400               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
401                          "have the ALLOCATABLE attribute", sym->name,
402                          &sym->declared_at);
403               continue;
404             }
405
406           if (sym->attr.pointer)
407             {
408               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
409                          "have the POINTER attribute", sym->name,
410                          &sym->declared_at);
411               continue;
412             }
413
414           if (sym->attr.flavor == FL_PROCEDURE)
415             {
416               gfc_error ("Dummy procedure '%s' not allowed in elemental "
417                          "procedure '%s' at %L", sym->name, proc->name,
418                          &sym->declared_at);
419               continue;
420             }
421
422           if (sym->attr.intent == INTENT_UNKNOWN)
423             {
424               gfc_error ("Argument '%s' of elemental procedure '%s' at %L must "
425                          "have its INTENT specified", sym->name, proc->name,
426                          &sym->declared_at);
427               continue;
428             }
429         }
430
431       /* Each dummy shall be specified to be scalar.  */
432       if (proc->attr.proc == PROC_ST_FUNCTION)
433         {
434           if (sym->as != NULL)
435             {
436               gfc_error ("Argument '%s' of statement function at %L must "
437                          "be scalar", sym->name, &sym->declared_at);
438               continue;
439             }
440
441           if (sym->ts.type == BT_CHARACTER)
442             {
443               gfc_charlen *cl = sym->ts.u.cl;
444               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
445                 {
446                   gfc_error ("Character-valued argument '%s' of statement "
447                              "function at %L must have constant length",
448                              sym->name, &sym->declared_at);
449                   continue;
450                 }
451             }
452         }
453     }
454   formal_arg_flag = 0;
455 }
456
457
458 /* Work function called when searching for symbols that have argument lists
459    associated with them.  */
460
461 static void
462 find_arglists (gfc_symbol *sym)
463 {
464   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
465     return;
466
467   resolve_formal_arglist (sym);
468 }
469
470
471 /* Given a namespace, resolve all formal argument lists within the namespace.
472  */
473
474 static void
475 resolve_formal_arglists (gfc_namespace *ns)
476 {
477   if (ns == NULL)
478     return;
479
480   gfc_traverse_ns (ns, find_arglists);
481 }
482
483
484 static void
485 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
486 {
487   gfc_try t;
488
489   /* If this namespace is not a function or an entry master function,
490      ignore it.  */
491   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
492       || sym->attr.entry_master)
493     return;
494
495   /* Try to find out of what the return type is.  */
496   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
497     {
498       t = gfc_set_default_type (sym->result, 0, ns);
499
500       if (t == FAILURE && !sym->result->attr.untyped)
501         {
502           if (sym->result == sym)
503             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
504                        sym->name, &sym->declared_at);
505           else if (!sym->result->attr.proc_pointer)
506             gfc_error ("Result '%s' of contained function '%s' at %L has "
507                        "no IMPLICIT type", sym->result->name, sym->name,
508                        &sym->result->declared_at);
509           sym->result->attr.untyped = 1;
510         }
511     }
512
513   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
514      type, lists the only ways a character length value of * can be used:
515      dummy arguments of procedures, named constants, and function results
516      in external functions.  Internal function results and results of module
517      procedures are not on this list, ergo, not permitted.  */
518
519   if (sym->result->ts.type == BT_CHARACTER)
520     {
521       gfc_charlen *cl = sym->result->ts.u.cl;
522       if ((!cl || !cl->length) && !sym->result->ts.deferred)
523         {
524           /* See if this is a module-procedure and adapt error message
525              accordingly.  */
526           bool module_proc;
527           gcc_assert (ns->parent && ns->parent->proc_name);
528           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
529
530           gfc_error ("Character-valued %s '%s' at %L must not be"
531                      " assumed length",
532                      module_proc ? _("module procedure")
533                                  : _("internal function"),
534                      sym->name, &sym->declared_at);
535         }
536     }
537 }
538
539
540 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
541    introduce duplicates.  */
542
543 static void
544 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
545 {
546   gfc_formal_arglist *f, *new_arglist;
547   gfc_symbol *new_sym;
548
549   for (; new_args != NULL; new_args = new_args->next)
550     {
551       new_sym = new_args->sym;
552       /* See if this arg is already in the formal argument list.  */
553       for (f = proc->formal; f; f = f->next)
554         {
555           if (new_sym == f->sym)
556             break;
557         }
558
559       if (f)
560         continue;
561
562       /* Add a new argument.  Argument order is not important.  */
563       new_arglist = gfc_get_formal_arglist ();
564       new_arglist->sym = new_sym;
565       new_arglist->next = proc->formal;
566       proc->formal  = new_arglist;
567     }
568 }
569
570
571 /* Flag the arguments that are not present in all entries.  */
572
573 static void
574 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
575 {
576   gfc_formal_arglist *f, *head;
577   head = new_args;
578
579   for (f = proc->formal; f; f = f->next)
580     {
581       if (f->sym == NULL)
582         continue;
583
584       for (new_args = head; new_args; new_args = new_args->next)
585         {
586           if (new_args->sym == f->sym)
587             break;
588         }
589
590       if (new_args)
591         continue;
592
593       f->sym->attr.not_always_present = 1;
594     }
595 }
596
597
598 /* Resolve alternate entry points.  If a symbol has multiple entry points we
599    create a new master symbol for the main routine, and turn the existing
600    symbol into an entry point.  */
601
602 static void
603 resolve_entries (gfc_namespace *ns)
604 {
605   gfc_namespace *old_ns;
606   gfc_code *c;
607   gfc_symbol *proc;
608   gfc_entry_list *el;
609   char name[GFC_MAX_SYMBOL_LEN + 1];
610   static int master_count = 0;
611
612   if (ns->proc_name == NULL)
613     return;
614
615   /* No need to do anything if this procedure doesn't have alternate entry
616      points.  */
617   if (!ns->entries)
618     return;
619
620   /* We may already have resolved alternate entry points.  */
621   if (ns->proc_name->attr.entry_master)
622     return;
623
624   /* If this isn't a procedure something has gone horribly wrong.  */
625   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
626
627   /* Remember the current namespace.  */
628   old_ns = gfc_current_ns;
629
630   gfc_current_ns = ns;
631
632   /* Add the main entry point to the list of entry points.  */
633   el = gfc_get_entry_list ();
634   el->sym = ns->proc_name;
635   el->id = 0;
636   el->next = ns->entries;
637   ns->entries = el;
638   ns->proc_name->attr.entry = 1;
639
640   /* If it is a module function, it needs to be in the right namespace
641      so that gfc_get_fake_result_decl can gather up the results. The
642      need for this arose in get_proc_name, where these beasts were
643      left in their own namespace, to keep prior references linked to
644      the entry declaration.*/
645   if (ns->proc_name->attr.function
646       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
647     el->sym->ns = ns;
648
649   /* Do the same for entries where the master is not a module
650      procedure.  These are retained in the module namespace because
651      of the module procedure declaration.  */
652   for (el = el->next; el; el = el->next)
653     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
654           && el->sym->attr.mod_proc)
655       el->sym->ns = ns;
656   el = ns->entries;
657
658   /* Add an entry statement for it.  */
659   c = gfc_get_code ();
660   c->op = EXEC_ENTRY;
661   c->ext.entry = el;
662   c->next = ns->code;
663   ns->code = c;
664
665   /* Create a new symbol for the master function.  */
666   /* Give the internal function a unique name (within this file).
667      Also include the function name so the user has some hope of figuring
668      out what is going on.  */
669   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
670             master_count++, ns->proc_name->name);
671   gfc_get_ha_symbol (name, &proc);
672   gcc_assert (proc != NULL);
673
674   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
675   if (ns->proc_name->attr.subroutine)
676     gfc_add_subroutine (&proc->attr, proc->name, NULL);
677   else
678     {
679       gfc_symbol *sym;
680       gfc_typespec *ts, *fts;
681       gfc_array_spec *as, *fas;
682       gfc_add_function (&proc->attr, proc->name, NULL);
683       proc->result = proc;
684       fas = ns->entries->sym->as;
685       fas = fas ? fas : ns->entries->sym->result->as;
686       fts = &ns->entries->sym->result->ts;
687       if (fts->type == BT_UNKNOWN)
688         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
689       for (el = ns->entries->next; el; el = el->next)
690         {
691           ts = &el->sym->result->ts;
692           as = el->sym->as;
693           as = as ? as : el->sym->result->as;
694           if (ts->type == BT_UNKNOWN)
695             ts = gfc_get_default_type (el->sym->result->name, NULL);
696
697           if (! gfc_compare_types (ts, fts)
698               || (el->sym->result->attr.dimension
699                   != ns->entries->sym->result->attr.dimension)
700               || (el->sym->result->attr.pointer
701                   != ns->entries->sym->result->attr.pointer))
702             break;
703           else if (as && fas && ns->entries->sym->result != el->sym->result
704                       && gfc_compare_array_spec (as, fas) == 0)
705             gfc_error ("Function %s at %L has entries with mismatched "
706                        "array specifications", ns->entries->sym->name,
707                        &ns->entries->sym->declared_at);
708           /* The characteristics need to match and thus both need to have
709              the same string length, i.e. both len=*, or both len=4.
710              Having both len=<variable> is also possible, but difficult to
711              check at compile time.  */
712           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
713                    && (((ts->u.cl->length && !fts->u.cl->length)
714                         ||(!ts->u.cl->length && fts->u.cl->length))
715                        || (ts->u.cl->length
716                            && ts->u.cl->length->expr_type
717                               != fts->u.cl->length->expr_type)
718                        || (ts->u.cl->length
719                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
720                            && mpz_cmp (ts->u.cl->length->value.integer,
721                                        fts->u.cl->length->value.integer) != 0)))
722             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
723                             "entries returning variables of different "
724                             "string lengths", ns->entries->sym->name,
725                             &ns->entries->sym->declared_at);
726         }
727
728       if (el == NULL)
729         {
730           sym = ns->entries->sym->result;
731           /* All result types the same.  */
732           proc->ts = *fts;
733           if (sym->attr.dimension)
734             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
735           if (sym->attr.pointer)
736             gfc_add_pointer (&proc->attr, NULL);
737         }
738       else
739         {
740           /* Otherwise the result will be passed through a union by
741              reference.  */
742           proc->attr.mixed_entry_master = 1;
743           for (el = ns->entries; el; el = el->next)
744             {
745               sym = el->sym->result;
746               if (sym->attr.dimension)
747                 {
748                   if (el == ns->entries)
749                     gfc_error ("FUNCTION result %s can't be an array in "
750                                "FUNCTION %s at %L", sym->name,
751                                ns->entries->sym->name, &sym->declared_at);
752                   else
753                     gfc_error ("ENTRY result %s can't be an array in "
754                                "FUNCTION %s at %L", sym->name,
755                                ns->entries->sym->name, &sym->declared_at);
756                 }
757               else if (sym->attr.pointer)
758                 {
759                   if (el == ns->entries)
760                     gfc_error ("FUNCTION result %s can't be a POINTER in "
761                                "FUNCTION %s at %L", sym->name,
762                                ns->entries->sym->name, &sym->declared_at);
763                   else
764                     gfc_error ("ENTRY result %s can't be a POINTER in "
765                                "FUNCTION %s at %L", sym->name,
766                                ns->entries->sym->name, &sym->declared_at);
767                 }
768               else
769                 {
770                   ts = &sym->ts;
771                   if (ts->type == BT_UNKNOWN)
772                     ts = gfc_get_default_type (sym->name, NULL);
773                   switch (ts->type)
774                     {
775                     case BT_INTEGER:
776                       if (ts->kind == gfc_default_integer_kind)
777                         sym = NULL;
778                       break;
779                     case BT_REAL:
780                       if (ts->kind == gfc_default_real_kind
781                           || ts->kind == gfc_default_double_kind)
782                         sym = NULL;
783                       break;
784                     case BT_COMPLEX:
785                       if (ts->kind == gfc_default_complex_kind)
786                         sym = NULL;
787                       break;
788                     case BT_LOGICAL:
789                       if (ts->kind == gfc_default_logical_kind)
790                         sym = NULL;
791                       break;
792                     case BT_UNKNOWN:
793                       /* We will issue error elsewhere.  */
794                       sym = NULL;
795                       break;
796                     default:
797                       break;
798                     }
799                   if (sym)
800                     {
801                       if (el == ns->entries)
802                         gfc_error ("FUNCTION result %s can't be of type %s "
803                                    "in FUNCTION %s at %L", sym->name,
804                                    gfc_typename (ts), ns->entries->sym->name,
805                                    &sym->declared_at);
806                       else
807                         gfc_error ("ENTRY result %s can't be of type %s "
808                                    "in FUNCTION %s at %L", sym->name,
809                                    gfc_typename (ts), ns->entries->sym->name,
810                                    &sym->declared_at);
811                     }
812                 }
813             }
814         }
815     }
816   proc->attr.access = ACCESS_PRIVATE;
817   proc->attr.entry_master = 1;
818
819   /* Merge all the entry point arguments.  */
820   for (el = ns->entries; el; el = el->next)
821     merge_argument_lists (proc, el->sym->formal);
822
823   /* Check the master formal arguments for any that are not
824      present in all entry points.  */
825   for (el = ns->entries; el; el = el->next)
826     check_argument_lists (proc, el->sym->formal);
827
828   /* Use the master function for the function body.  */
829   ns->proc_name = proc;
830
831   /* Finalize the new symbols.  */
832   gfc_commit_symbols ();
833
834   /* Restore the original namespace.  */
835   gfc_current_ns = old_ns;
836 }
837
838
839 /* Resolve common variables.  */
840 static void
841 resolve_common_vars (gfc_symbol *sym, bool named_common)
842 {
843   gfc_symbol *csym = sym;
844
845   for (; csym; csym = csym->common_next)
846     {
847       if (csym->value || csym->attr.data)
848         {
849           if (!csym->ns->is_block_data)
850             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
851                             "but only in BLOCK DATA initialization is "
852                             "allowed", csym->name, &csym->declared_at);
853           else if (!named_common)
854             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
855                             "in a blank COMMON but initialization is only "
856                             "allowed in named common blocks", csym->name,
857                             &csym->declared_at);
858         }
859
860       if (csym->ts.type != BT_DERIVED)
861         continue;
862
863       if (!(csym->ts.u.derived->attr.sequence
864             || csym->ts.u.derived->attr.is_bind_c))
865         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
866                        "has neither the SEQUENCE nor the BIND(C) "
867                        "attribute", csym->name, &csym->declared_at);
868       if (csym->ts.u.derived->attr.alloc_comp)
869         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
870                        "has an ultimate component that is "
871                        "allocatable", csym->name, &csym->declared_at);
872       if (gfc_has_default_initializer (csym->ts.u.derived))
873         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
874                        "may not have default initializer", csym->name,
875                        &csym->declared_at);
876
877       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
878         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
879     }
880 }
881
882 /* Resolve common blocks.  */
883 static void
884 resolve_common_blocks (gfc_symtree *common_root)
885 {
886   gfc_symbol *sym;
887
888   if (common_root == NULL)
889     return;
890
891   if (common_root->left)
892     resolve_common_blocks (common_root->left);
893   if (common_root->right)
894     resolve_common_blocks (common_root->right);
895
896   resolve_common_vars (common_root->n.common->head, true);
897
898   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
899   if (sym == NULL)
900     return;
901
902   if (sym->attr.flavor == FL_PARAMETER)
903     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
904                sym->name, &common_root->n.common->where, &sym->declared_at);
905
906   if (sym->attr.intrinsic)
907     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
908                sym->name, &common_root->n.common->where);
909   else if (sym->attr.result
910            || gfc_is_function_return_value (sym, gfc_current_ns))
911     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
912                     "that is also a function result", sym->name,
913                     &common_root->n.common->where);
914   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
915            && sym->attr.proc != PROC_ST_FUNCTION)
916     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
917                     "that is also a global procedure", sym->name,
918                     &common_root->n.common->where);
919 }
920
921
922 /* Resolve contained function types.  Because contained functions can call one
923    another, they have to be worked out before any of the contained procedures
924    can be resolved.
925
926    The good news is that if a function doesn't already have a type, the only
927    way it can get one is through an IMPLICIT type or a RESULT variable, because
928    by definition contained functions are contained namespace they're contained
929    in, not in a sibling or parent namespace.  */
930
931 static void
932 resolve_contained_functions (gfc_namespace *ns)
933 {
934   gfc_namespace *child;
935   gfc_entry_list *el;
936
937   resolve_formal_arglists (ns);
938
939   for (child = ns->contained; child; child = child->sibling)
940     {
941       /* Resolve alternate entry points first.  */
942       resolve_entries (child);
943
944       /* Then check function return types.  */
945       resolve_contained_fntype (child->proc_name, child);
946       for (el = child->entries; el; el = el->next)
947         resolve_contained_fntype (el->sym, child);
948     }
949 }
950
951
952 /* Resolve all of the elements of a structure constructor and make sure that
953    the types are correct. The 'init' flag indicates that the given
954    constructor is an initializer.  */
955
956 static gfc_try
957 resolve_structure_cons (gfc_expr *expr, int init)
958 {
959   gfc_constructor *cons;
960   gfc_component *comp;
961   gfc_try t;
962   symbol_attribute a;
963
964   t = SUCCESS;
965
966   if (expr->ts.type == BT_DERIVED)
967     resolve_symbol (expr->ts.u.derived);
968
969   cons = gfc_constructor_first (expr->value.constructor);
970   /* A constructor may have references if it is the result of substituting a
971      parameter variable.  In this case we just pull out the component we
972      want.  */
973   if (expr->ref)
974     comp = expr->ref->u.c.sym->components;
975   else
976     comp = expr->ts.u.derived->components;
977
978   /* See if the user is trying to invoke a structure constructor for one of
979      the iso_c_binding derived types.  */
980   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
981       && expr->ts.u.derived->ts.is_iso_c && cons
982       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
983     {
984       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
985                  expr->ts.u.derived->name, &(expr->where));
986       return FAILURE;
987     }
988
989   /* Return if structure constructor is c_null_(fun)prt.  */
990   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
991       && expr->ts.u.derived->ts.is_iso_c && cons
992       && cons->expr && cons->expr->expr_type == EXPR_NULL)
993     return SUCCESS;
994
995   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
996     {
997       int rank;
998
999       if (!cons->expr)
1000         continue;
1001
1002       if (gfc_resolve_expr (cons->expr) == FAILURE)
1003         {
1004           t = FAILURE;
1005           continue;
1006         }
1007
1008       rank = comp->as ? comp->as->rank : 0;
1009       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
1010           && (comp->attr.allocatable || cons->expr->rank))
1011         {
1012           gfc_error ("The rank of the element in the derived type "
1013                      "constructor at %L does not match that of the "
1014                      "component (%d/%d)", &cons->expr->where,
1015                      cons->expr->rank, rank);
1016           t = FAILURE;
1017         }
1018
1019       /* If we don't have the right type, try to convert it.  */
1020
1021       if (!comp->attr.proc_pointer &&
1022           !gfc_compare_types (&cons->expr->ts, &comp->ts))
1023         {
1024           t = FAILURE;
1025           if (strcmp (comp->name, "_extends") == 0)
1026             {
1027               /* Can afford to be brutal with the _extends initializer.
1028                  The derived type can get lost because it is PRIVATE
1029                  but it is not usage constrained by the standard.  */
1030               cons->expr->ts = comp->ts;
1031               t = SUCCESS;
1032             }
1033           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
1034             gfc_error ("The element in the derived type constructor at %L, "
1035                        "for pointer component '%s', is %s but should be %s",
1036                        &cons->expr->where, comp->name,
1037                        gfc_basic_typename (cons->expr->ts.type),
1038                        gfc_basic_typename (comp->ts.type));
1039           else
1040             t = gfc_convert_type (cons->expr, &comp->ts, 1);
1041         }
1042
1043       /* For strings, the length of the constructor should be the same as
1044          the one of the structure, ensure this if the lengths are known at
1045          compile time and when we are dealing with PARAMETER or structure
1046          constructors.  */
1047       if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1048           && comp->ts.u.cl->length
1049           && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1050           && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1051           && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1052           && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1053                       comp->ts.u.cl->length->value.integer) != 0)
1054         {
1055           if (cons->expr->expr_type == EXPR_VARIABLE
1056               && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1057             {
1058               /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1059                  to make use of the gfc_resolve_character_array_constructor
1060                  machinery.  The expression is later simplified away to
1061                  an array of string literals.  */
1062               gfc_expr *para = cons->expr;
1063               cons->expr = gfc_get_expr ();
1064               cons->expr->ts = para->ts;
1065               cons->expr->where = para->where;
1066               cons->expr->expr_type = EXPR_ARRAY;
1067               cons->expr->rank = para->rank;
1068               cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1069               gfc_constructor_append_expr (&cons->expr->value.constructor,
1070                                            para, &cons->expr->where);
1071             }
1072           if (cons->expr->expr_type == EXPR_ARRAY)
1073             {
1074               gfc_constructor *p;
1075               p = gfc_constructor_first (cons->expr->value.constructor);
1076               if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1077                 {
1078                   gfc_charlen *cl, *cl2;
1079
1080                   cl2 = NULL;
1081                   for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1082                     {
1083                       if (cl == cons->expr->ts.u.cl)
1084                         break;
1085                       cl2 = cl;
1086                     }
1087
1088                   gcc_assert (cl);
1089
1090                   if (cl2)
1091                     cl2->next = cl->next;
1092
1093                   gfc_free_expr (cl->length);
1094                   gfc_free (cl);
1095                 }
1096
1097               cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1098               cons->expr->ts.u.cl->length_from_typespec = true;
1099               cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1100               gfc_resolve_character_array_constructor (cons->expr);
1101             }
1102         }
1103
1104       if (cons->expr->expr_type == EXPR_NULL
1105           && !(comp->attr.pointer || comp->attr.allocatable
1106                || comp->attr.proc_pointer
1107                || (comp->ts.type == BT_CLASS
1108                    && (CLASS_DATA (comp)->attr.class_pointer
1109                        || CLASS_DATA (comp)->attr.allocatable))))
1110         {
1111           t = FAILURE;
1112           gfc_error ("The NULL in the derived type constructor at %L is "
1113                      "being applied to component '%s', which is neither "
1114                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
1115                      comp->name);
1116         }
1117
1118       if (!comp->attr.pointer || comp->attr.proc_pointer
1119           || cons->expr->expr_type == EXPR_NULL)
1120         continue;
1121
1122       a = gfc_expr_attr (cons->expr);
1123
1124       if (!a.pointer && !a.target)
1125         {
1126           t = FAILURE;
1127           gfc_error ("The element in the derived type constructor at %L, "
1128                      "for pointer component '%s' should be a POINTER or "
1129                      "a TARGET", &cons->expr->where, comp->name);
1130         }
1131
1132       if (init)
1133         {
1134           /* F08:C461. Additional checks for pointer initialization.  */
1135           if (a.allocatable)
1136             {
1137               t = FAILURE;
1138               gfc_error ("Pointer initialization target at %L "
1139                          "must not be ALLOCATABLE ", &cons->expr->where);
1140             }
1141           if (!a.save)
1142             {
1143               t = FAILURE;
1144               gfc_error ("Pointer initialization target at %L "
1145                          "must have the SAVE attribute", &cons->expr->where);
1146             }
1147         }
1148
1149       /* F2003, C1272 (3).  */
1150       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
1151           && (gfc_impure_variable (cons->expr->symtree->n.sym)
1152               || gfc_is_coindexed (cons->expr)))
1153         {
1154           t = FAILURE;
1155           gfc_error ("Invalid expression in the derived type constructor for "
1156                      "pointer component '%s' at %L in PURE procedure",
1157                      comp->name, &cons->expr->where);
1158         }
1159
1160       if (gfc_implicit_pure (NULL)
1161             && cons->expr->expr_type == EXPR_VARIABLE
1162             && (gfc_impure_variable (cons->expr->symtree->n.sym)
1163                 || gfc_is_coindexed (cons->expr)))
1164         gfc_current_ns->proc_name->attr.implicit_pure = 0;
1165
1166     }
1167
1168   return t;
1169 }
1170
1171
1172 /****************** Expression name resolution ******************/
1173
1174 /* Returns 0 if a symbol was not declared with a type or
1175    attribute declaration statement, nonzero otherwise.  */
1176
1177 static int
1178 was_declared (gfc_symbol *sym)
1179 {
1180   symbol_attribute a;
1181
1182   a = sym->attr;
1183
1184   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1185     return 1;
1186
1187   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1188       || a.optional || a.pointer || a.save || a.target || a.volatile_
1189       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1190       || a.asynchronous || a.codimension)
1191     return 1;
1192
1193   return 0;
1194 }
1195
1196
1197 /* Determine if a symbol is generic or not.  */
1198
1199 static int
1200 generic_sym (gfc_symbol *sym)
1201 {
1202   gfc_symbol *s;
1203
1204   if (sym->attr.generic ||
1205       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1206     return 1;
1207
1208   if (was_declared (sym) || sym->ns->parent == NULL)
1209     return 0;
1210
1211   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1212   
1213   if (s != NULL)
1214     {
1215       if (s == sym)
1216         return 0;
1217       else
1218         return generic_sym (s);
1219     }
1220
1221   return 0;
1222 }
1223
1224
1225 /* Determine if a symbol is specific or not.  */
1226
1227 static int
1228 specific_sym (gfc_symbol *sym)
1229 {
1230   gfc_symbol *s;
1231
1232   if (sym->attr.if_source == IFSRC_IFBODY
1233       || sym->attr.proc == PROC_MODULE
1234       || sym->attr.proc == PROC_INTERNAL
1235       || sym->attr.proc == PROC_ST_FUNCTION
1236       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1237       || sym->attr.external)
1238     return 1;
1239
1240   if (was_declared (sym) || sym->ns->parent == NULL)
1241     return 0;
1242
1243   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1244
1245   return (s == NULL) ? 0 : specific_sym (s);
1246 }
1247
1248
1249 /* Figure out if the procedure is specific, generic or unknown.  */
1250
1251 typedef enum
1252 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1253 proc_type;
1254
1255 static proc_type
1256 procedure_kind (gfc_symbol *sym)
1257 {
1258   if (generic_sym (sym))
1259     return PTYPE_GENERIC;
1260
1261   if (specific_sym (sym))
1262     return PTYPE_SPECIFIC;
1263
1264   return PTYPE_UNKNOWN;
1265 }
1266
1267 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1268    is nonzero when matching actual arguments.  */
1269
1270 static int need_full_assumed_size = 0;
1271
1272 static bool
1273 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1274 {
1275   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1276       return false;
1277
1278   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1279      What should it be?  */
1280   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1281           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1282                && (e->ref->u.ar.type == AR_FULL))
1283     {
1284       gfc_error ("The upper bound in the last dimension must "
1285                  "appear in the reference to the assumed size "
1286                  "array '%s' at %L", sym->name, &e->where);
1287       return true;
1288     }
1289   return false;
1290 }
1291
1292
1293 /* Look for bad assumed size array references in argument expressions
1294   of elemental and array valued intrinsic procedures.  Since this is
1295   called from procedure resolution functions, it only recurses at
1296   operators.  */
1297
1298 static bool
1299 resolve_assumed_size_actual (gfc_expr *e)
1300 {
1301   if (e == NULL)
1302    return false;
1303
1304   switch (e->expr_type)
1305     {
1306     case EXPR_VARIABLE:
1307       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1308         return true;
1309       break;
1310
1311     case EXPR_OP:
1312       if (resolve_assumed_size_actual (e->value.op.op1)
1313           || resolve_assumed_size_actual (e->value.op.op2))
1314         return true;
1315       break;
1316
1317     default:
1318       break;
1319     }
1320   return false;
1321 }
1322
1323
1324 /* Check a generic procedure, passed as an actual argument, to see if
1325    there is a matching specific name.  If none, it is an error, and if
1326    more than one, the reference is ambiguous.  */
1327 static int
1328 count_specific_procs (gfc_expr *e)
1329 {
1330   int n;
1331   gfc_interface *p;
1332   gfc_symbol *sym;
1333         
1334   n = 0;
1335   sym = e->symtree->n.sym;
1336
1337   for (p = sym->generic; p; p = p->next)
1338     if (strcmp (sym->name, p->sym->name) == 0)
1339       {
1340         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1341                                        sym->name);
1342         n++;
1343       }
1344
1345   if (n > 1)
1346     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1347                &e->where);
1348
1349   if (n == 0)
1350     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1351                "argument at %L", sym->name, &e->where);
1352
1353   return n;
1354 }
1355
1356
1357 /* See if a call to sym could possibly be a not allowed RECURSION because of
1358    a missing RECURIVE declaration.  This means that either sym is the current
1359    context itself, or sym is the parent of a contained procedure calling its
1360    non-RECURSIVE containing procedure.
1361    This also works if sym is an ENTRY.  */
1362
1363 static bool
1364 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1365 {
1366   gfc_symbol* proc_sym;
1367   gfc_symbol* context_proc;
1368   gfc_namespace* real_context;
1369
1370   if (sym->attr.flavor == FL_PROGRAM)
1371     return false;
1372
1373   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1374
1375   /* If we've got an ENTRY, find real procedure.  */
1376   if (sym->attr.entry && sym->ns->entries)
1377     proc_sym = sym->ns->entries->sym;
1378   else
1379     proc_sym = sym;
1380
1381   /* If sym is RECURSIVE, all is well of course.  */
1382   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1383     return false;
1384
1385   /* Find the context procedure's "real" symbol if it has entries.
1386      We look for a procedure symbol, so recurse on the parents if we don't
1387      find one (like in case of a BLOCK construct).  */
1388   for (real_context = context; ; real_context = real_context->parent)
1389     {
1390       /* We should find something, eventually!  */
1391       gcc_assert (real_context);
1392
1393       context_proc = (real_context->entries ? real_context->entries->sym
1394                                             : real_context->proc_name);
1395
1396       /* In some special cases, there may not be a proc_name, like for this
1397          invalid code:
1398          real(bad_kind()) function foo () ...
1399          when checking the call to bad_kind ().
1400          In these cases, we simply return here and assume that the
1401          call is ok.  */
1402       if (!context_proc)
1403         return false;
1404
1405       if (context_proc->attr.flavor != FL_LABEL)
1406         break;
1407     }
1408
1409   /* A call from sym's body to itself is recursion, of course.  */
1410   if (context_proc == proc_sym)
1411     return true;
1412
1413   /* The same is true if context is a contained procedure and sym the
1414      containing one.  */
1415   if (context_proc->attr.contained)
1416     {
1417       gfc_symbol* parent_proc;
1418
1419       gcc_assert (context->parent);
1420       parent_proc = (context->parent->entries ? context->parent->entries->sym
1421                                               : context->parent->proc_name);
1422
1423       if (parent_proc == proc_sym)
1424         return true;
1425     }
1426
1427   return false;
1428 }
1429
1430
1431 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1432    its typespec and formal argument list.  */
1433
1434 static gfc_try
1435 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1436 {
1437   gfc_intrinsic_sym* isym = NULL;
1438   const char* symstd;
1439
1440   if (sym->formal)
1441     return SUCCESS;
1442
1443   /* We already know this one is an intrinsic, so we don't call
1444      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1445      gfc_find_subroutine directly to check whether it is a function or
1446      subroutine.  */
1447
1448   if (sym->intmod_sym_id)
1449     isym = gfc_intrinsic_function_by_id ((gfc_isym_id) sym->intmod_sym_id);
1450   else
1451     isym = gfc_find_function (sym->name);
1452
1453   if (isym)
1454     {
1455       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1456           && !sym->attr.implicit_type)
1457         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1458                       " ignored", sym->name, &sym->declared_at);
1459
1460       if (!sym->attr.function &&
1461           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1462         return FAILURE;
1463
1464       sym->ts = isym->ts;
1465     }
1466   else if ((isym = gfc_find_subroutine (sym->name)))
1467     {
1468       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1469         {
1470           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1471                       " specifier", sym->name, &sym->declared_at);
1472           return FAILURE;
1473         }
1474
1475       if (!sym->attr.subroutine &&
1476           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1477         return FAILURE;
1478     }
1479   else
1480     {
1481       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1482                  &sym->declared_at);
1483       return FAILURE;
1484     }
1485
1486   gfc_copy_formal_args_intr (sym, isym);
1487
1488   /* Check it is actually available in the standard settings.  */
1489   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1490       == FAILURE)
1491     {
1492       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1493                  " available in the current standard settings but %s.  Use"
1494                  " an appropriate -std=* option or enable -fall-intrinsics"
1495                  " in order to use it.",
1496                  sym->name, &sym->declared_at, symstd);
1497       return FAILURE;
1498     }
1499
1500   return SUCCESS;
1501 }
1502
1503
1504 /* Resolve a procedure expression, like passing it to a called procedure or as
1505    RHS for a procedure pointer assignment.  */
1506
1507 static gfc_try
1508 resolve_procedure_expression (gfc_expr* expr)
1509 {
1510   gfc_symbol* sym;
1511
1512   if (expr->expr_type != EXPR_VARIABLE)
1513     return SUCCESS;
1514   gcc_assert (expr->symtree);
1515
1516   sym = expr->symtree->n.sym;
1517
1518   if (sym->attr.intrinsic)
1519     resolve_intrinsic (sym, &expr->where);
1520
1521   if (sym->attr.flavor != FL_PROCEDURE
1522       || (sym->attr.function && sym->result == sym))
1523     return SUCCESS;
1524
1525   /* A non-RECURSIVE procedure that is used as procedure expression within its
1526      own body is in danger of being called recursively.  */
1527   if (is_illegal_recursion (sym, gfc_current_ns))
1528     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1529                  " itself recursively.  Declare it RECURSIVE or use"
1530                  " -frecursive", sym->name, &expr->where);
1531   
1532   return SUCCESS;
1533 }
1534
1535
1536 /* Resolve an actual argument list.  Most of the time, this is just
1537    resolving the expressions in the list.
1538    The exception is that we sometimes have to decide whether arguments
1539    that look like procedure arguments are really simple variable
1540    references.  */
1541
1542 static gfc_try
1543 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1544                         bool no_formal_args)
1545 {
1546   gfc_symbol *sym;
1547   gfc_symtree *parent_st;
1548   gfc_expr *e;
1549   int save_need_full_assumed_size;
1550
1551   for (; arg; arg = arg->next)
1552     {
1553       e = arg->expr;
1554       if (e == NULL)
1555         {
1556           /* Check the label is a valid branching target.  */
1557           if (arg->label)
1558             {
1559               if (arg->label->defined == ST_LABEL_UNKNOWN)
1560                 {
1561                   gfc_error ("Label %d referenced at %L is never defined",
1562                              arg->label->value, &arg->label->where);
1563                   return FAILURE;
1564                 }
1565             }
1566           continue;
1567         }
1568
1569       if (e->expr_type == EXPR_VARIABLE
1570             && e->symtree->n.sym->attr.generic
1571             && no_formal_args
1572             && count_specific_procs (e) != 1)
1573         return FAILURE;
1574
1575       if (e->ts.type != BT_PROCEDURE)
1576         {
1577           save_need_full_assumed_size = need_full_assumed_size;
1578           if (e->expr_type != EXPR_VARIABLE)
1579             need_full_assumed_size = 0;
1580           if (gfc_resolve_expr (e) != SUCCESS)
1581             return FAILURE;
1582           need_full_assumed_size = save_need_full_assumed_size;
1583           goto argument_list;
1584         }
1585
1586       /* See if the expression node should really be a variable reference.  */
1587
1588       sym = e->symtree->n.sym;
1589
1590       if (sym->attr.flavor == FL_PROCEDURE
1591           || sym->attr.intrinsic
1592           || sym->attr.external)
1593         {
1594           int actual_ok;
1595
1596           /* If a procedure is not already determined to be something else
1597              check if it is intrinsic.  */
1598           if (!sym->attr.intrinsic
1599               && !(sym->attr.external || sym->attr.use_assoc
1600                    || sym->attr.if_source == IFSRC_IFBODY)
1601               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1602             sym->attr.intrinsic = 1;
1603
1604           if (sym->attr.proc == PROC_ST_FUNCTION)
1605             {
1606               gfc_error ("Statement function '%s' at %L is not allowed as an "
1607                          "actual argument", sym->name, &e->where);
1608             }
1609
1610           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1611                                                sym->attr.subroutine);
1612           if (sym->attr.intrinsic && actual_ok == 0)
1613             {
1614               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1615                          "actual argument", sym->name, &e->where);
1616             }
1617
1618           if (sym->attr.contained && !sym->attr.use_assoc
1619               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1620             {
1621               if (gfc_notify_std (GFC_STD_F2008,
1622                                   "Fortran 2008: Internal procedure '%s' is"
1623                                   " used as actual argument at %L",
1624                                   sym->name, &e->where) == FAILURE)
1625                 return FAILURE;
1626             }
1627
1628           if (sym->attr.elemental && !sym->attr.intrinsic)
1629             {
1630               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1631                          "allowed as an actual argument at %L", sym->name,
1632                          &e->where);
1633             }
1634
1635           /* Check if a generic interface has a specific procedure
1636             with the same name before emitting an error.  */
1637           if (sym->attr.generic && count_specific_procs (e) != 1)
1638             return FAILURE;
1639           
1640           /* Just in case a specific was found for the expression.  */
1641           sym = e->symtree->n.sym;
1642
1643           /* If the symbol is the function that names the current (or
1644              parent) scope, then we really have a variable reference.  */
1645
1646           if (gfc_is_function_return_value (sym, sym->ns))
1647             goto got_variable;
1648
1649           /* If all else fails, see if we have a specific intrinsic.  */
1650           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1651             {
1652               gfc_intrinsic_sym *isym;
1653
1654               isym = gfc_find_function (sym->name);
1655               if (isym == NULL || !isym->specific)
1656                 {
1657                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1658                              "for the reference '%s' at %L", sym->name,
1659                              &e->where);
1660                   return FAILURE;
1661                 }
1662               sym->ts = isym->ts;
1663               sym->attr.intrinsic = 1;
1664               sym->attr.function = 1;
1665             }
1666
1667           if (gfc_resolve_expr (e) == FAILURE)
1668             return FAILURE;
1669           goto argument_list;
1670         }
1671
1672       /* See if the name is a module procedure in a parent unit.  */
1673
1674       if (was_declared (sym) || sym->ns->parent == NULL)
1675         goto got_variable;
1676
1677       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1678         {
1679           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1680           return FAILURE;
1681         }
1682
1683       if (parent_st == NULL)
1684         goto got_variable;
1685
1686       sym = parent_st->n.sym;
1687       e->symtree = parent_st;           /* Point to the right thing.  */
1688
1689       if (sym->attr.flavor == FL_PROCEDURE
1690           || sym->attr.intrinsic
1691           || sym->attr.external)
1692         {
1693           if (gfc_resolve_expr (e) == FAILURE)
1694             return FAILURE;
1695           goto argument_list;
1696         }
1697
1698     got_variable:
1699       e->expr_type = EXPR_VARIABLE;
1700       e->ts = sym->ts;
1701       if (sym->as != NULL)
1702         {
1703           e->rank = sym->as->rank;
1704           e->ref = gfc_get_ref ();
1705           e->ref->type = REF_ARRAY;
1706           e->ref->u.ar.type = AR_FULL;
1707           e->ref->u.ar.as = sym->as;
1708         }
1709
1710       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1711          primary.c (match_actual_arg). If above code determines that it
1712          is a  variable instead, it needs to be resolved as it was not
1713          done at the beginning of this function.  */
1714       save_need_full_assumed_size = need_full_assumed_size;
1715       if (e->expr_type != EXPR_VARIABLE)
1716         need_full_assumed_size = 0;
1717       if (gfc_resolve_expr (e) != SUCCESS)
1718         return FAILURE;
1719       need_full_assumed_size = save_need_full_assumed_size;
1720
1721     argument_list:
1722       /* Check argument list functions %VAL, %LOC and %REF.  There is
1723          nothing to do for %REF.  */
1724       if (arg->name && arg->name[0] == '%')
1725         {
1726           if (strncmp ("%VAL", arg->name, 4) == 0)
1727             {
1728               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1729                 {
1730                   gfc_error ("By-value argument at %L is not of numeric "
1731                              "type", &e->where);
1732                   return FAILURE;
1733                 }
1734
1735               if (e->rank)
1736                 {
1737                   gfc_error ("By-value argument at %L cannot be an array or "
1738                              "an array section", &e->where);
1739                 return FAILURE;
1740                 }
1741
1742               /* Intrinsics are still PROC_UNKNOWN here.  However,
1743                  since same file external procedures are not resolvable
1744                  in gfortran, it is a good deal easier to leave them to
1745                  intrinsic.c.  */
1746               if (ptype != PROC_UNKNOWN
1747                   && ptype != PROC_DUMMY
1748                   && ptype != PROC_EXTERNAL
1749                   && ptype != PROC_MODULE)
1750                 {
1751                   gfc_error ("By-value argument at %L is not allowed "
1752                              "in this context", &e->where);
1753                   return FAILURE;
1754                 }
1755             }
1756
1757           /* Statement functions have already been excluded above.  */
1758           else if (strncmp ("%LOC", arg->name, 4) == 0
1759                    && e->ts.type == BT_PROCEDURE)
1760             {
1761               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1762                 {
1763                   gfc_error ("Passing internal procedure at %L by location "
1764                              "not allowed", &e->where);
1765                   return FAILURE;
1766                 }
1767             }
1768         }
1769
1770       /* Fortran 2008, C1237.  */
1771       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1772           && gfc_has_ultimate_pointer (e))
1773         {
1774           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1775                      "component", &e->where);
1776           return FAILURE;
1777         }
1778     }
1779
1780   return SUCCESS;
1781 }
1782
1783
1784 /* Do the checks of the actual argument list that are specific to elemental
1785    procedures.  If called with c == NULL, we have a function, otherwise if
1786    expr == NULL, we have a subroutine.  */
1787
1788 static gfc_try
1789 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1790 {
1791   gfc_actual_arglist *arg0;
1792   gfc_actual_arglist *arg;
1793   gfc_symbol *esym = NULL;
1794   gfc_intrinsic_sym *isym = NULL;
1795   gfc_expr *e = NULL;
1796   gfc_intrinsic_arg *iformal = NULL;
1797   gfc_formal_arglist *eformal = NULL;
1798   bool formal_optional = false;
1799   bool set_by_optional = false;
1800   int i;
1801   int rank = 0;
1802
1803   /* Is this an elemental procedure?  */
1804   if (expr && expr->value.function.actual != NULL)
1805     {
1806       if (expr->value.function.esym != NULL
1807           && expr->value.function.esym->attr.elemental)
1808         {
1809           arg0 = expr->value.function.actual;
1810           esym = expr->value.function.esym;
1811         }
1812       else if (expr->value.function.isym != NULL
1813                && expr->value.function.isym->elemental)
1814         {
1815           arg0 = expr->value.function.actual;
1816           isym = expr->value.function.isym;
1817         }
1818       else
1819         return SUCCESS;
1820     }
1821   else if (c && c->ext.actual != NULL)
1822     {
1823       arg0 = c->ext.actual;
1824       
1825       if (c->resolved_sym)
1826         esym = c->resolved_sym;
1827       else
1828         esym = c->symtree->n.sym;
1829       gcc_assert (esym);
1830
1831       if (!esym->attr.elemental)
1832         return SUCCESS;
1833     }
1834   else
1835     return SUCCESS;
1836
1837   /* The rank of an elemental is the rank of its array argument(s).  */
1838   for (arg = arg0; arg; arg = arg->next)
1839     {
1840       if (arg->expr != NULL && arg->expr->rank > 0)
1841         {
1842           rank = arg->expr->rank;
1843           if (arg->expr->expr_type == EXPR_VARIABLE
1844               && arg->expr->symtree->n.sym->attr.optional)
1845             set_by_optional = true;
1846
1847           /* Function specific; set the result rank and shape.  */
1848           if (expr)
1849             {
1850               expr->rank = rank;
1851               if (!expr->shape && arg->expr->shape)
1852                 {
1853                   expr->shape = gfc_get_shape (rank);
1854                   for (i = 0; i < rank; i++)
1855                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1856                 }
1857             }
1858           break;
1859         }
1860     }
1861
1862   /* If it is an array, it shall not be supplied as an actual argument
1863      to an elemental procedure unless an array of the same rank is supplied
1864      as an actual argument corresponding to a nonoptional dummy argument of
1865      that elemental procedure(12.4.1.5).  */
1866   formal_optional = false;
1867   if (isym)
1868     iformal = isym->formal;
1869   else
1870     eformal = esym->formal;
1871
1872   for (arg = arg0; arg; arg = arg->next)
1873     {
1874       if (eformal)
1875         {
1876           if (eformal->sym && eformal->sym->attr.optional)
1877             formal_optional = true;
1878           eformal = eformal->next;
1879         }
1880       else if (isym && iformal)
1881         {
1882           if (iformal->optional)
1883             formal_optional = true;
1884           iformal = iformal->next;
1885         }
1886       else if (isym)
1887         formal_optional = true;
1888
1889       if (pedantic && arg->expr != NULL
1890           && arg->expr->expr_type == EXPR_VARIABLE
1891           && arg->expr->symtree->n.sym->attr.optional
1892           && formal_optional
1893           && arg->expr->rank
1894           && (set_by_optional || arg->expr->rank != rank)
1895           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1896         {
1897           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1898                        "MISSING, it cannot be the actual argument of an "
1899                        "ELEMENTAL procedure unless there is a non-optional "
1900                        "argument with the same rank (12.4.1.5)",
1901                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1902           return FAILURE;
1903         }
1904     }
1905
1906   for (arg = arg0; arg; arg = arg->next)
1907     {
1908       if (arg->expr == NULL || arg->expr->rank == 0)
1909         continue;
1910
1911       /* Being elemental, the last upper bound of an assumed size array
1912          argument must be present.  */
1913       if (resolve_assumed_size_actual (arg->expr))
1914         return FAILURE;
1915
1916       /* Elemental procedure's array actual arguments must conform.  */
1917       if (e != NULL)
1918         {
1919           if (gfc_check_conformance (arg->expr, e,
1920                                      "elemental procedure") == FAILURE)
1921             return FAILURE;
1922         }
1923       else
1924         e = arg->expr;
1925     }
1926
1927   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1928      is an array, the intent inout/out variable needs to be also an array.  */
1929   if (rank > 0 && esym && expr == NULL)
1930     for (eformal = esym->formal, arg = arg0; arg && eformal;
1931          arg = arg->next, eformal = eformal->next)
1932       if ((eformal->sym->attr.intent == INTENT_OUT
1933            || eformal->sym->attr.intent == INTENT_INOUT)
1934           && arg->expr && arg->expr->rank == 0)
1935         {
1936           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1937                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1938                      "actual argument is an array", &arg->expr->where,
1939                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1940                      : "INOUT", eformal->sym->name, esym->name);
1941           return FAILURE;
1942         }
1943   return SUCCESS;
1944 }
1945
1946
1947 /* This function does the checking of references to global procedures
1948    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1949    77 and 95 standards.  It checks for a gsymbol for the name, making
1950    one if it does not already exist.  If it already exists, then the
1951    reference being resolved must correspond to the type of gsymbol.
1952    Otherwise, the new symbol is equipped with the attributes of the
1953    reference.  The corresponding code that is called in creating
1954    global entities is parse.c.
1955
1956    In addition, for all but -std=legacy, the gsymbols are used to
1957    check the interfaces of external procedures from the same file.
1958    The namespace of the gsymbol is resolved and then, once this is
1959    done the interface is checked.  */
1960
1961
1962 static bool
1963 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1964 {
1965   if (!gsym_ns->proc_name->attr.recursive)
1966     return true;
1967
1968   if (sym->ns == gsym_ns)
1969     return false;
1970
1971   if (sym->ns->parent && sym->ns->parent == gsym_ns)
1972     return false;
1973
1974   return true;
1975 }
1976
1977 static bool
1978 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
1979 {
1980   if (gsym_ns->entries)
1981     {
1982       gfc_entry_list *entry = gsym_ns->entries;
1983
1984       for (; entry; entry = entry->next)
1985         {
1986           if (strcmp (sym->name, entry->sym->name) == 0)
1987             {
1988               if (strcmp (gsym_ns->proc_name->name,
1989                           sym->ns->proc_name->name) == 0)
1990                 return false;
1991
1992               if (sym->ns->parent
1993                   && strcmp (gsym_ns->proc_name->name,
1994                              sym->ns->parent->proc_name->name) == 0)
1995                 return false;
1996             }
1997         }
1998     }
1999   return true;
2000 }
2001
2002 static void
2003 resolve_global_procedure (gfc_symbol *sym, locus *where,
2004                           gfc_actual_arglist **actual, int sub)
2005 {
2006   gfc_gsymbol * gsym;
2007   gfc_namespace *ns;
2008   enum gfc_symbol_type type;
2009
2010   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
2011
2012   gsym = gfc_get_gsymbol (sym->name);
2013
2014   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
2015     gfc_global_used (gsym, where);
2016
2017   if (gfc_option.flag_whole_file
2018         && (sym->attr.if_source == IFSRC_UNKNOWN
2019             || sym->attr.if_source == IFSRC_IFBODY)
2020         && gsym->type != GSYM_UNKNOWN
2021         && gsym->ns
2022         && gsym->ns->resolved != -1
2023         && gsym->ns->proc_name
2024         && not_in_recursive (sym, gsym->ns)
2025         && not_entry_self_reference (sym, gsym->ns))
2026     {
2027       gfc_symbol *def_sym;
2028
2029       /* Resolve the gsymbol namespace if needed.  */
2030       if (!gsym->ns->resolved)
2031         {
2032           gfc_dt_list *old_dt_list;
2033           struct gfc_omp_saved_state old_omp_state;
2034
2035           /* Stash away derived types so that the backend_decls do not
2036              get mixed up.  */
2037           old_dt_list = gfc_derived_types;
2038           gfc_derived_types = NULL;
2039           /* And stash away openmp state.  */
2040           gfc_omp_save_and_clear_state (&old_omp_state);
2041
2042           gfc_resolve (gsym->ns);
2043
2044           /* Store the new derived types with the global namespace.  */
2045           if (gfc_derived_types)
2046             gsym->ns->derived_types = gfc_derived_types;
2047
2048           /* Restore the derived types of this namespace.  */
2049           gfc_derived_types = old_dt_list;
2050           /* And openmp state.  */
2051           gfc_omp_restore_state (&old_omp_state);
2052         }
2053
2054       /* Make sure that translation for the gsymbol occurs before
2055          the procedure currently being resolved.  */
2056       ns = gfc_global_ns_list;
2057       for (; ns && ns != gsym->ns; ns = ns->sibling)
2058         {
2059           if (ns->sibling == gsym->ns)
2060             {
2061               ns->sibling = gsym->ns->sibling;
2062               gsym->ns->sibling = gfc_global_ns_list;
2063               gfc_global_ns_list = gsym->ns;
2064               break;
2065             }
2066         }
2067
2068       def_sym = gsym->ns->proc_name;
2069       if (def_sym->attr.entry_master)
2070         {
2071           gfc_entry_list *entry;
2072           for (entry = gsym->ns->entries; entry; entry = entry->next)
2073             if (strcmp (entry->sym->name, sym->name) == 0)
2074               {
2075                 def_sym = entry->sym;
2076                 break;
2077               }
2078         }
2079
2080       /* Differences in constant character lengths.  */
2081       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
2082         {
2083           long int l1 = 0, l2 = 0;
2084           gfc_charlen *cl1 = sym->ts.u.cl;
2085           gfc_charlen *cl2 = def_sym->ts.u.cl;
2086
2087           if (cl1 != NULL
2088               && cl1->length != NULL
2089               && cl1->length->expr_type == EXPR_CONSTANT)
2090             l1 = mpz_get_si (cl1->length->value.integer);
2091
2092           if (cl2 != NULL
2093               && cl2->length != NULL
2094               && cl2->length->expr_type == EXPR_CONSTANT)
2095             l2 = mpz_get_si (cl2->length->value.integer);
2096
2097           if (l1 && l2 && l1 != l2)
2098             gfc_error ("Character length mismatch in return type of "
2099                        "function '%s' at %L (%ld/%ld)", sym->name,
2100                        &sym->declared_at, l1, l2);
2101         }
2102
2103      /* Type mismatch of function return type and expected type.  */
2104      if (sym->attr.function
2105          && !gfc_compare_types (&sym->ts, &def_sym->ts))
2106         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
2107                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2108                    gfc_typename (&def_sym->ts));
2109
2110       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
2111         {
2112           gfc_formal_arglist *arg = def_sym->formal;
2113           for ( ; arg; arg = arg->next)
2114             if (!arg->sym)
2115               continue;
2116             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
2117             else if (arg->sym->attr.allocatable
2118                      || arg->sym->attr.asynchronous
2119                      || arg->sym->attr.optional
2120                      || arg->sym->attr.pointer
2121                      || arg->sym->attr.target
2122                      || arg->sym->attr.value
2123                      || arg->sym->attr.volatile_)
2124               {
2125                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
2126                            "has an attribute that requires an explicit "
2127                            "interface for this procedure", arg->sym->name,
2128                            sym->name, &sym->declared_at);
2129                 break;
2130               }
2131             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
2132             else if (arg->sym && arg->sym->as
2133                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
2134               {
2135                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
2136                            "argument '%s' must have an explicit interface",
2137                            sym->name, &sym->declared_at, arg->sym->name);
2138                 break;
2139               }
2140             /* F2008, 12.4.2.2 (2c)  */
2141             else if (arg->sym->attr.codimension)
2142               {
2143                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
2144                            "'%s' must have an explicit interface",
2145                            sym->name, &sym->declared_at, arg->sym->name);
2146                 break;
2147               }
2148             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
2149             else if (false) /* TODO: is a parametrized derived type  */
2150               {
2151                 gfc_error ("Procedure '%s' at %L with parametrized derived "
2152                            "type argument '%s' must have an explicit "
2153                            "interface", sym->name, &sym->declared_at,
2154                            arg->sym->name);
2155                 break;
2156               }
2157             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
2158             else if (arg->sym->ts.type == BT_CLASS)
2159               {
2160                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
2161                            "argument '%s' must have an explicit interface",
2162                            sym->name, &sym->declared_at, arg->sym->name);
2163                 break;
2164               }
2165         }
2166
2167       if (def_sym->attr.function)
2168         {
2169           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
2170           if (def_sym->as && def_sym->as->rank
2171               && (!sym->as || sym->as->rank != def_sym->as->rank))
2172             gfc_error ("The reference to function '%s' at %L either needs an "
2173                        "explicit INTERFACE or the rank is incorrect", sym->name,
2174                        where);
2175
2176           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
2177           if ((def_sym->result->attr.pointer
2178                || def_sym->result->attr.allocatable)
2179                && (sym->attr.if_source != IFSRC_IFBODY
2180                    || def_sym->result->attr.pointer
2181                         != sym->result->attr.pointer
2182                    || def_sym->result->attr.allocatable
2183                         != sym->result->attr.allocatable))
2184             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
2185                        "result must have an explicit interface", sym->name,
2186                        where);
2187
2188           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
2189           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
2190               && def_sym->ts.u.cl->length != NULL)
2191             {
2192               gfc_charlen *cl = sym->ts.u.cl;
2193
2194               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
2195                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
2196                 {
2197                   gfc_error ("Nonconstant character-length function '%s' at %L "
2198                              "must have an explicit interface", sym->name,
2199                              &sym->declared_at);
2200                 }
2201             }
2202         }
2203
2204       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2205       if (def_sym->attr.elemental && !sym->attr.elemental)
2206         {
2207           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2208                      "interface", sym->name, &sym->declared_at);
2209         }
2210
2211       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2212       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2213         {
2214           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2215                      "an explicit interface", sym->name, &sym->declared_at);
2216         }
2217
2218       if (gfc_option.flag_whole_file == 1
2219           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2220               && !(gfc_option.warn_std & GFC_STD_GNU)))
2221         gfc_errors_to_warnings (1);
2222
2223       if (sym->attr.if_source != IFSRC_IFBODY)  
2224         gfc_procedure_use (def_sym, actual, where);
2225
2226       gfc_errors_to_warnings (0);
2227     }
2228
2229   if (gsym->type == GSYM_UNKNOWN)
2230     {
2231       gsym->type = type;
2232       gsym->where = *where;
2233     }
2234
2235   gsym->used = 1;
2236 }
2237
2238
2239 /************* Function resolution *************/
2240
2241 /* Resolve a function call known to be generic.
2242    Section 14.1.2.4.1.  */
2243
2244 static match
2245 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2246 {
2247   gfc_symbol *s;
2248
2249   if (sym->attr.generic)
2250     {
2251       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2252       if (s != NULL)
2253         {
2254           expr->value.function.name = s->name;
2255           expr->value.function.esym = s;
2256
2257           if (s->ts.type != BT_UNKNOWN)
2258             expr->ts = s->ts;
2259           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2260             expr->ts = s->result->ts;
2261
2262           if (s->as != NULL)
2263             expr->rank = s->as->rank;
2264           else if (s->result != NULL && s->result->as != NULL)
2265             expr->rank = s->result->as->rank;
2266
2267           gfc_set_sym_referenced (expr->value.function.esym);
2268
2269           return MATCH_YES;
2270         }
2271
2272       /* TODO: Need to search for elemental references in generic
2273          interface.  */
2274     }
2275
2276   if (sym->attr.intrinsic)
2277     return gfc_intrinsic_func_interface (expr, 0);
2278
2279   return MATCH_NO;
2280 }
2281
2282
2283 static gfc_try
2284 resolve_generic_f (gfc_expr *expr)
2285 {
2286   gfc_symbol *sym;
2287   match m;
2288
2289   sym = expr->symtree->n.sym;
2290
2291   for (;;)
2292     {
2293       m = resolve_generic_f0 (expr, sym);
2294       if (m == MATCH_YES)
2295         return SUCCESS;
2296       else if (m == MATCH_ERROR)
2297         return FAILURE;
2298
2299 generic:
2300       if (sym->ns->parent == NULL)
2301         break;
2302       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2303
2304       if (sym == NULL)
2305         break;
2306       if (!generic_sym (sym))
2307         goto generic;
2308     }
2309
2310   /* Last ditch attempt.  See if the reference is to an intrinsic
2311      that possesses a matching interface.  14.1.2.4  */
2312   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
2313     {
2314       gfc_error ("There is no specific function for the generic '%s' at %L",
2315                  expr->symtree->n.sym->name, &expr->where);
2316       return FAILURE;
2317     }
2318
2319   m = gfc_intrinsic_func_interface (expr, 0);
2320   if (m == MATCH_YES)
2321     return SUCCESS;
2322   if (m == MATCH_NO)
2323     gfc_error ("Generic function '%s' at %L is not consistent with a "
2324                "specific intrinsic interface", expr->symtree->n.sym->name,
2325                &expr->where);
2326
2327   return FAILURE;
2328 }
2329
2330
2331 /* Resolve a function call known to be specific.  */
2332
2333 static match
2334 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2335 {
2336   match m;
2337
2338   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2339     {
2340       if (sym->attr.dummy)
2341         {
2342           sym->attr.proc = PROC_DUMMY;
2343           goto found;
2344         }
2345
2346       sym->attr.proc = PROC_EXTERNAL;
2347       goto found;
2348     }
2349
2350   if (sym->attr.proc == PROC_MODULE
2351       || sym->attr.proc == PROC_ST_FUNCTION
2352       || sym->attr.proc == PROC_INTERNAL)
2353     goto found;
2354
2355   if (sym->attr.intrinsic)
2356     {
2357       m = gfc_intrinsic_func_interface (expr, 1);
2358       if (m == MATCH_YES)
2359         return MATCH_YES;
2360       if (m == MATCH_NO)
2361         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2362                    "with an intrinsic", sym->name, &expr->where);
2363
2364       return MATCH_ERROR;
2365     }
2366
2367   return MATCH_NO;
2368
2369 found:
2370   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2371
2372   if (sym->result)
2373     expr->ts = sym->result->ts;
2374   else
2375     expr->ts = sym->ts;
2376   expr->value.function.name = sym->name;
2377   expr->value.function.esym = sym;
2378   if (sym->as != NULL)
2379     expr->rank = sym->as->rank;
2380
2381   return MATCH_YES;
2382 }
2383
2384
2385 static gfc_try
2386 resolve_specific_f (gfc_expr *expr)
2387 {
2388   gfc_symbol *sym;
2389   match m;
2390
2391   sym = expr->symtree->n.sym;
2392
2393   for (;;)
2394     {
2395       m = resolve_specific_f0 (sym, expr);
2396       if (m == MATCH_YES)
2397         return SUCCESS;
2398       if (m == MATCH_ERROR)
2399         return FAILURE;
2400
2401       if (sym->ns->parent == NULL)
2402         break;
2403
2404       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2405
2406       if (sym == NULL)
2407         break;
2408     }
2409
2410   gfc_error ("Unable to resolve the specific function '%s' at %L",
2411              expr->symtree->n.sym->name, &expr->where);
2412
2413   return SUCCESS;
2414 }
2415
2416
2417 /* Resolve a procedure call not known to be generic nor specific.  */
2418
2419 static gfc_try
2420 resolve_unknown_f (gfc_expr *expr)
2421 {
2422   gfc_symbol *sym;
2423   gfc_typespec *ts;
2424
2425   sym = expr->symtree->n.sym;
2426
2427   if (sym->attr.dummy)
2428     {
2429       sym->attr.proc = PROC_DUMMY;
2430       expr->value.function.name = sym->name;
2431       goto set_type;
2432     }
2433
2434   /* See if we have an intrinsic function reference.  */
2435
2436   if (gfc_is_intrinsic (sym, 0, expr->where))
2437     {
2438       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2439         return SUCCESS;
2440       return FAILURE;
2441     }
2442
2443   /* The reference is to an external name.  */
2444
2445   sym->attr.proc = PROC_EXTERNAL;
2446   expr->value.function.name = sym->name;
2447   expr->value.function.esym = expr->symtree->n.sym;
2448
2449   if (sym->as != NULL)
2450     expr->rank = sym->as->rank;
2451
2452   /* Type of the expression is either the type of the symbol or the
2453      default type of the symbol.  */
2454
2455 set_type:
2456   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2457
2458   if (sym->ts.type != BT_UNKNOWN)
2459     expr->ts = sym->ts;
2460   else
2461     {
2462       ts = gfc_get_default_type (sym->name, sym->ns);
2463
2464       if (ts->type == BT_UNKNOWN)
2465         {
2466           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2467                      sym->name, &expr->where);
2468           return FAILURE;
2469         }
2470       else
2471         expr->ts = *ts;
2472     }
2473
2474   return SUCCESS;
2475 }
2476
2477
2478 /* Return true, if the symbol is an external procedure.  */
2479 static bool
2480 is_external_proc (gfc_symbol *sym)
2481 {
2482   if (!sym->attr.dummy && !sym->attr.contained
2483         && !(sym->attr.intrinsic
2484               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2485         && sym->attr.proc != PROC_ST_FUNCTION
2486         && !sym->attr.proc_pointer
2487         && !sym->attr.use_assoc
2488         && sym->name)
2489     return true;
2490
2491   return false;
2492 }
2493
2494
2495 /* Figure out if a function reference is pure or not.  Also set the name
2496    of the function for a potential error message.  Return nonzero if the
2497    function is PURE, zero if not.  */
2498 static int
2499 pure_stmt_function (gfc_expr *, gfc_symbol *);
2500
2501 static int
2502 pure_function (gfc_expr *e, const char **name)
2503 {
2504   int pure;
2505
2506   *name = NULL;
2507
2508   if (e->symtree != NULL
2509         && e->symtree->n.sym != NULL
2510         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2511     return pure_stmt_function (e, e->symtree->n.sym);
2512
2513   if (e->value.function.esym)
2514     {
2515       pure = gfc_pure (e->value.function.esym);
2516       *name = e->value.function.esym->name;
2517     }
2518   else if (e->value.function.isym)
2519     {
2520       pure = e->value.function.isym->pure
2521              || e->value.function.isym->elemental;
2522       *name = e->value.function.isym->name;
2523     }
2524   else
2525     {
2526       /* Implicit functions are not pure.  */
2527       pure = 0;
2528       *name = e->value.function.name;
2529     }
2530
2531   return pure;
2532 }
2533
2534
2535 static bool
2536 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2537                  int *f ATTRIBUTE_UNUSED)
2538 {
2539   const char *name;
2540
2541   /* Don't bother recursing into other statement functions
2542      since they will be checked individually for purity.  */
2543   if (e->expr_type != EXPR_FUNCTION
2544         || !e->symtree
2545         || e->symtree->n.sym == sym
2546         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2547     return false;
2548
2549   return pure_function (e, &name) ? false : true;
2550 }
2551
2552
2553 static int
2554 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2555 {
2556   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2557 }
2558
2559
2560 static gfc_try
2561 is_scalar_expr_ptr (gfc_expr *expr)
2562 {
2563   gfc_try retval = SUCCESS;
2564   gfc_ref *ref;
2565   int start;
2566   int end;
2567
2568   /* See if we have a gfc_ref, which means we have a substring, array
2569      reference, or a component.  */
2570   if (expr->ref != NULL)
2571     {
2572       ref = expr->ref;
2573       while (ref->next != NULL)
2574         ref = ref->next;
2575
2576       switch (ref->type)
2577         {
2578         case REF_SUBSTRING:
2579           if (ref->u.ss.start == NULL || ref->u.ss.end == NULL
2580               || gfc_dep_compare_expr (ref->u.ss.start, ref->u.ss.end) != 0)
2581             retval = FAILURE;
2582           break;
2583
2584         case REF_ARRAY:
2585           if (ref->u.ar.type == AR_ELEMENT)
2586             retval = SUCCESS;
2587           else if (ref->u.ar.type == AR_FULL)
2588             {
2589               /* The user can give a full array if the array is of size 1.  */
2590               if (ref->u.ar.as != NULL
2591                   && ref->u.ar.as->rank == 1
2592                   && ref->u.ar.as->type == AS_EXPLICIT
2593                   && ref->u.ar.as->lower[0] != NULL
2594                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2595                   && ref->u.ar.as->upper[0] != NULL
2596                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2597                 {
2598                   /* If we have a character string, we need to check if
2599                      its length is one.  */
2600                   if (expr->ts.type == BT_CHARACTER)
2601                     {
2602                       if (expr->ts.u.cl == NULL
2603                           || expr->ts.u.cl->length == NULL
2604                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2605                           != 0)
2606                         retval = FAILURE;
2607                     }
2608                   else
2609                     {
2610                       /* We have constant lower and upper bounds.  If the
2611                          difference between is 1, it can be considered a
2612                          scalar.  
2613                          FIXME: Use gfc_dep_compare_expr instead.  */
2614                       start = (int) mpz_get_si
2615                                 (ref->u.ar.as->lower[0]->value.integer);
2616                       end = (int) mpz_get_si
2617                                 (ref->u.ar.as->upper[0]->value.integer);
2618                       if (end - start + 1 != 1)
2619                         retval = FAILURE;
2620                    }
2621                 }
2622               else
2623                 retval = FAILURE;
2624             }
2625           else
2626             retval = FAILURE;
2627           break;
2628         default:
2629           retval = SUCCESS;
2630           break;
2631         }
2632     }
2633   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2634     {
2635       /* Character string.  Make sure it's of length 1.  */
2636       if (expr->ts.u.cl == NULL
2637           || expr->ts.u.cl->length == NULL
2638           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2639         retval = FAILURE;
2640     }
2641   else if (expr->rank != 0)
2642     retval = FAILURE;
2643
2644   return retval;
2645 }
2646
2647
2648 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2649    and, in the case of c_associated, set the binding label based on
2650    the arguments.  */
2651
2652 static gfc_try
2653 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2654                           gfc_symbol **new_sym)
2655 {
2656   char name[GFC_MAX_SYMBOL_LEN + 1];
2657   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2658   int optional_arg = 0;
2659   gfc_try retval = SUCCESS;
2660   gfc_symbol *args_sym;
2661   gfc_typespec *arg_ts;
2662   symbol_attribute arg_attr;
2663
2664   if (args->expr->expr_type == EXPR_CONSTANT
2665       || args->expr->expr_type == EXPR_OP
2666       || args->expr->expr_type == EXPR_NULL)
2667     {
2668       gfc_error ("Argument to '%s' at %L is not a variable",
2669                  sym->name, &(args->expr->where));
2670       return FAILURE;
2671     }
2672
2673   args_sym = args->expr->symtree->n.sym;
2674
2675   /* The typespec for the actual arg should be that stored in the expr
2676      and not necessarily that of the expr symbol (args_sym), because
2677      the actual expression could be a part-ref of the expr symbol.  */
2678   arg_ts = &(args->expr->ts);
2679   arg_attr = gfc_expr_attr (args->expr);
2680     
2681   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2682     {
2683       /* If the user gave two args then they are providing something for
2684          the optional arg (the second cptr).  Therefore, set the name and
2685          binding label to the c_associated for two cptrs.  Otherwise,
2686          set c_associated to expect one cptr.  */
2687       if (args->next)
2688         {
2689           /* two args.  */
2690           sprintf (name, "%s_2", sym->name);
2691           sprintf (binding_label, "%s_2", sym->binding_label);
2692           optional_arg = 1;
2693         }
2694       else
2695         {
2696           /* one arg.  */
2697           sprintf (name, "%s_1", sym->name);
2698           sprintf (binding_label, "%s_1", sym->binding_label);
2699           optional_arg = 0;
2700         }
2701
2702       /* Get a new symbol for the version of c_associated that
2703          will get called.  */
2704       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2705     }
2706   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2707            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2708     {
2709       sprintf (name, "%s", sym->name);
2710       sprintf (binding_label, "%s", sym->binding_label);
2711
2712       /* Error check the call.  */
2713       if (args->next != NULL)
2714         {
2715           gfc_error_now ("More actual than formal arguments in '%s' "
2716                          "call at %L", name, &(args->expr->where));
2717           retval = FAILURE;
2718         }
2719       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2720         {
2721           gfc_ref *ref;
2722           bool seen_section;
2723
2724           /* Make sure we have either the target or pointer attribute.  */
2725           if (!arg_attr.target && !arg_attr.pointer)
2726             {
2727               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2728                              "a TARGET or an associated pointer",
2729                              args_sym->name,
2730                              sym->name, &(args->expr->where));
2731               retval = FAILURE;
2732             }
2733
2734           if (gfc_is_coindexed (args->expr))
2735             {
2736               gfc_error_now ("Coindexed argument not permitted"
2737                              " in '%s' call at %L", name,
2738                              &(args->expr->where));
2739               retval = FAILURE;
2740             }
2741
2742           /* Follow references to make sure there are no array
2743              sections.  */
2744           seen_section = false;
2745
2746           for (ref=args->expr->ref; ref; ref = ref->next)
2747             {
2748               if (ref->type == REF_ARRAY)
2749                 {
2750                   if (ref->u.ar.type == AR_SECTION)
2751                     seen_section = true;
2752
2753                   if (ref->u.ar.type != AR_ELEMENT)
2754                     {
2755                       gfc_ref *r;
2756                       for (r = ref->next; r; r=r->next)
2757                         if (r->type == REF_COMPONENT)
2758                           {
2759                             gfc_error_now ("Array section not permitted"
2760                                            " in '%s' call at %L", name,
2761                                            &(args->expr->where));
2762                             retval = FAILURE;
2763                             break;
2764                           }
2765                     }
2766                 }
2767             }
2768
2769           if (seen_section && retval == SUCCESS)
2770             gfc_warning ("Array section in '%s' call at %L", name,
2771                          &(args->expr->where));
2772                          
2773           /* See if we have interoperable type and type param.  */
2774           if (verify_c_interop (arg_ts) == SUCCESS
2775               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2776             {
2777               if (args_sym->attr.target == 1)
2778                 {
2779                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2780                      has the target attribute and is interoperable.  */
2781                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2782                      allocatable variable that has the TARGET attribute and
2783                      is not an array of zero size.  */
2784                   if (args_sym->attr.allocatable == 1)
2785                     {
2786                       if (args_sym->attr.dimension != 0 
2787                           && (args_sym->as && args_sym->as->rank == 0))
2788                         {
2789                           gfc_error_now ("Allocatable variable '%s' used as a "
2790                                          "parameter to '%s' at %L must not be "
2791                                          "an array of zero size",
2792                                          args_sym->name, sym->name,
2793                                          &(args->expr->where));
2794                           retval = FAILURE;
2795                         }
2796                     }
2797                   else
2798                     {
2799                       /* A non-allocatable target variable with C
2800                          interoperable type and type parameters must be
2801                          interoperable.  */
2802                       if (args_sym && args_sym->attr.dimension)
2803                         {
2804                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2805                             {
2806                               gfc_error ("Assumed-shape array '%s' at %L "
2807                                          "cannot be an argument to the "
2808                                          "procedure '%s' because "
2809                                          "it is not C interoperable",
2810                                          args_sym->name,
2811                                          &(args->expr->where), sym->name);
2812                               retval = FAILURE;
2813                             }
2814                           else if (args_sym->as->type == AS_DEFERRED)
2815                             {
2816                               gfc_error ("Deferred-shape array '%s' at %L "
2817                                          "cannot be an argument to the "
2818                                          "procedure '%s' because "
2819                                          "it is not C interoperable",
2820                                          args_sym->name,
2821                                          &(args->expr->where), sym->name);
2822                               retval = FAILURE;
2823                             }
2824                         }
2825                               
2826                       /* Make sure it's not a character string.  Arrays of
2827                          any type should be ok if the variable is of a C
2828                          interoperable type.  */
2829                       if (arg_ts->type == BT_CHARACTER)
2830                         if (arg_ts->u.cl != NULL
2831                             && (arg_ts->u.cl->length == NULL
2832                                 || arg_ts->u.cl->length->expr_type
2833                                    != EXPR_CONSTANT
2834                                 || mpz_cmp_si
2835                                     (arg_ts->u.cl->length->value.integer, 1)
2836                                    != 0)
2837                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2838                           {
2839                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2840                                            "at %L must have a length of 1",
2841                                            args_sym->name, sym->name,
2842                                            &(args->expr->where));
2843                             retval = FAILURE;
2844                           }
2845                     }
2846                 }
2847               else if (arg_attr.pointer
2848                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2849                 {
2850                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2851                      scalar pointer.  */
2852                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2853                                  "associated scalar POINTER", args_sym->name,
2854                                  sym->name, &(args->expr->where));
2855                   retval = FAILURE;
2856                 }
2857             }
2858           else
2859             {
2860               /* The parameter is not required to be C interoperable.  If it
2861                  is not C interoperable, it must be a nonpolymorphic scalar
2862                  with no length type parameters.  It still must have either
2863                  the pointer or target attribute, and it can be
2864                  allocatable (but must be allocated when c_loc is called).  */
2865               if (args->expr->rank != 0 
2866                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2867                 {
2868                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2869                                  "scalar", args_sym->name, sym->name,
2870                                  &(args->expr->where));
2871                   retval = FAILURE;
2872                 }
2873               else if (arg_ts->type == BT_CHARACTER 
2874                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2875                 {
2876                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2877                                  "%L must have a length of 1",
2878                                  args_sym->name, sym->name,
2879                                  &(args->expr->where));
2880                   retval = FAILURE;
2881                 }
2882               else if (arg_ts->type == BT_CLASS)
2883                 {
2884                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
2885                                  "polymorphic", args_sym->name, sym->name,
2886                                  &(args->expr->where));
2887                   retval = FAILURE;
2888                 }
2889             }
2890         }
2891       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2892         {
2893           if (args_sym->attr.flavor != FL_PROCEDURE)
2894             {
2895               /* TODO: Update this error message to allow for procedure
2896                  pointers once they are implemented.  */
2897               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2898                              "procedure",
2899                              args_sym->name, sym->name,
2900                              &(args->expr->where));
2901               retval = FAILURE;
2902             }
2903           else if (args_sym->attr.is_bind_c != 1)
2904             {
2905               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2906                              "BIND(C)",
2907                              args_sym->name, sym->name,
2908                              &(args->expr->where));
2909               retval = FAILURE;
2910             }
2911         }
2912       
2913       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2914       *new_sym = sym;
2915     }
2916   else
2917     {
2918       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2919                           "iso_c_binding function: '%s'!\n", sym->name);
2920     }
2921
2922   return retval;
2923 }
2924
2925
2926 /* Resolve a function call, which means resolving the arguments, then figuring
2927    out which entity the name refers to.  */
2928
2929 static gfc_try
2930 resolve_function (gfc_expr *expr)
2931 {
2932   gfc_actual_arglist *arg;
2933   gfc_symbol *sym;
2934   const char *name;
2935   gfc_try t;
2936   int temp;
2937   procedure_type p = PROC_INTRINSIC;
2938   bool no_formal_args;
2939
2940   sym = NULL;
2941   if (expr->symtree)
2942     sym = expr->symtree->n.sym;
2943
2944   /* If this is a procedure pointer component, it has already been resolved.  */
2945   if (gfc_is_proc_ptr_comp (expr, NULL))
2946     return SUCCESS;
2947   
2948   if (sym && sym->attr.intrinsic
2949       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2950     return FAILURE;
2951
2952   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2953     {
2954       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2955       return FAILURE;
2956     }
2957
2958   /* If this ia a deferred TBP with an abstract interface (which may
2959      of course be referenced), expr->value.function.esym will be set.  */
2960   if (sym && sym->attr.abstract && !expr->value.function.esym)
2961     {
2962       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2963                  sym->name, &expr->where);
2964       return FAILURE;
2965     }
2966
2967   /* Switch off assumed size checking and do this again for certain kinds
2968      of procedure, once the procedure itself is resolved.  */
2969   need_full_assumed_size++;
2970
2971   if (expr->symtree && expr->symtree->n.sym)
2972     p = expr->symtree->n.sym->attr.proc;
2973
2974   if (expr->value.function.isym && expr->value.function.isym->inquiry)
2975     inquiry_argument = true;
2976   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2977
2978   if (resolve_actual_arglist (expr->value.function.actual,
2979                               p, no_formal_args) == FAILURE)
2980     {
2981       inquiry_argument = false;
2982       return FAILURE;
2983     }
2984
2985   inquiry_argument = false;
2986  
2987   /* Need to setup the call to the correct c_associated, depending on
2988      the number of cptrs to user gives to compare.  */
2989   if (sym && sym->attr.is_iso_c == 1)
2990     {
2991       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2992           == FAILURE)
2993         return FAILURE;
2994       
2995       /* Get the symtree for the new symbol (resolved func).
2996          the old one will be freed later, when it's no longer used.  */
2997       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2998     }
2999   
3000   /* Resume assumed_size checking.  */
3001   need_full_assumed_size--;
3002
3003   /* If the procedure is external, check for usage.  */
3004   if (sym && is_external_proc (sym))
3005     resolve_global_procedure (sym, &expr->where,
3006                               &expr->value.function.actual, 0);
3007
3008   if (sym && sym->ts.type == BT_CHARACTER
3009       && sym->ts.u.cl
3010       && sym->ts.u.cl->length == NULL
3011       && !sym->attr.dummy
3012       && !sym->ts.deferred
3013       && expr->value.function.esym == NULL
3014       && !sym->attr.contained)
3015     {
3016       /* Internal procedures are taken care of in resolve_contained_fntype.  */
3017       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
3018                  "be used at %L since it is not a dummy argument",
3019                  sym->name, &expr->where);
3020       return FAILURE;
3021     }
3022
3023   /* See if function is already resolved.  */
3024
3025   if (expr->value.function.name != NULL)
3026     {
3027       if (expr->ts.type == BT_UNKNOWN)
3028         expr->ts = sym->ts;
3029       t = SUCCESS;
3030     }
3031   else
3032     {
3033       /* Apply the rules of section 14.1.2.  */
3034
3035       switch (procedure_kind (sym))
3036         {
3037         case PTYPE_GENERIC:
3038           t = resolve_generic_f (expr);
3039           break;
3040
3041         case PTYPE_SPECIFIC:
3042           t = resolve_specific_f (expr);
3043           break;
3044
3045         case PTYPE_UNKNOWN:
3046           t = resolve_unknown_f (expr);
3047           break;
3048
3049         default:
3050           gfc_internal_error ("resolve_function(): bad function type");
3051         }
3052     }
3053
3054   /* If the expression is still a function (it might have simplified),
3055      then we check to see if we are calling an elemental function.  */
3056
3057   if (expr->expr_type != EXPR_FUNCTION)
3058     return t;
3059
3060   temp = need_full_assumed_size;
3061   need_full_assumed_size = 0;
3062
3063   if (resolve_elemental_actual (expr, NULL) == FAILURE)
3064     return FAILURE;
3065
3066   if (omp_workshare_flag
3067       && expr->value.function.esym
3068       && ! gfc_elemental (expr->value.function.esym))
3069     {
3070       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
3071                  "in WORKSHARE construct", expr->value.function.esym->name,
3072                  &expr->where);
3073       t = FAILURE;
3074     }
3075
3076 #define GENERIC_ID expr->value.function.isym->id
3077   else if (expr->value.function.actual != NULL
3078            && expr->value.function.isym != NULL
3079            && GENERIC_ID != GFC_ISYM_LBOUND
3080            && GENERIC_ID != GFC_ISYM_LEN
3081            && GENERIC_ID != GFC_ISYM_LOC
3082            && GENERIC_ID != GFC_ISYM_PRESENT)
3083     {
3084       /* Array intrinsics must also have the last upper bound of an
3085          assumed size array argument.  UBOUND and SIZE have to be
3086          excluded from the check if the second argument is anything
3087          than a constant.  */
3088
3089       for (arg = expr->value.function.actual; arg; arg = arg->next)
3090         {
3091           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3092               && arg->next != NULL && arg->next->expr)
3093             {
3094               if (arg->next->expr->expr_type != EXPR_CONSTANT)
3095                 break;
3096
3097               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
3098                 break;
3099
3100               if ((int)mpz_get_si (arg->next->expr->value.integer)
3101                         < arg->expr->rank)
3102                 break;
3103             }
3104
3105           if (arg->expr != NULL
3106               && arg->expr->rank > 0
3107               && resolve_assumed_size_actual (arg->expr))
3108             return FAILURE;
3109         }
3110     }
3111 #undef GENERIC_ID
3112
3113   need_full_assumed_size = temp;
3114   name = NULL;
3115
3116   if (!pure_function (expr, &name) && name)
3117     {
3118       if (forall_flag)
3119         {
3120           gfc_error ("reference to non-PURE function '%s' at %L inside a "
3121                      "FORALL %s", name, &expr->where,
3122                      forall_flag == 2 ? "mask" : "block");
3123           t = FAILURE;
3124         }
3125       else if (gfc_pure (NULL))
3126         {
3127           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
3128                      "procedure within a PURE procedure", name, &expr->where);
3129           t = FAILURE;
3130         }
3131     }
3132
3133   if (!pure_function (expr, &name) && name && gfc_implicit_pure (NULL))
3134     gfc_current_ns->proc_name->attr.implicit_pure = 0;
3135
3136   /* Functions without the RECURSIVE attribution are not allowed to
3137    * call themselves.  */
3138   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3139     {
3140       gfc_symbol *esym;
3141       esym = expr->value.function.esym;
3142
3143       if (is_illegal_recursion (esym, gfc_current_ns))
3144       {
3145         if (esym->attr.entry && esym->ns->entries)
3146           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3147                      " function '%s' is not RECURSIVE",
3148                      esym->name, &expr->where, esym->ns->entries->sym->name);
3149         else
3150           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
3151                      " is not RECURSIVE", esym->name, &expr->where);
3152
3153         t = FAILURE;
3154       }
3155     }
3156
3157   /* Character lengths of use associated functions may contains references to
3158      symbols not referenced from the current program unit otherwise.  Make sure
3159      those symbols are marked as referenced.  */
3160
3161   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3162       && expr->value.function.esym->attr.use_assoc)
3163     {
3164       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3165     }
3166
3167   /* Make sure that the expression has a typespec that works.  */
3168   if (expr->ts.type == BT_UNKNOWN)
3169     {
3170       if (expr->symtree->n.sym->result
3171             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3172             && !expr->symtree->n.sym->result->attr.proc_pointer)
3173         expr->ts = expr->symtree->n.sym->result->ts;
3174     }
3175
3176   return t;
3177 }
3178
3179
3180 /************* Subroutine resolution *************/
3181
3182 static void
3183 pure_subroutine (gfc_code *c, gfc_symbol *sym)
3184 {
3185   if (gfc_pure (sym))
3186     return;
3187
3188   if (forall_flag)
3189     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
3190                sym->name, &c->loc);
3191   else if (gfc_pure (NULL))
3192     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
3193                &c->loc);
3194 }
3195
3196
3197 static match
3198 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3199 {
3200   gfc_symbol *s;
3201
3202   if (sym->attr.generic)
3203     {
3204       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3205       if (s != NULL)
3206         {
3207           c->resolved_sym = s;
3208           pure_subroutine (c, s);
3209           return MATCH_YES;
3210         }
3211
3212       /* TODO: Need to search for elemental references in generic interface.  */
3213     }
3214
3215   if (sym->attr.intrinsic)
3216     return gfc_intrinsic_sub_interface (c, 0);
3217
3218   return MATCH_NO;
3219 }
3220
3221
3222 static gfc_try
3223 resolve_generic_s (gfc_code *c)
3224 {
3225   gfc_symbol *sym;
3226   match m;
3227
3228   sym = c->symtree->n.sym;
3229
3230   for (;;)
3231     {
3232       m = resolve_generic_s0 (c, sym);
3233       if (m == MATCH_YES)
3234         return SUCCESS;
3235       else if (m == MATCH_ERROR)
3236         return FAILURE;
3237
3238 generic:
3239       if (sym->ns->parent == NULL)
3240         break;
3241       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3242
3243       if (sym == NULL)
3244         break;
3245       if (!generic_sym (sym))
3246         goto generic;
3247     }
3248
3249   /* Last ditch attempt.  See if the reference is to an intrinsic
3250      that possesses a matching interface.  14.1.2.4  */
3251   sym = c->symtree->n.sym;
3252
3253   if (!gfc_is_intrinsic (sym, 1, c->loc))
3254     {
3255       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3256                  sym->name, &c->loc);
3257       return FAILURE;
3258     }
3259
3260   m = gfc_intrinsic_sub_interface (c, 0);
3261   if (m == MATCH_YES)
3262     return SUCCESS;
3263   if (m == MATCH_NO)
3264     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3265                "intrinsic subroutine interface", sym->name, &c->loc);
3266
3267   return FAILURE;
3268 }
3269
3270
3271 /* Set the name and binding label of the subroutine symbol in the call
3272    expression represented by 'c' to include the type and kind of the
3273    second parameter.  This function is for resolving the appropriate
3274    version of c_f_pointer() and c_f_procpointer().  For example, a
3275    call to c_f_pointer() for a default integer pointer could have a
3276    name of c_f_pointer_i4.  If no second arg exists, which is an error
3277    for these two functions, it defaults to the generic symbol's name
3278    and binding label.  */
3279
3280 static void
3281 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3282                     char *name, char *binding_label)
3283 {
3284   gfc_expr *arg = NULL;
3285   char type;
3286   int kind;
3287
3288   /* The second arg of c_f_pointer and c_f_procpointer determines
3289      the type and kind for the procedure name.  */
3290   arg = c->ext.actual->next->expr;
3291
3292   if (arg != NULL)
3293     {
3294       /* Set up the name to have the given symbol's name,
3295          plus the type and kind.  */
3296       /* a derived type is marked with the type letter 'u' */
3297       if (arg->ts.type == BT_DERIVED)
3298         {
3299           type = 'd';
3300           kind = 0; /* set the kind as 0 for now */
3301         }
3302       else
3303         {
3304           type = gfc_type_letter (arg->ts.type);
3305           kind = arg->ts.kind;
3306         }
3307
3308       if (arg->ts.type == BT_CHARACTER)
3309         /* Kind info for character strings not needed.  */
3310         kind = 0;
3311
3312       sprintf (name, "%s_%c%d", sym->name, type, kind);
3313       /* Set up the binding label as the given symbol's label plus
3314          the type and kind.  */
3315       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
3316     }
3317   else
3318     {
3319       /* If the second arg is missing, set the name and label as
3320          was, cause it should at least be found, and the missing
3321          arg error will be caught by compare_parameters().  */
3322       sprintf (name, "%s", sym->name);
3323       sprintf (binding_label, "%s", sym->binding_label);
3324     }
3325    
3326   return;
3327 }
3328
3329
3330 /* Resolve a generic version of the iso_c_binding procedure given
3331    (sym) to the specific one based on the type and kind of the
3332    argument(s).  Currently, this function resolves c_f_pointer() and
3333    c_f_procpointer based on the type and kind of the second argument
3334    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3335    Upon successfully exiting, c->resolved_sym will hold the resolved
3336    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3337    otherwise.  */
3338
3339 match
3340 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3341 {
3342   gfc_symbol *new_sym;
3343   /* this is fine, since we know the names won't use the max */
3344   char name[GFC_MAX_SYMBOL_LEN + 1];
3345   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3346   /* default to success; will override if find error */
3347   match m = MATCH_YES;
3348
3349   /* Make sure the actual arguments are in the necessary order (based on the 
3350      formal args) before resolving.  */
3351   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3352
3353   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3354       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3355     {
3356       set_name_and_label (c, sym, name, binding_label);
3357       
3358       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3359         {
3360           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3361             {
3362               /* Make sure we got a third arg if the second arg has non-zero
3363                  rank.  We must also check that the type and rank are
3364                  correct since we short-circuit this check in
3365                  gfc_procedure_use() (called above to sort actual args).  */
3366               if (c->ext.actual->next->expr->rank != 0)
3367                 {
3368                   if(c->ext.actual->next->next == NULL 
3369                      || c->ext.actual->next->next->expr == NULL)
3370                     {
3371                       m = MATCH_ERROR;
3372                       gfc_error ("Missing SHAPE parameter for call to %s "
3373                                  "at %L", sym->name, &(c->loc));
3374                     }
3375                   else if (c->ext.actual->next->next->expr->ts.type
3376                            != BT_INTEGER
3377                            || c->ext.actual->next->next->expr->rank != 1)
3378                     {
3379                       m = MATCH_ERROR;
3380                       gfc_error ("SHAPE parameter for call to %s at %L must "
3381                                  "be a rank 1 INTEGER array", sym->name,
3382                                  &(c->loc));
3383                     }
3384                 }
3385             }
3386         }
3387       
3388       if (m != MATCH_ERROR)
3389         {
3390           /* the 1 means to add the optional arg to formal list */
3391           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3392          
3393           /* for error reporting, say it's declared where the original was */
3394           new_sym->declared_at = sym->declared_at;
3395         }
3396     }
3397   else
3398     {
3399       /* no differences for c_loc or c_funloc */
3400       new_sym = sym;
3401     }
3402
3403   /* set the resolved symbol */
3404   if (m != MATCH_ERROR)
3405     c->resolved_sym = new_sym;
3406   else
3407     c->resolved_sym = sym;
3408   
3409   return m;
3410 }
3411
3412
3413 /* Resolve a subroutine call known to be specific.  */
3414
3415 static match
3416 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3417 {
3418   match m;
3419
3420   if(sym->attr.is_iso_c)
3421     {
3422       m = gfc_iso_c_sub_interface (c,sym);
3423       return m;
3424     }
3425   
3426   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3427     {
3428       if (sym->attr.dummy)
3429         {
3430           sym->attr.proc = PROC_DUMMY;
3431           goto found;
3432         }
3433
3434       sym->attr.proc = PROC_EXTERNAL;
3435       goto found;
3436     }
3437
3438   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3439     goto found;
3440
3441   if (sym->attr.intrinsic)
3442     {
3443       m = gfc_intrinsic_sub_interface (c, 1);
3444       if (m == MATCH_YES)
3445         return MATCH_YES;
3446       if (m == MATCH_NO)
3447         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3448                    "with an intrinsic", sym->name, &c->loc);
3449
3450       return MATCH_ERROR;
3451     }
3452
3453   return MATCH_NO;
3454
3455 found:
3456   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3457
3458   c->resolved_sym = sym;
3459   pure_subroutine (c, sym);
3460
3461   return MATCH_YES;
3462 }
3463
3464
3465 static gfc_try
3466 resolve_specific_s (gfc_code *c)
3467 {
3468   gfc_symbol *sym;
3469   match m;
3470
3471   sym = c->symtree->n.sym;
3472
3473   for (;;)
3474     {
3475       m = resolve_specific_s0 (c, sym);
3476       if (m == MATCH_YES)
3477         return SUCCESS;
3478       if (m == MATCH_ERROR)
3479         return FAILURE;
3480
3481       if (sym->ns->parent == NULL)
3482         break;
3483
3484       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3485
3486       if (sym == NULL)
3487         break;
3488     }
3489
3490   sym = c->symtree->n.sym;
3491   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3492              sym->name, &c->loc);
3493
3494   return FAILURE;
3495 }
3496
3497
3498 /* Resolve a subroutine call not known to be generic nor specific.  */
3499
3500 static gfc_try
3501 resolve_unknown_s (gfc_code *c)
3502 {
3503   gfc_symbol *sym;
3504
3505   sym = c->symtree->n.sym;
3506
3507   if (sym->attr.dummy)
3508     {
3509       sym->attr.proc = PROC_DUMMY;
3510       goto found;
3511     }
3512
3513   /* See if we have an intrinsic function reference.  */
3514
3515   if (gfc_is_intrinsic (sym, 1, c->loc))
3516     {
3517       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3518         return SUCCESS;
3519       return FAILURE;
3520     }
3521
3522   /* The reference is to an external name.  */
3523
3524 found:
3525   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3526
3527   c->resolved_sym = sym;
3528
3529   pure_subroutine (c, sym);
3530
3531   return SUCCESS;
3532 }
3533
3534
3535 /* Resolve a subroutine call.  Although it was tempting to use the same code
3536    for functions, subroutines and functions are stored differently and this
3537    makes things awkward.  */
3538
3539 static gfc_try
3540 resolve_call (gfc_code *c)
3541 {
3542   gfc_try t;
3543   procedure_type ptype = PROC_INTRINSIC;
3544   gfc_symbol *csym, *sym;
3545   bool no_formal_args;
3546
3547   csym = c->symtree ? c->symtree->n.sym : NULL;
3548
3549   if (csym && csym->ts.type != BT_UNKNOWN)
3550     {
3551       gfc_error ("'%s' at %L has a type, which is not consistent with "
3552                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3553       return FAILURE;
3554     }
3555
3556   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3557     {
3558       gfc_symtree *st;
3559       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3560       sym = st ? st->n.sym : NULL;
3561       if (sym && csym != sym
3562               && sym->ns == gfc_current_ns
3563               && sym->attr.flavor == FL_PROCEDURE
3564               && sym->attr.contained)
3565         {
3566           sym->refs++;
3567           if (csym->attr.generic)
3568             c->symtree->n.sym = sym;
3569           else
3570             c->symtree = st;
3571           csym = c->symtree->n.sym;
3572         }
3573     }
3574
3575   /* If this ia a deferred TBP with an abstract interface
3576      (which may of course be referenced), c->expr1 will be set.  */
3577   if (csym && csym->attr.abstract && !c->expr1)
3578     {
3579       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3580                  csym->name, &c->loc);
3581       return FAILURE;
3582     }
3583
3584   /* Subroutines without the RECURSIVE attribution are not allowed to
3585    * call themselves.  */
3586   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3587     {
3588       if (csym->attr.entry && csym->ns->entries)
3589         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3590                    " subroutine '%s' is not RECURSIVE",
3591                    csym->name, &c->loc, csym->ns->entries->sym->name);
3592       else
3593         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3594                    " is not RECURSIVE", csym->name, &c->loc);
3595
3596       t = FAILURE;
3597     }
3598
3599   /* Switch off assumed size checking and do this again for certain kinds
3600      of procedure, once the procedure itself is resolved.  */
3601   need_full_assumed_size++;
3602
3603   if (csym)
3604     ptype = csym->attr.proc;
3605
3606   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3607   if (resolve_actual_arglist (c->ext.actual, ptype,
3608                               no_formal_args) == FAILURE)
3609     return FAILURE;
3610
3611   /* Resume assumed_size checking.  */
3612   need_full_assumed_size--;
3613
3614   /* If external, check for usage.  */
3615   if (csym && is_external_proc (csym))
3616     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3617
3618   t = SUCCESS;
3619   if (c->resolved_sym == NULL)
3620     {
3621       c->resolved_isym = NULL;
3622       switch (procedure_kind (csym))
3623         {
3624         case PTYPE_GENERIC:
3625           t = resolve_generic_s (c);
3626           break;
3627
3628         case PTYPE_SPECIFIC:
3629           t = resolve_specific_s (c);
3630           break;
3631
3632         case PTYPE_UNKNOWN:
3633           t = resolve_unknown_s (c);
3634           break;
3635
3636         default:
3637           gfc_internal_error ("resolve_subroutine(): bad function type");
3638         }
3639     }
3640
3641   /* Some checks of elemental subroutine actual arguments.  */
3642   if (resolve_elemental_actual (NULL, c) == FAILURE)
3643     return FAILURE;
3644
3645   return t;
3646 }
3647
3648
3649 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3650    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3651    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3652    if their shapes do not match.  If either op1->shape or op2->shape is
3653    NULL, return SUCCESS.  */
3654
3655 static gfc_try
3656 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3657 {
3658   gfc_try t;
3659   int i;
3660
3661   t = SUCCESS;
3662
3663   if (op1->shape != NULL && op2->shape != NULL)
3664     {
3665       for (i = 0; i < op1->rank; i++)
3666         {
3667           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3668            {
3669              gfc_error ("Shapes for operands at %L and %L are not conformable",
3670                          &op1->where, &op2->where);
3671              t = FAILURE;
3672              break;
3673            }
3674         }
3675     }
3676
3677   return t;
3678 }
3679
3680
3681 /* Resolve an operator expression node.  This can involve replacing the
3682    operation with a user defined function call.  */
3683
3684 static gfc_try
3685 resolve_operator (gfc_expr *e)
3686 {
3687   gfc_expr *op1, *op2;
3688   char msg[200];
3689   bool dual_locus_error;
3690   gfc_try t;
3691
3692   /* Resolve all subnodes-- give them types.  */
3693
3694   switch (e->value.op.op)
3695     {
3696     default:
3697       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3698         return FAILURE;
3699
3700     /* Fall through...  */
3701
3702     case INTRINSIC_NOT:
3703     case INTRINSIC_UPLUS:
3704     case INTRINSIC_UMINUS:
3705     case INTRINSIC_PARENTHESES:
3706       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3707         return FAILURE;
3708       break;
3709     }
3710
3711   /* Typecheck the new node.  */
3712
3713   op1 = e->value.op.op1;
3714   op2 = e->value.op.op2;
3715   dual_locus_error = false;
3716
3717   if ((op1 && op1->expr_type == EXPR_NULL)
3718       || (op2 && op2->expr_type == EXPR_NULL))
3719     {
3720       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3721       goto bad_op;
3722     }
3723
3724   switch (e->value.op.op)
3725     {
3726     case INTRINSIC_UPLUS:
3727     case INTRINSIC_UMINUS:
3728       if (op1->ts.type == BT_INTEGER
3729           || op1->ts.type == BT_REAL
3730           || op1->ts.type == BT_COMPLEX)
3731         {
3732           e->ts = op1->ts;
3733           break;
3734         }
3735
3736       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3737                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3738       goto bad_op;
3739
3740     case INTRINSIC_PLUS:
3741     case INTRINSIC_MINUS:
3742     case INTRINSIC_TIMES:
3743     case INTRINSIC_DIVIDE:
3744     case INTRINSIC_POWER:
3745       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3746         {
3747           gfc_type_convert_binary (e, 1);
3748           break;
3749         }
3750
3751       sprintf (msg,
3752                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3753                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3754                gfc_typename (&op2->ts));
3755       goto bad_op;
3756
3757     case INTRINSIC_CONCAT:
3758       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3759           && op1->ts.kind == op2->ts.kind)
3760         {
3761           e->ts.type = BT_CHARACTER;
3762           e->ts.kind = op1->ts.kind;
3763           break;
3764         }
3765
3766       sprintf (msg,
3767                _("Operands of string concatenation operator at %%L are %s/%s"),
3768                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3769       goto bad_op;
3770
3771     case INTRINSIC_AND:
3772     case INTRINSIC_OR:
3773     case INTRINSIC_EQV:
3774     case INTRINSIC_NEQV:
3775       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3776         {
3777           e->ts.type = BT_LOGICAL;
3778           e->ts.kind = gfc_kind_max (op1, op2);
3779           if (op1->ts.kind < e->ts.kind)
3780             gfc_convert_type (op1, &e->ts, 2);
3781           else if (op2->ts.kind < e->ts.kind)
3782             gfc_convert_type (op2, &e->ts, 2);
3783           break;
3784         }
3785
3786       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3787                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3788                gfc_typename (&op2->ts));
3789
3790       goto bad_op;
3791
3792     case INTRINSIC_NOT:
3793       if (op1->ts.type == BT_LOGICAL)
3794         {
3795           e->ts.type = BT_LOGICAL;
3796           e->ts.kind = op1->ts.kind;
3797           break;
3798         }
3799
3800       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3801                gfc_typename (&op1->ts));
3802       goto bad_op;
3803
3804     case INTRINSIC_GT:
3805     case INTRINSIC_GT_OS:
3806     case INTRINSIC_GE:
3807     case INTRINSIC_GE_OS:
3808     case INTRINSIC_LT:
3809     case INTRINSIC_LT_OS:
3810     case INTRINSIC_LE:
3811     case INTRINSIC_LE_OS:
3812       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3813         {
3814           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3815           goto bad_op;
3816         }
3817
3818       /* Fall through...  */
3819
3820     case INTRINSIC_EQ:
3821     case INTRINSIC_EQ_OS:
3822     case INTRINSIC_NE:
3823     case INTRINSIC_NE_OS:
3824       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3825           && op1->ts.kind == op2->ts.kind)
3826         {
3827           e->ts.type = BT_LOGICAL;
3828           e->ts.kind = gfc_default_logical_kind;
3829           break;
3830         }
3831
3832       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3833         {
3834           gfc_type_convert_binary (e, 1);
3835
3836           e->ts.type = BT_LOGICAL;
3837           e->ts.kind = gfc_default_logical_kind;
3838           break;
3839         }
3840
3841       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3842         sprintf (msg,
3843                  _("Logicals at %%L must be compared with %s instead of %s"),
3844                  (e->value.op.op == INTRINSIC_EQ 
3845                   || e->value.op.op == INTRINSIC_EQ_OS)
3846                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3847       else
3848         sprintf (msg,
3849                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3850                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3851                  gfc_typename (&op2->ts));
3852
3853       goto bad_op;
3854
3855     case INTRINSIC_USER:
3856       if (e->value.op.uop->op == NULL)
3857         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3858       else if (op2 == NULL)
3859         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3860                  e->value.op.uop->name, gfc_typename (&op1->ts));
3861       else
3862         {
3863           sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3864                    e->value.op.uop->name, gfc_typename (&op1->ts),
3865                    gfc_typename (&op2->ts));
3866           e->value.op.uop->op->sym->attr.referenced = 1;
3867         }
3868
3869       goto bad_op;
3870
3871     case INTRINSIC_PARENTHESES:
3872       e->ts = op1->ts;
3873       if (e->ts.type == BT_CHARACTER)
3874         e->ts.u.cl = op1->ts.u.cl;
3875       break;
3876
3877     default:
3878       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3879     }
3880
3881   /* Deal with arrayness of an operand through an operator.  */
3882
3883   t = SUCCESS;
3884
3885   switch (e->value.op.op)
3886     {
3887     case INTRINSIC_PLUS:
3888     case INTRINSIC_MINUS:
3889     case INTRINSIC_TIMES:
3890     case INTRINSIC_DIVIDE:
3891     case INTRINSIC_POWER:
3892     case INTRINSIC_CONCAT:
3893     case INTRINSIC_AND:
3894     case INTRINSIC_OR:
3895     case INTRINSIC_EQV:
3896     case INTRINSIC_NEQV:
3897     case INTRINSIC_EQ:
3898     case INTRINSIC_EQ_OS:
3899     case INTRINSIC_NE:
3900     case INTRINSIC_NE_OS:
3901     case INTRINSIC_GT:
3902     case INTRINSIC_GT_OS:
3903     case INTRINSIC_GE:
3904     case INTRINSIC_GE_OS:
3905     case INTRINSIC_LT:
3906     case INTRINSIC_LT_OS:
3907     case INTRINSIC_LE:
3908     case INTRINSIC_LE_OS:
3909
3910       if (op1->rank == 0 && op2->rank == 0)
3911         e->rank = 0;
3912
3913       if (op1->rank == 0 && op2->rank != 0)
3914         {
3915           e->rank = op2->rank;
3916
3917           if (e->shape == NULL)
3918             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3919         }
3920
3921       if (op1->rank != 0 && op2->rank == 0)
3922         {
3923           e->rank = op1->rank;
3924
3925           if (e->shape == NULL)
3926             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3927         }
3928
3929       if (op1->rank != 0 && op2->rank != 0)
3930         {
3931           if (op1->rank == op2->rank)
3932             {
3933               e->rank = op1->rank;
3934               if (e->shape == NULL)
3935                 {
3936                   t = compare_shapes (op1, op2);
3937                   if (t == FAILURE)
3938                     e->shape = NULL;
3939                   else
3940                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
3941                 }
3942             }
3943           else
3944             {
3945               /* Allow higher level expressions to work.  */
3946               e->rank = 0;
3947
3948               /* Try user-defined operators, and otherwise throw an error.  */
3949               dual_locus_error = true;
3950               sprintf (msg,
3951                        _("Inconsistent ranks for operator at %%L and %%L"));
3952               goto bad_op;
3953             }
3954         }
3955
3956       break;
3957
3958     case INTRINSIC_PARENTHESES:
3959     case INTRINSIC_NOT:
3960     case INTRINSIC_UPLUS:
3961     case INTRINSIC_UMINUS:
3962       /* Simply copy arrayness attribute */
3963       e->rank = op1->rank;
3964
3965       if (e->shape == NULL)
3966         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3967
3968       break;
3969
3970     default:
3971       break;
3972     }
3973
3974   /* Attempt to simplify the expression.  */
3975   if (t == SUCCESS)
3976     {
3977       t = gfc_simplify_expr (e, 0);
3978       /* Some calls do not succeed in simplification and return FAILURE
3979          even though there is no error; e.g. variable references to
3980          PARAMETER arrays.  */
3981       if (!gfc_is_constant_expr (e))
3982         t = SUCCESS;
3983     }
3984   return t;
3985
3986 bad_op:
3987
3988   {
3989     bool real_error;
3990     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3991       return SUCCESS;
3992
3993     if (real_error)
3994       return FAILURE;
3995   }
3996
3997   if (dual_locus_error)
3998     gfc_error (msg, &op1->where, &op2->where);
3999   else
4000     gfc_error (msg, &e->where);
4001
4002   return FAILURE;
4003 }
4004
4005
4006 /************** Array resolution subroutines **************/
4007
4008 typedef enum
4009 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
4010 comparison;
4011
4012 /* Compare two integer expressions.  */
4013
4014 static comparison
4015 compare_bound (gfc_expr *a, gfc_expr *b)
4016 {
4017   int i;
4018
4019   if (a == NULL || a->expr_type != EXPR_CONSTANT
4020       || b == NULL || b->expr_type != EXPR_CONSTANT)
4021     return CMP_UNKNOWN;
4022
4023   /* If either of the types isn't INTEGER, we must have
4024      raised an error earlier.  */
4025
4026   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
4027     return CMP_UNKNOWN;
4028
4029   i = mpz_cmp (a->value.integer, b->value.integer);
4030
4031   if (i < 0)
4032     return CMP_LT;
4033   if (i > 0)
4034     return CMP_GT;
4035   return CMP_EQ;
4036 }
4037
4038
4039 /* Compare an integer expression with an integer.  */
4040
4041 static comparison
4042 compare_bound_int (gfc_expr *a, int b)
4043 {
4044   int i;
4045
4046   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4047     return CMP_UNKNOWN;
4048
4049   if (a->ts.type != BT_INTEGER)
4050     gfc_internal_error ("compare_bound_int(): Bad expression");
4051
4052   i = mpz_cmp_si (a->value.integer, b);
4053
4054   if (i < 0)
4055     return CMP_LT;
4056   if (i > 0)
4057     return CMP_GT;
4058   return CMP_EQ;
4059 }
4060
4061
4062 /* Compare an integer expression with a mpz_t.  */
4063
4064 static comparison
4065 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
4066 {
4067   int i;
4068
4069   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4070     return CMP_UNKNOWN;
4071
4072   if (a->ts.type != BT_INTEGER)
4073     gfc_internal_error ("compare_bound_int(): Bad expression");
4074
4075   i = mpz_cmp (a->value.integer, b);
4076
4077   if (i < 0)
4078     return CMP_LT;
4079   if (i > 0)
4080     return CMP_GT;
4081   return CMP_EQ;
4082 }
4083
4084
4085 /* Compute the last value of a sequence given by a triplet.  
4086    Return 0 if it wasn't able to compute the last value, or if the
4087    sequence if empty, and 1 otherwise.  */
4088
4089 static int
4090 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
4091                                 gfc_expr *stride, mpz_t last)
4092 {
4093   mpz_t rem;
4094
4095   if (start == NULL || start->expr_type != EXPR_CONSTANT
4096       || end == NULL || end->expr_type != EXPR_CONSTANT
4097       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
4098     return 0;
4099
4100   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
4101       || (stride != NULL && stride->ts.type != BT_INTEGER))
4102     return 0;
4103
4104   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
4105     {
4106       if (compare_bound (start, end) == CMP_GT)
4107         return 0;
4108       mpz_set (last, end->value.integer);
4109       return 1;
4110     }
4111
4112   if (compare_bound_int (stride, 0) == CMP_GT)
4113     {
4114       /* Stride is positive */
4115       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
4116         return 0;
4117     }
4118   else
4119     {
4120       /* Stride is negative */
4121       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
4122         return 0;
4123     }
4124
4125   mpz_init (rem);
4126   mpz_sub (rem, end->value.integer, start->value.integer);
4127   mpz_tdiv_r (rem, rem, stride->value.integer);
4128   mpz_sub (last, end->value.integer, rem);
4129   mpz_clear (rem);
4130
4131   return 1;
4132 }
4133
4134
4135 /* Compare a single dimension of an array reference to the array
4136    specification.  */
4137
4138 static gfc_try
4139 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
4140 {
4141   mpz_t last_value;
4142
4143   if (ar->dimen_type[i] == DIMEN_STAR)
4144     {
4145       gcc_assert (ar->stride[i] == NULL);
4146       /* This implies [*] as [*:] and [*:3] are not possible.  */
4147       if (ar->start[i] == NULL)
4148         {
4149           gcc_assert (ar->end[i] == NULL);
4150           return SUCCESS;
4151         }
4152     }
4153
4154 /* Given start, end and stride values, calculate the minimum and
4155    maximum referenced indexes.  */
4156
4157   switch (ar->dimen_type[i])
4158     {
4159     case DIMEN_VECTOR:
4160     case DIMEN_THIS_IMAGE:
4161       break;
4162
4163     case DIMEN_STAR:
4164     case DIMEN_ELEMENT:
4165       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4166         {
4167           if (i < as->rank)
4168             gfc_warning ("Array reference at %L is out of bounds "
4169                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
4170                          mpz_get_si (ar->start[i]->value.integer),
4171                          mpz_get_si (as->lower[i]->value.integer), i+1);
4172           else
4173             gfc_warning ("Array reference at %L is out of bounds "
4174                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
4175                          mpz_get_si (ar->start[i]->value.integer),
4176                          mpz_get_si (as->lower[i]->value.integer),
4177                          i + 1 - as->rank);
4178           return SUCCESS;
4179         }
4180       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4181         {
4182           if (i < as->rank)
4183             gfc_warning ("Array reference at %L is out of bounds "
4184                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
4185                          mpz_get_si (ar->start[i]->value.integer),
4186                          mpz_get_si (as->upper[i]->value.integer), i+1);
4187           else
4188             gfc_warning ("Array reference at %L is out of bounds "
4189                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
4190                          mpz_get_si (ar->start[i]->value.integer),
4191                          mpz_get_si (as->upper[i]->value.integer),
4192                          i + 1 - as->rank);
4193           return SUCCESS;
4194         }
4195
4196       break;
4197
4198     case DIMEN_RANGE:
4199       {
4200 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4201 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4202
4203         comparison comp_start_end = compare_bound (AR_START, AR_END);
4204
4205         /* Check for zero stride, which is not allowed.  */
4206         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4207           {
4208             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4209             return FAILURE;
4210           }
4211
4212         /* if start == len || (stride > 0 && start < len)
4213                            || (stride < 0 && start > len),
4214            then the array section contains at least one element.  In this
4215            case, there is an out-of-bounds access if
4216            (start < lower || start > upper).  */
4217         if (compare_bound (AR_START, AR_END) == CMP_EQ
4218             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4219                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4220             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4221                 && comp_start_end == CMP_GT))
4222           {
4223             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4224               {
4225                 gfc_warning ("Lower array reference at %L is out of bounds "
4226                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4227                        mpz_get_si (AR_START->value.integer),
4228                        mpz_get_si (as->lower[i]->value.integer), i+1);
4229                 return SUCCESS;
4230               }
4231             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4232               {
4233                 gfc_warning ("Lower array reference at %L is out of bounds "
4234                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4235                        mpz_get_si (AR_START->value.integer),
4236                        mpz_get_si (as->upper[i]->value.integer), i+1);
4237                 return SUCCESS;
4238               }
4239           }
4240
4241         /* If we can compute the highest index of the array section,
4242            then it also has to be between lower and upper.  */
4243         mpz_init (last_value);
4244         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4245                                             last_value))
4246           {
4247             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4248               {
4249                 gfc_warning ("Upper array reference at %L is out of bounds "
4250                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4251                        mpz_get_si (last_value),
4252                        mpz_get_si (as->lower[i]->value.integer), i+1);
4253                 mpz_clear (last_value);
4254                 return SUCCESS;
4255               }
4256             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4257               {
4258                 gfc_warning ("Upper array reference at %L is out of bounds "
4259                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4260                        mpz_get_si (last_value),
4261                        mpz_get_si (as->upper[i]->value.integer), i+1);
4262                 mpz_clear (last_value);
4263                 return SUCCESS;
4264               }
4265           }
4266         mpz_clear (last_value);
4267
4268 #undef AR_START
4269 #undef AR_END
4270       }
4271       break;
4272
4273     default:
4274       gfc_internal_error ("check_dimension(): Bad array reference");
4275     }
4276
4277   return SUCCESS;
4278 }
4279
4280
4281 /* Compare an array reference with an array specification.  */
4282
4283 static gfc_try
4284 compare_spec_to_ref (gfc_array_ref *ar)
4285 {
4286   gfc_array_spec *as;
4287   int i;
4288
4289   as = ar->as;
4290   i = as->rank - 1;
4291   /* TODO: Full array sections are only allowed as actual parameters.  */
4292   if (as->type == AS_ASSUMED_SIZE
4293       && (/*ar->type == AR_FULL
4294           ||*/ (ar->type == AR_SECTION
4295               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4296     {
4297       gfc_error ("Rightmost upper bound of assumed size array section "
4298                  "not specified at %L", &ar->where);
4299       return FAILURE;
4300     }
4301
4302   if (ar->type == AR_FULL)
4303     return SUCCESS;
4304
4305   if (as->rank != ar->dimen)
4306     {
4307       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4308                  &ar->where, ar->dimen, as->rank);
4309       return FAILURE;
4310     }
4311
4312   /* ar->codimen == 0 is a local array.  */
4313   if (as->corank != ar->codimen && ar->codimen != 0)
4314     {
4315       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4316                  &ar->where, ar->codimen, as->corank);
4317       return FAILURE;
4318     }
4319
4320   for (i = 0; i < as->rank; i++)
4321     if (check_dimension (i, ar, as) == FAILURE)
4322       return FAILURE;
4323
4324   /* Local access has no coarray spec.  */
4325   if (ar->codimen != 0)
4326     for (i = as->rank; i < as->rank + as->corank; i++)
4327       {
4328         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate
4329             && ar->dimen_type[i] != DIMEN_THIS_IMAGE)
4330           {
4331             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4332                        i + 1 - as->rank, &ar->where);
4333             return FAILURE;
4334           }
4335         if (check_dimension (i, ar, as) == FAILURE)
4336           return FAILURE;
4337       }
4338
4339   if (as->corank && ar->codimen == 0)
4340     {
4341       int n;
4342       ar->codimen = as->corank;
4343       for (n = ar->dimen; n < ar->dimen + ar->codimen; n++)
4344         ar->dimen_type[n] = DIMEN_THIS_IMAGE;
4345     }
4346
4347   return SUCCESS;
4348 }
4349
4350
4351 /* Resolve one part of an array index.  */
4352
4353 static gfc_try
4354 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4355                      int force_index_integer_kind)
4356 {
4357   gfc_typespec ts;
4358
4359   if (index == NULL)
4360     return SUCCESS;
4361
4362   if (gfc_resolve_expr (index) == FAILURE)
4363     return FAILURE;
4364
4365   if (check_scalar && index->rank != 0)
4366     {
4367       gfc_error ("Array index at %L must be scalar", &index->where);
4368       return FAILURE;
4369     }
4370
4371   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4372     {
4373       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4374                  &index->where, gfc_basic_typename (index->ts.type));
4375       return FAILURE;
4376     }
4377
4378   if (index->ts.type == BT_REAL)
4379     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4380                         &index->where) == FAILURE)
4381       return FAILURE;
4382
4383   if ((index->ts.kind != gfc_index_integer_kind
4384        && force_index_integer_kind)
4385       || index->ts.type != BT_INTEGER)
4386     {
4387       gfc_clear_ts (&ts);
4388       ts.type = BT_INTEGER;
4389       ts.kind = gfc_index_integer_kind;
4390
4391       gfc_convert_type_warn (index, &ts, 2, 0);
4392     }
4393
4394   return SUCCESS;
4395 }
4396
4397 /* Resolve one part of an array index.  */
4398
4399 gfc_try
4400 gfc_resolve_index (gfc_expr *index, int check_scalar)
4401 {
4402   return gfc_resolve_index_1 (index, check_scalar, 1);
4403 }
4404
4405 /* Resolve a dim argument to an intrinsic function.  */
4406
4407 gfc_try
4408 gfc_resolve_dim_arg (gfc_expr *dim)
4409 {
4410   if (dim == NULL)
4411     return SUCCESS;
4412
4413   if (gfc_resolve_expr (dim) == FAILURE)
4414     return FAILURE;
4415
4416   if (dim->rank != 0)
4417     {
4418       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4419       return FAILURE;
4420
4421     }
4422
4423   if (dim->ts.type != BT_INTEGER)
4424     {
4425       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4426       return FAILURE;
4427     }
4428
4429   if (dim->ts.kind != gfc_index_integer_kind)
4430     {
4431       gfc_typespec ts;
4432
4433       gfc_clear_ts (&ts);
4434       ts.type = BT_INTEGER;
4435       ts.kind = gfc_index_integer_kind;
4436
4437       gfc_convert_type_warn (dim, &ts, 2, 0);
4438     }
4439
4440   return SUCCESS;
4441 }
4442
4443 /* Given an expression that contains array references, update those array
4444    references to point to the right array specifications.  While this is
4445    filled in during matching, this information is difficult to save and load
4446    in a module, so we take care of it here.
4447
4448    The idea here is that the original array reference comes from the
4449    base symbol.  We traverse the list of reference structures, setting
4450    the stored reference to references.  Component references can
4451    provide an additional array specification.  */
4452
4453 static void
4454 find_array_spec (gfc_expr *e)
4455 {
4456   gfc_array_spec *as;
4457   gfc_component *c;
4458   gfc_symbol *derived;
4459   gfc_ref *ref;
4460
4461   if (e->symtree->n.sym->ts.type == BT_CLASS)
4462     as = CLASS_DATA (e->symtree->n.sym)->as;
4463   else
4464     as = e->symtree->n.sym->as;
4465   derived = NULL;
4466
4467   for (ref = e->ref; ref; ref = ref->next)
4468     switch (ref->type)
4469       {
4470       case REF_ARRAY:
4471         if (as == NULL)
4472           gfc_internal_error ("find_array_spec(): Missing spec");
4473
4474         ref->u.ar.as = as;
4475         as = NULL;
4476         break;
4477
4478       case REF_COMPONENT:
4479         if (derived == NULL)
4480           derived = e->symtree->n.sym->ts.u.derived;
4481
4482         if (derived->attr.is_class)
4483           derived = derived->components->ts.u.derived;
4484
4485         c = derived->components;
4486
4487         for (; c; c = c->next)
4488           if (c == ref->u.c.component)
4489             {
4490               /* Track the sequence of component references.  */
4491               if (c->ts.type == BT_DERIVED)
4492                 derived = c->ts.u.derived;
4493               break;
4494             }
4495
4496         if (c == NULL)
4497           gfc_internal_error ("find_array_spec(): Component not found");
4498
4499         if (c->attr.dimension)
4500           {
4501             if (as != NULL)
4502               gfc_internal_error ("find_array_spec(): unused as(1)");
4503             as = c->as;
4504           }
4505
4506         break;
4507
4508       case REF_SUBSTRING:
4509         break;
4510       }
4511
4512   if (as != NULL)
4513     gfc_internal_error ("find_array_spec(): unused as(2)");
4514 }
4515
4516
4517 /* Resolve an array reference.  */
4518
4519 static gfc_try
4520 resolve_array_ref (gfc_array_ref *ar)
4521 {
4522   int i, check_scalar;
4523   gfc_expr *e;
4524
4525   for (i = 0; i < ar->dimen + ar->codimen; i++)
4526     {
4527       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4528
4529       /* Do not force gfc_index_integer_kind for the start.  We can
4530          do fine with any integer kind.  This avoids temporary arrays
4531          created for indexing with a vector.  */
4532       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4533         return FAILURE;
4534       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4535         return FAILURE;
4536       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4537         return FAILURE;
4538
4539       e = ar->start[i];
4540
4541       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4542         switch (e->rank)
4543           {
4544           case 0:
4545             ar->dimen_type[i] = DIMEN_ELEMENT;
4546             break;
4547
4548           case 1:
4549             ar->dimen_type[i] = DIMEN_VECTOR;
4550             if (e->expr_type == EXPR_VARIABLE
4551                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4552               ar->start[i] = gfc_get_parentheses (e);
4553             break;
4554
4555           default:
4556             gfc_error ("Array index at %L is an array of rank %d",
4557                        &ar->c_where[i], e->rank);
4558             return FAILURE;
4559           }
4560
4561       /* Fill in the upper bound, which may be lower than the
4562          specified one for something like a(2:10:5), which is
4563          identical to a(2:7:5).  Only relevant for strides not equal
4564          to one.  */
4565       if (ar->dimen_type[i] == DIMEN_RANGE
4566           && ar->stride[i] != NULL && ar->stride[i]->expr_type == EXPR_CONSTANT
4567           && mpz_cmp_si (ar->stride[i]->value.integer, 1L) != 0)
4568         {
4569           mpz_t size, end;
4570
4571           if (gfc_ref_dimen_size (ar, i, &size, &end) == SUCCESS)
4572             {
4573               if (ar->end[i] == NULL)
4574                 {
4575                   ar->end[i] =
4576                     gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
4577                                            &ar->where);
4578                   mpz_set (ar->end[i]->value.integer, end);
4579                 }
4580               else if (ar->end[i]->ts.type == BT_INTEGER
4581                        && ar->end[i]->expr_type == EXPR_CONSTANT)
4582                 {
4583                   mpz_set (ar->end[i]->value.integer, end);
4584                 }
4585               else
4586                 gcc_unreachable ();
4587
4588               mpz_clear (size);
4589               mpz_clear (end);
4590             }
4591         }
4592     }
4593
4594   if (ar->type == AR_FULL && ar->as->rank == 0)
4595     ar->type = AR_ELEMENT;
4596
4597   /* If the reference type is unknown, figure out what kind it is.  */
4598
4599   if (ar->type == AR_UNKNOWN)
4600     {
4601       ar->type = AR_ELEMENT;
4602       for (i = 0; i < ar->dimen; i++)
4603         if (ar->dimen_type[i] == DIMEN_RANGE
4604             || ar->dimen_type[i] == DIMEN_VECTOR)
4605           {
4606             ar->type = AR_SECTION;
4607             break;
4608           }
4609     }
4610
4611   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4612     return FAILURE;
4613
4614   return SUCCESS;
4615 }
4616
4617
4618 static gfc_try
4619 resolve_substring (gfc_ref *ref)
4620 {
4621   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4622
4623   if (ref->u.ss.start != NULL)
4624     {
4625       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4626         return FAILURE;
4627
4628       if (ref->u.ss.start->ts.type != BT_INTEGER)
4629         {
4630           gfc_error ("Substring start index at %L must be of type INTEGER",
4631                      &ref->u.ss.start->where);
4632           return FAILURE;
4633         }
4634
4635       if (ref->u.ss.start->rank != 0)
4636         {
4637           gfc_error ("Substring start index at %L must be scalar",
4638                      &ref->u.ss.start->where);
4639           return FAILURE;
4640         }
4641
4642       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4643           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4644               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4645         {
4646           gfc_error ("Substring start index at %L is less than one",
4647                      &ref->u.ss.start->where);
4648           return FAILURE;
4649         }
4650     }
4651
4652   if (ref->u.ss.end != NULL)
4653     {
4654       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4655         return FAILURE;
4656
4657       if (ref->u.ss.end->ts.type != BT_INTEGER)
4658         {
4659           gfc_error ("Substring end index at %L must be of type INTEGER",
4660                      &ref->u.ss.end->where);
4661           return FAILURE;
4662         }
4663
4664       if (ref->u.ss.end->rank != 0)
4665         {
4666           gfc_error ("Substring end index at %L must be scalar",
4667                      &ref->u.ss.end->where);
4668           return FAILURE;
4669         }
4670
4671       if (ref->u.ss.length != NULL
4672           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4673           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4674               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4675         {
4676           gfc_error ("Substring end index at %L exceeds the string length",
4677                      &ref->u.ss.start->where);
4678           return FAILURE;
4679         }
4680
4681       if (compare_bound_mpz_t (ref->u.ss.end,
4682                                gfc_integer_kinds[k].huge) == CMP_GT
4683           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4684               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4685         {
4686           gfc_error ("Substring end index at %L is too large",
4687                      &ref->u.ss.end->where);
4688           return FAILURE;
4689         }
4690     }
4691
4692   return SUCCESS;
4693 }
4694
4695
4696 /* This function supplies missing substring charlens.  */
4697
4698 void
4699 gfc_resolve_substring_charlen (gfc_expr *e)
4700 {
4701   gfc_ref *char_ref;
4702   gfc_expr *start, *end;
4703
4704   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4705     if (char_ref->type == REF_SUBSTRING)
4706       break;
4707
4708   if (!char_ref)
4709     return;
4710
4711   gcc_assert (char_ref->next == NULL);
4712
4713   if (e->ts.u.cl)
4714     {
4715       if (e->ts.u.cl->length)
4716         gfc_free_expr (e->ts.u.cl->length);
4717       else if (e->expr_type == EXPR_VARIABLE
4718                  && e->symtree->n.sym->attr.dummy)
4719         return;
4720     }
4721
4722   e->ts.type = BT_CHARACTER;
4723   e->ts.kind = gfc_default_character_kind;
4724
4725   if (!e->ts.u.cl)
4726     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4727
4728   if (char_ref->u.ss.start)
4729     start = gfc_copy_expr (char_ref->u.ss.start);
4730   else
4731     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4732
4733   if (char_ref->u.ss.end)
4734     end = gfc_copy_expr (char_ref->u.ss.end);
4735   else if (e->expr_type == EXPR_VARIABLE)
4736     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4737   else
4738     end = NULL;
4739
4740   if (!start || !end)
4741     return;
4742
4743   /* Length = (end - start +1).  */
4744   e->ts.u.cl->length = gfc_subtract (end, start);
4745   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4746                                 gfc_get_int_expr (gfc_default_integer_kind,
4747                                                   NULL, 1));
4748
4749   e->ts.u.cl->length->ts.type = BT_INTEGER;
4750   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4751
4752   /* Make sure that the length is simplified.  */
4753   gfc_simplify_expr (e->ts.u.cl->length, 1);
4754   gfc_resolve_expr (e->ts.u.cl->length);
4755 }
4756
4757
4758 /* Resolve subtype references.  */
4759
4760 static gfc_try
4761 resolve_ref (gfc_expr *expr)
4762 {
4763   int current_part_dimension, n_components, seen_part_dimension;
4764   gfc_ref *ref;
4765
4766   for (ref = expr->ref; ref; ref = ref->next)
4767     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4768       {
4769         find_array_spec (expr);
4770         break;
4771       }
4772
4773   for (ref = expr->ref; ref; ref = ref->next)
4774     switch (ref->type)
4775       {
4776       case REF_ARRAY:
4777         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4778           return FAILURE;
4779         break;
4780
4781       case REF_COMPONENT:
4782         break;
4783
4784       case REF_SUBSTRING:
4785         resolve_substring (ref);
4786         break;
4787       }
4788
4789   /* Check constraints on part references.  */
4790
4791   current_part_dimension = 0;
4792   seen_part_dimension = 0;
4793   n_components = 0;
4794
4795   for (ref = expr->ref; ref; ref = ref->next)
4796     {
4797       switch (ref->type)
4798         {
4799         case REF_ARRAY:
4800           switch (ref->u.ar.type)
4801             {
4802             case AR_FULL:
4803               /* Coarray scalar.  */
4804               if (ref->u.ar.as->rank == 0)
4805                 {
4806                   current_part_dimension = 0;
4807                   break;
4808                 }
4809               /* Fall through.  */
4810             case AR_SECTION:
4811               current_part_dimension = 1;
4812               break;
4813
4814             case AR_ELEMENT:
4815               current_part_dimension = 0;
4816               break;
4817
4818             case AR_UNKNOWN:
4819               gfc_internal_error ("resolve_ref(): Bad array reference");
4820             }
4821
4822           break;
4823
4824         case REF_COMPONENT:
4825           if (current_part_dimension || seen_part_dimension)
4826             {
4827               /* F03:C614.  */
4828               if (ref->u.c.component->attr.pointer
4829                   || ref->u.c.component->attr.proc_pointer)
4830                 {
4831                   gfc_error ("Component to the right of a part reference "
4832                              "with nonzero rank must not have the POINTER "
4833                              "attribute at %L", &expr->where);
4834                   return FAILURE;
4835                 }
4836               else if (ref->u.c.component->attr.allocatable)
4837                 {
4838                   gfc_error ("Component to the right of a part reference "
4839                              "with nonzero rank must not have the ALLOCATABLE "
4840                              "attribute at %L", &expr->where);
4841                   return FAILURE;
4842                 }
4843             }
4844
4845           n_components++;
4846           break;
4847
4848         case REF_SUBSTRING:
4849           break;
4850         }
4851
4852       if (((ref->type == REF_COMPONENT && n_components > 1)
4853            || ref->next == NULL)
4854           && current_part_dimension
4855           && seen_part_dimension)
4856         {
4857           gfc_error ("Two or more part references with nonzero rank must "
4858                      "not be specified at %L", &expr->where);
4859           return FAILURE;
4860         }
4861
4862       if (ref->type == REF_COMPONENT)
4863         {
4864           if (current_part_dimension)
4865             seen_part_dimension = 1;
4866
4867           /* reset to make sure */
4868           current_part_dimension = 0;
4869         }
4870     }
4871
4872   return SUCCESS;
4873 }
4874
4875
4876 /* Given an expression, determine its shape.  This is easier than it sounds.
4877    Leaves the shape array NULL if it is not possible to determine the shape.  */
4878
4879 static void
4880 expression_shape (gfc_expr *e)
4881 {
4882   mpz_t array[GFC_MAX_DIMENSIONS];
4883   int i;
4884
4885   if (e->rank == 0 || e->shape != NULL)
4886     return;
4887
4888   for (i = 0; i < e->rank; i++)
4889     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4890       goto fail;
4891
4892   e->shape = gfc_get_shape (e->rank);
4893
4894   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4895
4896   return;
4897
4898 fail:
4899   for (i--; i >= 0; i--)
4900     mpz_clear (array[i]);
4901 }
4902
4903
4904 /* Given a variable expression node, compute the rank of the expression by
4905    examining the base symbol and any reference structures it may have.  */
4906
4907 static void
4908 expression_rank (gfc_expr *e)
4909 {
4910   gfc_ref *ref;
4911   int i, rank;
4912
4913   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4914      could lead to serious confusion...  */
4915   gcc_assert (e->expr_type != EXPR_COMPCALL);
4916
4917   if (e->ref == NULL)
4918     {
4919       if (e->expr_type == EXPR_ARRAY)
4920         goto done;
4921       /* Constructors can have a rank different from one via RESHAPE().  */
4922
4923       if (e->symtree == NULL)
4924         {
4925           e->rank = 0;
4926           goto done;
4927         }
4928
4929       e->rank = (e->symtree->n.sym->as == NULL)
4930                 ? 0 : e->symtree->n.sym->as->rank;
4931       goto done;
4932     }
4933
4934   rank = 0;
4935
4936   for (ref = e->ref; ref; ref = ref->next)
4937     {
4938       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.proc_pointer
4939           && ref->u.c.component->attr.function && !ref->next)
4940         rank = ref->u.c.component->as ? ref->u.c.component->as->rank : 0;
4941
4942       if (ref->type != REF_ARRAY)
4943         continue;
4944
4945       if (ref->u.ar.type == AR_FULL)
4946         {
4947           rank = ref->u.ar.as->rank;
4948           break;
4949         }
4950
4951       if (ref->u.ar.type == AR_SECTION)
4952         {
4953           /* Figure out the rank of the section.  */
4954           if (rank != 0)
4955             gfc_internal_error ("expression_rank(): Two array specs");
4956
4957           for (i = 0; i < ref->u.ar.dimen; i++)
4958             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4959                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4960               rank++;
4961
4962           break;
4963         }
4964     }
4965
4966   e->rank = rank;
4967
4968 done:
4969   expression_shape (e);
4970 }
4971
4972
4973 /* Resolve a variable expression.  */
4974
4975 static gfc_try
4976 resolve_variable (gfc_expr *e)
4977 {
4978   gfc_symbol *sym;
4979   gfc_try t;
4980
4981   t = SUCCESS;
4982
4983   if (e->symtree == NULL)
4984     return FAILURE;
4985   sym = e->symtree->n.sym;
4986
4987   /* If this is an associate-name, it may be parsed with an array reference
4988      in error even though the target is scalar.  Fail directly in this case.  */
4989   if (sym->assoc && !sym->attr.dimension && e->ref && e->ref->type == REF_ARRAY)
4990     return FAILURE;
4991
4992   /* On the other hand, the parser may not have known this is an array;
4993      in this case, we have to add a FULL reference.  */
4994   if (sym->assoc && sym->attr.dimension && !e->ref)
4995     {
4996       e->ref = gfc_get_ref ();
4997       e->ref->type = REF_ARRAY;
4998       e->ref->u.ar.type = AR_FULL;
4999       e->ref->u.ar.dimen = 0;
5000     }
5001
5002   if (e->ref && resolve_ref (e) == FAILURE)
5003     return FAILURE;
5004
5005   if (sym->attr.flavor == FL_PROCEDURE
5006       && (!sym->attr.function
5007           || (sym->attr.function && sym->result
5008               && sym->result->attr.proc_pointer
5009               && !sym->result->attr.function)))
5010     {
5011       e->ts.type = BT_PROCEDURE;
5012       goto resolve_procedure;
5013     }
5014
5015   if (sym->ts.type != BT_UNKNOWN)
5016     gfc_variable_attr (e, &e->ts);
5017   else
5018     {
5019       /* Must be a simple variable reference.  */
5020       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
5021         return FAILURE;
5022       e->ts = sym->ts;
5023     }
5024
5025   if (check_assumed_size_reference (sym, e))
5026     return FAILURE;
5027
5028   /* Deal with forward references to entries during resolve_code, to
5029      satisfy, at least partially, 12.5.2.5.  */
5030   if (gfc_current_ns->entries
5031       && current_entry_id == sym->entry_id
5032       && cs_base
5033       && cs_base->current
5034       && cs_base->current->op != EXEC_ENTRY)
5035     {
5036       gfc_entry_list *entry;
5037       gfc_formal_arglist *formal;
5038       int n;
5039       bool seen;
5040
5041       /* If the symbol is a dummy...  */
5042       if (sym->attr.dummy && sym->ns == gfc_current_ns)
5043         {
5044           entry = gfc_current_ns->entries;
5045           seen = false;
5046
5047           /* ...test if the symbol is a parameter of previous entries.  */
5048           for (; entry && entry->id <= current_entry_id; entry = entry->next)
5049             for (formal = entry->sym->formal; formal; formal = formal->next)
5050               {
5051                 if (formal->sym && sym->name == formal->sym->name)
5052                   seen = true;
5053               }
5054
5055           /*  If it has not been seen as a dummy, this is an error.  */
5056           if (!seen)
5057             {
5058               if (specification_expr)
5059                 gfc_error ("Variable '%s', used in a specification expression"
5060                            ", is referenced at %L before the ENTRY statement "
5061                            "in which it is a parameter",
5062                            sym->name, &cs_base->current->loc);
5063               else
5064                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
5065                            "statement in which it is a parameter",
5066                            sym->name, &cs_base->current->loc);
5067               t = FAILURE;
5068             }
5069         }
5070
5071       /* Now do the same check on the specification expressions.  */
5072       specification_expr = 1;
5073       if (sym->ts.type == BT_CHARACTER
5074           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
5075         t = FAILURE;
5076
5077       if (sym->as)
5078         for (n = 0; n < sym->as->rank; n++)
5079           {
5080              specification_expr = 1;
5081              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
5082                t = FAILURE;
5083              specification_expr = 1;
5084              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
5085                t = FAILURE;
5086           }
5087       specification_expr = 0;
5088
5089       if (t == SUCCESS)
5090         /* Update the symbol's entry level.  */
5091         sym->entry_id = current_entry_id + 1;
5092     }
5093
5094   /* If a symbol has been host_associated mark it.  This is used latter,
5095      to identify if aliasing is possible via host association.  */
5096   if (sym->attr.flavor == FL_VARIABLE
5097         && gfc_current_ns->parent
5098         && (gfc_current_ns->parent == sym->ns
5099               || (gfc_current_ns->parent->parent
5100                     && gfc_current_ns->parent->parent == sym->ns)))
5101     sym->attr.host_assoc = 1;
5102
5103 resolve_procedure:
5104   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
5105     t = FAILURE;
5106
5107   /* F2008, C617 and C1229.  */
5108   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5109       && gfc_is_coindexed (e))
5110     {
5111       gfc_ref *ref, *ref2 = NULL;
5112
5113       for (ref = e->ref; ref; ref = ref->next)
5114         {
5115           if (ref->type == REF_COMPONENT)
5116             ref2 = ref;
5117           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5118             break;
5119         }
5120
5121       for ( ; ref; ref = ref->next)
5122         if (ref->type == REF_COMPONENT)
5123           break;
5124
5125       /* Expression itself is not coindexed object.  */
5126       if (ref && e->ts.type == BT_CLASS)
5127         {
5128           gfc_error ("Polymorphic subobject of coindexed object at %L",
5129                      &e->where);
5130           t = FAILURE;
5131         }
5132
5133       /* Expression itself is coindexed object.  */
5134       if (ref == NULL)
5135         {
5136           gfc_component *c;
5137           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5138           for ( ; c; c = c->next)
5139             if (c->attr.allocatable && c->ts.type == BT_CLASS)
5140               {
5141                 gfc_error ("Coindexed object with polymorphic allocatable "
5142                          "subcomponent at %L", &e->where);
5143                 t = FAILURE;
5144                 break;
5145               }
5146         }
5147     }
5148
5149   return t;
5150 }
5151
5152
5153 /* Checks to see that the correct symbol has been host associated.
5154    The only situation where this arises is that in which a twice
5155    contained function is parsed after the host association is made.
5156    Therefore, on detecting this, change the symbol in the expression
5157    and convert the array reference into an actual arglist if the old
5158    symbol is a variable.  */
5159 static bool
5160 check_host_association (gfc_expr *e)
5161 {
5162   gfc_symbol *sym, *old_sym;
5163   gfc_symtree *st;
5164   int n;
5165   gfc_ref *ref;
5166   gfc_actual_arglist *arg, *tail = NULL;
5167   bool retval = e->expr_type == EXPR_FUNCTION;
5168
5169   /*  If the expression is the result of substitution in
5170       interface.c(gfc_extend_expr) because there is no way in
5171       which the host association can be wrong.  */
5172   if (e->symtree == NULL
5173         || e->symtree->n.sym == NULL
5174         || e->user_operator)
5175     return retval;
5176
5177   old_sym = e->symtree->n.sym;
5178
5179   if (gfc_current_ns->parent
5180         && old_sym->ns != gfc_current_ns)
5181     {
5182       /* Use the 'USE' name so that renamed module symbols are
5183          correctly handled.  */
5184       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5185
5186       if (sym && old_sym != sym
5187               && sym->ts.type == old_sym->ts.type
5188               && sym->attr.flavor == FL_PROCEDURE
5189               && sym->attr.contained)
5190         {
5191           /* Clear the shape, since it might not be valid.  */
5192           if (e->shape != NULL)
5193             {
5194               for (n = 0; n < e->rank; n++)
5195                 mpz_clear (e->shape[n]);
5196
5197               gfc_free (e->shape);
5198             }
5199
5200           /* Give the expression the right symtree!  */
5201           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5202           gcc_assert (st != NULL);
5203
5204           if (old_sym->attr.flavor == FL_PROCEDURE
5205                 || e->expr_type == EXPR_FUNCTION)
5206             {
5207               /* Original was function so point to the new symbol, since
5208                  the actual argument list is already attached to the
5209                  expression. */
5210               e->value.function.esym = NULL;
5211               e->symtree = st;
5212             }
5213           else
5214             {
5215               /* Original was variable so convert array references into
5216                  an actual arglist. This does not need any checking now
5217                  since gfc_resolve_function will take care of it.  */
5218               e->value.function.actual = NULL;
5219               e->expr_type = EXPR_FUNCTION;
5220               e->symtree = st;
5221
5222               /* Ambiguity will not arise if the array reference is not
5223                  the last reference.  */
5224               for (ref = e->ref; ref; ref = ref->next)
5225                 if (ref->type == REF_ARRAY && ref->next == NULL)
5226                   break;
5227
5228               gcc_assert (ref->type == REF_ARRAY);
5229
5230               /* Grab the start expressions from the array ref and
5231                  copy them into actual arguments.  */
5232               for (n = 0; n < ref->u.ar.dimen; n++)
5233                 {
5234                   arg = gfc_get_actual_arglist ();
5235                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5236                   if (e->value.function.actual == NULL)
5237                     tail = e->value.function.actual = arg;
5238                   else
5239                     {
5240                       tail->next = arg;
5241                       tail = arg;
5242                     }
5243                 }
5244
5245               /* Dump the reference list and set the rank.  */
5246               gfc_free_ref_list (e->ref);
5247               e->ref = NULL;
5248               e->rank = sym->as ? sym->as->rank : 0;
5249             }
5250
5251           gfc_resolve_expr (e);
5252           sym->refs++;
5253         }
5254     }
5255   /* This might have changed!  */
5256   return e->expr_type == EXPR_FUNCTION;
5257 }
5258
5259
5260 static void
5261 gfc_resolve_character_operator (gfc_expr *e)
5262 {
5263   gfc_expr *op1 = e->value.op.op1;
5264   gfc_expr *op2 = e->value.op.op2;
5265   gfc_expr *e1 = NULL;
5266   gfc_expr *e2 = NULL;
5267
5268   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5269
5270   if (op1->ts.u.cl && op1->ts.u.cl->length)
5271     e1 = gfc_copy_expr (op1->ts.u.cl->length);
5272   else if (op1->expr_type == EXPR_CONSTANT)
5273     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5274                            op1->value.character.length);
5275
5276   if (op2->ts.u.cl && op2->ts.u.cl->length)
5277     e2 = gfc_copy_expr (op2->ts.u.cl->length);
5278   else if (op2->expr_type == EXPR_CONSTANT)
5279     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5280                            op2->value.character.length);
5281
5282   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5283
5284   if (!e1 || !e2)
5285     return;
5286
5287   e->ts.u.cl->length = gfc_add (e1, e2);
5288   e->ts.u.cl->length->ts.type = BT_INTEGER;
5289   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5290   gfc_simplify_expr (e->ts.u.cl->length, 0);
5291   gfc_resolve_expr (e->ts.u.cl->length);
5292
5293   return;
5294 }
5295
5296
5297 /*  Ensure that an character expression has a charlen and, if possible, a
5298     length expression.  */
5299
5300 static void
5301 fixup_charlen (gfc_expr *e)
5302 {
5303   /* The cases fall through so that changes in expression type and the need
5304      for multiple fixes are picked up.  In all circumstances, a charlen should
5305      be available for the middle end to hang a backend_decl on.  */
5306   switch (e->expr_type)
5307     {
5308     case EXPR_OP:
5309       gfc_resolve_character_operator (e);
5310
5311     case EXPR_ARRAY:
5312       if (e->expr_type == EXPR_ARRAY)
5313         gfc_resolve_character_array_constructor (e);
5314
5315     case EXPR_SUBSTRING:
5316       if (!e->ts.u.cl && e->ref)
5317         gfc_resolve_substring_charlen (e);
5318
5319     default:
5320       if (!e->ts.u.cl)
5321         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5322
5323       break;
5324     }
5325 }
5326
5327
5328 /* Update an actual argument to include the passed-object for type-bound
5329    procedures at the right position.  */
5330
5331 static gfc_actual_arglist*
5332 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5333                      const char *name)
5334 {
5335   gcc_assert (argpos > 0);
5336
5337   if (argpos == 1)
5338     {
5339       gfc_actual_arglist* result;
5340
5341       result = gfc_get_actual_arglist ();
5342       result->expr = po;
5343       result->next = lst;
5344       if (name)
5345         result->name = name;
5346
5347       return result;
5348     }
5349
5350   if (lst)
5351     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5352   else
5353     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5354   return lst;
5355 }
5356
5357
5358 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5359
5360 static gfc_expr*
5361 extract_compcall_passed_object (gfc_expr* e)
5362 {
5363   gfc_expr* po;
5364
5365   gcc_assert (e->expr_type == EXPR_COMPCALL);
5366
5367   if (e->value.compcall.base_object)
5368     po = gfc_copy_expr (e->value.compcall.base_object);
5369   else
5370     {
5371       po = gfc_get_expr ();
5372       po->expr_type = EXPR_VARIABLE;
5373       po->symtree = e->symtree;
5374       po->ref = gfc_copy_ref (e->ref);
5375       po->where = e->where;
5376     }
5377
5378   if (gfc_resolve_expr (po) == FAILURE)
5379     return NULL;
5380
5381   return po;
5382 }
5383
5384
5385 /* Update the arglist of an EXPR_COMPCALL expression to include the
5386    passed-object.  */
5387
5388 static gfc_try
5389 update_compcall_arglist (gfc_expr* e)
5390 {
5391   gfc_expr* po;
5392   gfc_typebound_proc* tbp;
5393
5394   tbp = e->value.compcall.tbp;
5395
5396   if (tbp->error)
5397     return FAILURE;
5398
5399   po = extract_compcall_passed_object (e);
5400   if (!po)
5401     return FAILURE;
5402
5403   if (tbp->nopass || e->value.compcall.ignore_pass)
5404     {
5405       gfc_free_expr (po);
5406       return SUCCESS;
5407     }
5408
5409   gcc_assert (tbp->pass_arg_num > 0);
5410   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5411                                                   tbp->pass_arg_num,
5412                                                   tbp->pass_arg);
5413
5414   return SUCCESS;
5415 }
5416
5417
5418 /* Extract the passed object from a PPC call (a copy of it).  */
5419
5420 static gfc_expr*
5421 extract_ppc_passed_object (gfc_expr *e)
5422 {
5423   gfc_expr *po;
5424   gfc_ref **ref;
5425
5426   po = gfc_get_expr ();
5427   po->expr_type = EXPR_VARIABLE;
5428   po->symtree = e->symtree;
5429   po->ref = gfc_copy_ref (e->ref);
5430   po->where = e->where;
5431
5432   /* Remove PPC reference.  */
5433   ref = &po->ref;
5434   while ((*ref)->next)
5435     ref = &(*ref)->next;
5436   gfc_free_ref_list (*ref);
5437   *ref = NULL;
5438
5439   if (gfc_resolve_expr (po) == FAILURE)
5440     return NULL;
5441
5442   return po;
5443 }
5444
5445
5446 /* Update the actual arglist of a procedure pointer component to include the
5447    passed-object.  */
5448
5449 static gfc_try
5450 update_ppc_arglist (gfc_expr* e)
5451 {
5452   gfc_expr* po;
5453   gfc_component *ppc;
5454   gfc_typebound_proc* tb;
5455
5456   if (!gfc_is_proc_ptr_comp (e, &ppc))
5457     return FAILURE;
5458
5459   tb = ppc->tb;
5460
5461   if (tb->error)
5462     return FAILURE;
5463   else if (tb->nopass)
5464     return SUCCESS;
5465
5466   po = extract_ppc_passed_object (e);
5467   if (!po)
5468     return FAILURE;
5469
5470   /* F08:R739.  */
5471   if (po->rank > 0)
5472     {
5473       gfc_error ("Passed-object at %L must be scalar", &e->where);
5474       return FAILURE;
5475     }
5476
5477   /* F08:C611.  */
5478   if (po->ts.type == BT_DERIVED && po->ts.u.derived->attr.abstract)
5479     {
5480       gfc_error ("Base object for procedure-pointer component call at %L is of"
5481                  " ABSTRACT type '%s'", &e->where, po->ts.u.derived->name);
5482       return FAILURE;
5483     }
5484
5485   gcc_assert (tb->pass_arg_num > 0);
5486   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5487                                                   tb->pass_arg_num,
5488                                                   tb->pass_arg);
5489
5490   return SUCCESS;
5491 }
5492
5493
5494 /* Check that the object a TBP is called on is valid, i.e. it must not be
5495    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5496
5497 static gfc_try
5498 check_typebound_baseobject (gfc_expr* e)
5499 {
5500   gfc_expr* base;
5501   gfc_try return_value = FAILURE;
5502
5503   base = extract_compcall_passed_object (e);
5504   if (!base)
5505     return FAILURE;
5506
5507   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5508
5509   /* F08:C611.  */
5510   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5511     {
5512       gfc_error ("Base object for type-bound procedure call at %L is of"
5513                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5514       goto cleanup;
5515     }
5516
5517   /* F08:C1230. If the procedure called is NOPASS,
5518      the base object must be scalar.  */
5519   if (e->value.compcall.tbp->nopass && base->rank > 0)
5520     {
5521       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5522                  " be scalar", &e->where);
5523       goto cleanup;
5524     }
5525
5526   /* FIXME: Remove once PR 43214 is fixed (TBP with non-scalar PASS).  */
5527   if (base->rank > 0)
5528     {
5529       gfc_error ("Non-scalar base object at %L currently not implemented",
5530                  &e->where);
5531       goto cleanup;
5532     }
5533
5534   return_value = SUCCESS;
5535
5536 cleanup:
5537   gfc_free_expr (base);
5538   return return_value;
5539 }
5540
5541
5542 /* Resolve a call to a type-bound procedure, either function or subroutine,
5543    statically from the data in an EXPR_COMPCALL expression.  The adapted
5544    arglist and the target-procedure symtree are returned.  */
5545
5546 static gfc_try
5547 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5548                           gfc_actual_arglist** actual)
5549 {
5550   gcc_assert (e->expr_type == EXPR_COMPCALL);
5551   gcc_assert (!e->value.compcall.tbp->is_generic);
5552
5553   /* Update the actual arglist for PASS.  */
5554   if (update_compcall_arglist (e) == FAILURE)
5555     return FAILURE;
5556
5557   *actual = e->value.compcall.actual;
5558   *target = e->value.compcall.tbp->u.specific;
5559
5560   gfc_free_ref_list (e->ref);
5561   e->ref = NULL;
5562   e->value.compcall.actual = NULL;
5563
5564   return SUCCESS;
5565 }
5566
5567
5568 /* Get the ultimate declared type from an expression.  In addition,
5569    return the last class/derived type reference and the copy of the
5570    reference list.  */
5571 static gfc_symbol*
5572 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5573                         gfc_expr *e)
5574 {
5575   gfc_symbol *declared;
5576   gfc_ref *ref;
5577
5578   declared = NULL;
5579   if (class_ref)
5580     *class_ref = NULL;
5581   if (new_ref)
5582     *new_ref = gfc_copy_ref (e->ref);
5583
5584   for (ref = e->ref; ref; ref = ref->next)
5585     {
5586       if (ref->type != REF_COMPONENT)
5587         continue;
5588
5589       if (ref->u.c.component->ts.type == BT_CLASS
5590             || ref->u.c.component->ts.type == BT_DERIVED)
5591         {
5592           declared = ref->u.c.component->ts.u.derived;
5593           if (class_ref)
5594             *class_ref = ref;
5595         }
5596     }
5597
5598   if (declared == NULL)
5599     declared = e->symtree->n.sym->ts.u.derived;
5600
5601   return declared;
5602 }
5603
5604
5605 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5606    which of the specific bindings (if any) matches the arglist and transform
5607    the expression into a call of that binding.  */
5608
5609 static gfc_try
5610 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5611 {
5612   gfc_typebound_proc* genproc;
5613   const char* genname;
5614   gfc_symtree *st;
5615   gfc_symbol *derived;
5616
5617   gcc_assert (e->expr_type == EXPR_COMPCALL);
5618   genname = e->value.compcall.name;
5619   genproc = e->value.compcall.tbp;
5620
5621   if (!genproc->is_generic)
5622     return SUCCESS;
5623
5624   /* Try the bindings on this type and in the inheritance hierarchy.  */
5625   for (; genproc; genproc = genproc->overridden)
5626     {
5627       gfc_tbp_generic* g;
5628
5629       gcc_assert (genproc->is_generic);
5630       for (g = genproc->u.generic; g; g = g->next)
5631         {
5632           gfc_symbol* target;
5633           gfc_actual_arglist* args;
5634           bool matches;
5635
5636           gcc_assert (g->specific);
5637
5638           if (g->specific->error)
5639             continue;
5640
5641           target = g->specific->u.specific->n.sym;
5642
5643           /* Get the right arglist by handling PASS/NOPASS.  */
5644           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5645           if (!g->specific->nopass)
5646             {
5647               gfc_expr* po;
5648               po = extract_compcall_passed_object (e);
5649               if (!po)
5650                 return FAILURE;
5651
5652               gcc_assert (g->specific->pass_arg_num > 0);
5653               gcc_assert (!g->specific->error);
5654               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5655                                           g->specific->pass_arg);
5656             }
5657           resolve_actual_arglist (args, target->attr.proc,
5658                                   is_external_proc (target) && !target->formal);
5659
5660           /* Check if this arglist matches the formal.  */
5661           matches = gfc_arglist_matches_symbol (&args, target);
5662
5663           /* Clean up and break out of the loop if we've found it.  */
5664           gfc_free_actual_arglist (args);
5665           if (matches)
5666             {
5667               e->value.compcall.tbp = g->specific;
5668               genname = g->specific_st->name;
5669               /* Pass along the name for CLASS methods, where the vtab
5670                  procedure pointer component has to be referenced.  */
5671               if (name)
5672                 *name = genname;
5673               goto success;
5674             }
5675         }
5676     }
5677
5678   /* Nothing matching found!  */
5679   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5680              " '%s' at %L", genname, &e->where);
5681   return FAILURE;
5682
5683 success:
5684   /* Make sure that we have the right specific instance for the name.  */
5685   derived = get_declared_from_expr (NULL, NULL, e);
5686
5687   st = gfc_find_typebound_proc (derived, NULL, genname, false, &e->where);
5688   if (st)
5689     e->value.compcall.tbp = st->n.tb;
5690
5691   return SUCCESS;
5692 }
5693
5694
5695 /* Resolve a call to a type-bound subroutine.  */
5696
5697 static gfc_try
5698 resolve_typebound_call (gfc_code* c, const char **name)
5699 {
5700   gfc_actual_arglist* newactual;
5701   gfc_symtree* target;
5702
5703   /* Check that's really a SUBROUTINE.  */
5704   if (!c->expr1->value.compcall.tbp->subroutine)
5705     {
5706       gfc_error ("'%s' at %L should be a SUBROUTINE",
5707                  c->expr1->value.compcall.name, &c->loc);
5708       return FAILURE;
5709     }
5710
5711   if (check_typebound_baseobject (c->expr1) == FAILURE)
5712     return FAILURE;
5713
5714   /* Pass along the name for CLASS methods, where the vtab
5715      procedure pointer component has to be referenced.  */
5716   if (name)
5717     *name = c->expr1->value.compcall.name;
5718
5719   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5720     return FAILURE;
5721
5722   /* Transform into an ordinary EXEC_CALL for now.  */
5723
5724   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5725     return FAILURE;
5726
5727   c->ext.actual = newactual;
5728   c->symtree = target;
5729   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5730
5731   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5732
5733   gfc_free_expr (c->expr1);
5734   c->expr1 = gfc_get_expr ();
5735   c->expr1->expr_type = EXPR_FUNCTION;
5736   c->expr1->symtree = target;
5737   c->expr1->where = c->loc;
5738
5739   return resolve_call (c);
5740 }
5741
5742
5743 /* Resolve a component-call expression.  */
5744 static gfc_try
5745 resolve_compcall (gfc_expr* e, const char **name)
5746 {
5747   gfc_actual_arglist* newactual;
5748   gfc_symtree* target;
5749
5750   /* Check that's really a FUNCTION.  */
5751   if (!e->value.compcall.tbp->function)
5752     {
5753       gfc_error ("'%s' at %L should be a FUNCTION",
5754                  e->value.compcall.name, &e->where);
5755       return FAILURE;
5756     }
5757
5758   /* These must not be assign-calls!  */
5759   gcc_assert (!e->value.compcall.assign);
5760
5761   if (check_typebound_baseobject (e) == FAILURE)
5762     return FAILURE;
5763
5764   /* Pass along the name for CLASS methods, where the vtab
5765      procedure pointer component has to be referenced.  */
5766   if (name)
5767     *name = e->value.compcall.name;
5768
5769   if (resolve_typebound_generic_call (e, name) == FAILURE)
5770     return FAILURE;
5771   gcc_assert (!e->value.compcall.tbp->is_generic);
5772
5773   /* Take the rank from the function's symbol.  */
5774   if (e->value.compcall.tbp->u.specific->n.sym->as)
5775     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5776
5777   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5778      arglist to the TBP's binding target.  */
5779
5780   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5781     return FAILURE;
5782
5783   e->value.function.actual = newactual;
5784   e->value.function.name = NULL;
5785   e->value.function.esym = target->n.sym;
5786   e->value.function.isym = NULL;
5787   e->symtree = target;
5788   e->ts = target->n.sym->ts;
5789   e->expr_type = EXPR_FUNCTION;
5790
5791   /* Resolution is not necessary if this is a class subroutine; this
5792      function only has to identify the specific proc. Resolution of
5793      the call will be done next in resolve_typebound_call.  */
5794   return gfc_resolve_expr (e);
5795 }
5796
5797
5798
5799 /* Resolve a typebound function, or 'method'. First separate all
5800    the non-CLASS references by calling resolve_compcall directly.  */
5801
5802 static gfc_try
5803 resolve_typebound_function (gfc_expr* e)
5804 {
5805   gfc_symbol *declared;
5806   gfc_component *c;
5807   gfc_ref *new_ref;
5808   gfc_ref *class_ref;
5809   gfc_symtree *st;
5810   const char *name;
5811   gfc_typespec ts;
5812   gfc_expr *expr;
5813
5814   st = e->symtree;
5815
5816   /* Deal with typebound operators for CLASS objects.  */
5817   expr = e->value.compcall.base_object;
5818   if (expr && expr->ts.type == BT_CLASS && e->value.compcall.name)
5819     {
5820       /* Since the typebound operators are generic, we have to ensure
5821          that any delays in resolution are corrected and that the vtab
5822          is present.  */
5823       ts = expr->ts;
5824       declared = ts.u.derived;
5825       c = gfc_find_component (declared, "_vptr", true, true);
5826       if (c->ts.u.derived == NULL)
5827         c->ts.u.derived = gfc_find_derived_vtab (declared);
5828
5829       if (resolve_compcall (e, &name) == FAILURE)
5830         return FAILURE;
5831
5832       /* Use the generic name if it is there.  */
5833       name = name ? name : e->value.function.esym->name;
5834       e->symtree = expr->symtree;
5835       e->ref = gfc_copy_ref (expr->ref);
5836       gfc_add_vptr_component (e);
5837       gfc_add_component_ref (e, name);
5838       e->value.function.esym = NULL;
5839       return SUCCESS;
5840     }
5841
5842   if (st == NULL)
5843     return resolve_compcall (e, NULL);
5844
5845   if (resolve_ref (e) == FAILURE)
5846     return FAILURE;
5847
5848   /* Get the CLASS declared type.  */
5849   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5850
5851   /* Weed out cases of the ultimate component being a derived type.  */
5852   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5853          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5854     {
5855       gfc_free_ref_list (new_ref);
5856       return resolve_compcall (e, NULL);
5857     }
5858
5859   c = gfc_find_component (declared, "_data", true, true);
5860   declared = c->ts.u.derived;
5861
5862   /* Treat the call as if it is a typebound procedure, in order to roll
5863      out the correct name for the specific function.  */
5864   if (resolve_compcall (e, &name) == FAILURE)
5865     return FAILURE;
5866   ts = e->ts;
5867
5868   /* Then convert the expression to a procedure pointer component call.  */
5869   e->value.function.esym = NULL;
5870   e->symtree = st;
5871
5872   if (new_ref)  
5873     e->ref = new_ref;
5874
5875   /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5876   gfc_add_vptr_component (e);
5877   gfc_add_component_ref (e, name);
5878
5879   /* Recover the typespec for the expression.  This is really only
5880      necessary for generic procedures, where the additional call
5881      to gfc_add_component_ref seems to throw the collection of the
5882      correct typespec.  */
5883   e->ts = ts;
5884   return SUCCESS;
5885 }
5886
5887 /* Resolve a typebound subroutine, or 'method'. First separate all
5888    the non-CLASS references by calling resolve_typebound_call
5889    directly.  */
5890
5891 static gfc_try
5892 resolve_typebound_subroutine (gfc_code *code)
5893 {
5894   gfc_symbol *declared;
5895   gfc_component *c;
5896   gfc_ref *new_ref;
5897   gfc_ref *class_ref;
5898   gfc_symtree *st;
5899   const char *name;
5900   gfc_typespec ts;
5901   gfc_expr *expr;
5902
5903   st = code->expr1->symtree;
5904
5905   /* Deal with typebound operators for CLASS objects.  */
5906   expr = code->expr1->value.compcall.base_object;
5907   if (expr && expr->ts.type == BT_CLASS && code->expr1->value.compcall.name)
5908     {
5909       /* Since the typebound operators are generic, we have to ensure
5910          that any delays in resolution are corrected and that the vtab
5911          is present.  */
5912       declared = expr->ts.u.derived;
5913       c = gfc_find_component (declared, "_vptr", true, true);
5914       if (c->ts.u.derived == NULL)
5915         c->ts.u.derived = gfc_find_derived_vtab (declared);
5916
5917       if (resolve_typebound_call (code, &name) == FAILURE)
5918         return FAILURE;
5919
5920       /* Use the generic name if it is there.  */
5921       name = name ? name : code->expr1->value.function.esym->name;
5922       code->expr1->symtree = expr->symtree;
5923       code->expr1->ref = gfc_copy_ref (expr->ref);
5924       gfc_add_vptr_component (code->expr1);
5925       gfc_add_component_ref (code->expr1, name);
5926       code->expr1->value.function.esym = NULL;
5927       return SUCCESS;
5928     }
5929
5930   if (st == NULL)
5931     return resolve_typebound_call (code, NULL);
5932
5933   if (resolve_ref (code->expr1) == FAILURE)
5934     return FAILURE;
5935
5936   /* Get the CLASS declared type.  */
5937   get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5938
5939   /* Weed out cases of the ultimate component being a derived type.  */
5940   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5941          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5942     {
5943       gfc_free_ref_list (new_ref);
5944       return resolve_typebound_call (code, NULL);
5945     }
5946
5947   if (resolve_typebound_call (code, &name) == FAILURE)
5948     return FAILURE;
5949   ts = code->expr1->ts;
5950
5951   /* Then convert the expression to a procedure pointer component call.  */
5952   code->expr1->value.function.esym = NULL;
5953   code->expr1->symtree = st;
5954
5955   if (new_ref)
5956     code->expr1->ref = new_ref;
5957
5958   /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5959   gfc_add_vptr_component (code->expr1);
5960   gfc_add_component_ref (code->expr1, name);
5961
5962   /* Recover the typespec for the expression.  This is really only
5963      necessary for generic procedures, where the additional call
5964      to gfc_add_component_ref seems to throw the collection of the
5965      correct typespec.  */
5966   code->expr1->ts = ts;
5967   return SUCCESS;
5968 }
5969
5970
5971 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5972
5973 static gfc_try
5974 resolve_ppc_call (gfc_code* c)
5975 {
5976   gfc_component *comp;
5977   bool b;
5978
5979   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5980   gcc_assert (b);
5981
5982   c->resolved_sym = c->expr1->symtree->n.sym;
5983   c->expr1->expr_type = EXPR_VARIABLE;
5984
5985   if (!comp->attr.subroutine)
5986     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5987
5988   if (resolve_ref (c->expr1) == FAILURE)
5989     return FAILURE;
5990
5991   if (update_ppc_arglist (c->expr1) == FAILURE)
5992     return FAILURE;
5993
5994   c->ext.actual = c->expr1->value.compcall.actual;
5995
5996   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5997                               comp->formal == NULL) == FAILURE)
5998     return FAILURE;
5999
6000   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
6001
6002   return SUCCESS;
6003 }
6004
6005
6006 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
6007
6008 static gfc_try
6009 resolve_expr_ppc (gfc_expr* e)
6010 {
6011   gfc_component *comp;
6012   bool b;
6013
6014   b = gfc_is_proc_ptr_comp (e, &comp);
6015   gcc_assert (b);
6016
6017   /* Convert to EXPR_FUNCTION.  */
6018   e->expr_type = EXPR_FUNCTION;
6019   e->value.function.isym = NULL;
6020   e->value.function.actual = e->value.compcall.actual;
6021   e->ts = comp->ts;
6022   if (comp->as != NULL)
6023     e->rank = comp->as->rank;
6024
6025   if (!comp->attr.function)
6026     gfc_add_function (&comp->attr, comp->name, &e->where);
6027
6028   if (resolve_ref (e) == FAILURE)
6029     return FAILURE;
6030
6031   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
6032                               comp->formal == NULL) == FAILURE)
6033     return FAILURE;
6034
6035   if (update_ppc_arglist (e) == FAILURE)
6036     return FAILURE;
6037
6038   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
6039
6040   return SUCCESS;
6041 }
6042
6043
6044 static bool
6045 gfc_is_expandable_expr (gfc_expr *e)
6046 {
6047   gfc_constructor *con;
6048
6049   if (e->expr_type == EXPR_ARRAY)
6050     {
6051       /* Traverse the constructor looking for variables that are flavor
6052          parameter.  Parameters must be expanded since they are fully used at
6053          compile time.  */
6054       con = gfc_constructor_first (e->value.constructor);
6055       for (; con; con = gfc_constructor_next (con))
6056         {
6057           if (con->expr->expr_type == EXPR_VARIABLE
6058               && con->expr->symtree
6059               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
6060               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
6061             return true;
6062           if (con->expr->expr_type == EXPR_ARRAY
6063               && gfc_is_expandable_expr (con->expr))
6064             return true;
6065         }
6066     }
6067
6068   return false;
6069 }
6070
6071 /* Resolve an expression.  That is, make sure that types of operands agree
6072    with their operators, intrinsic operators are converted to function calls
6073    for overloaded types and unresolved function references are resolved.  */
6074
6075 gfc_try
6076 gfc_resolve_expr (gfc_expr *e)
6077 {
6078   gfc_try t;
6079   bool inquiry_save;
6080
6081   if (e == NULL)
6082     return SUCCESS;
6083
6084   /* inquiry_argument only applies to variables.  */
6085   inquiry_save = inquiry_argument;
6086   if (e->expr_type != EXPR_VARIABLE)
6087     inquiry_argument = false;
6088
6089   switch (e->expr_type)
6090     {
6091     case EXPR_OP:
6092       t = resolve_operator (e);
6093       break;
6094
6095     case EXPR_FUNCTION:
6096     case EXPR_VARIABLE:
6097
6098       if (check_host_association (e))
6099         t = resolve_function (e);
6100       else
6101         {
6102           t = resolve_variable (e);
6103           if (t == SUCCESS)
6104             expression_rank (e);
6105         }
6106
6107       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6108           && e->ref->type != REF_SUBSTRING)
6109         gfc_resolve_substring_charlen (e);
6110
6111       break;
6112
6113     case EXPR_COMPCALL:
6114       t = resolve_typebound_function (e);
6115       break;
6116
6117     case EXPR_SUBSTRING:
6118       t = resolve_ref (e);
6119       break;
6120
6121     case EXPR_CONSTANT:
6122     case EXPR_NULL:
6123       t = SUCCESS;
6124       break;
6125
6126     case EXPR_PPC:
6127       t = resolve_expr_ppc (e);
6128       break;
6129
6130     case EXPR_ARRAY:
6131       t = FAILURE;
6132       if (resolve_ref (e) == FAILURE)
6133         break;
6134
6135       t = gfc_resolve_array_constructor (e);
6136       /* Also try to expand a constructor.  */
6137       if (t == SUCCESS)
6138         {
6139           expression_rank (e);
6140           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6141             gfc_expand_constructor (e, false);
6142         }
6143
6144       /* This provides the opportunity for the length of constructors with
6145          character valued function elements to propagate the string length
6146          to the expression.  */
6147       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
6148         {
6149           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6150              here rather then add a duplicate test for it above.  */ 
6151           gfc_expand_constructor (e, false);
6152           t = gfc_resolve_character_array_constructor (e);
6153         }
6154
6155       break;
6156
6157     case EXPR_STRUCTURE:
6158       t = resolve_ref (e);
6159       if (t == FAILURE)
6160         break;
6161
6162       t = resolve_structure_cons (e, 0);
6163       if (t == FAILURE)
6164         break;
6165
6166       t = gfc_simplify_expr (e, 0);
6167       break;
6168
6169     default:
6170       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6171     }
6172
6173   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
6174     fixup_charlen (e);
6175
6176   inquiry_argument = inquiry_save;
6177
6178   return t;
6179 }
6180
6181
6182 /* Resolve an expression from an iterator.  They must be scalar and have
6183    INTEGER or (optionally) REAL type.  */
6184
6185 static gfc_try
6186 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6187                            const char *name_msgid)
6188 {
6189   if (gfc_resolve_expr (expr) == FAILURE)
6190     return FAILURE;
6191
6192   if (expr->rank != 0)
6193     {
6194       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6195       return FAILURE;
6196     }
6197
6198   if (expr->ts.type != BT_INTEGER)
6199     {
6200       if (expr->ts.type == BT_REAL)
6201         {
6202           if (real_ok)
6203             return gfc_notify_std (GFC_STD_F95_DEL,
6204                                    "Deleted feature: %s at %L must be integer",
6205                                    _(name_msgid), &expr->where);
6206           else
6207             {
6208               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6209                          &expr->where);
6210               return FAILURE;
6211             }
6212         }
6213       else
6214         {
6215           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6216           return FAILURE;
6217         }
6218     }
6219   return SUCCESS;
6220 }
6221
6222
6223 /* Resolve the expressions in an iterator structure.  If REAL_OK is
6224    false allow only INTEGER type iterators, otherwise allow REAL types.  */
6225
6226 gfc_try
6227 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
6228 {
6229   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
6230       == FAILURE)
6231     return FAILURE;
6232
6233   if (gfc_check_vardef_context (iter->var, false, _("iterator variable"))
6234       == FAILURE)
6235     return FAILURE;
6236
6237   if (gfc_resolve_iterator_expr (iter->start, real_ok,
6238                                  "Start expression in DO loop") == FAILURE)
6239     return FAILURE;
6240
6241   if (gfc_resolve_iterator_expr (iter->end, real_ok,
6242                                  "End expression in DO loop") == FAILURE)
6243     return FAILURE;
6244
6245   if (gfc_resolve_iterator_expr (iter->step, real_ok,
6246                                  "Step expression in DO loop") == FAILURE)
6247     return FAILURE;
6248
6249   if (iter->step->expr_type == EXPR_CONSTANT)
6250     {
6251       if ((iter->step->ts.type == BT_INTEGER
6252            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6253           || (iter->step->ts.type == BT_REAL
6254               && mpfr_sgn (iter->step->value.real) == 0))
6255         {
6256           gfc_error ("Step expression in DO loop at %L cannot be zero",
6257                      &iter->step->where);
6258           return FAILURE;
6259         }
6260     }
6261
6262   /* Convert start, end, and step to the same type as var.  */
6263   if (iter->start->ts.kind != iter->var->ts.kind
6264       || iter->start->ts.type != iter->var->ts.type)
6265     gfc_convert_type (iter->start, &iter->var->ts, 2);
6266
6267   if (iter->end->ts.kind != iter->var->ts.kind
6268       || iter->end->ts.type != iter->var->ts.type)
6269     gfc_convert_type (iter->end, &iter->var->ts, 2);
6270
6271   if (iter->step->ts.kind != iter->var->ts.kind
6272       || iter->step->ts.type != iter->var->ts.type)
6273     gfc_convert_type (iter->step, &iter->var->ts, 2);
6274
6275   if (iter->start->expr_type == EXPR_CONSTANT
6276       && iter->end->expr_type == EXPR_CONSTANT
6277       && iter->step->expr_type == EXPR_CONSTANT)
6278     {
6279       int sgn, cmp;
6280       if (iter->start->ts.type == BT_INTEGER)
6281         {
6282           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6283           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6284         }
6285       else
6286         {
6287           sgn = mpfr_sgn (iter->step->value.real);
6288           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6289         }
6290       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
6291         gfc_warning ("DO loop at %L will be executed zero times",
6292                      &iter->step->where);
6293     }
6294
6295   return SUCCESS;
6296 }
6297
6298
6299 /* Traversal function for find_forall_index.  f == 2 signals that
6300    that variable itself is not to be checked - only the references.  */
6301
6302 static bool
6303 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6304 {
6305   if (expr->expr_type != EXPR_VARIABLE)
6306     return false;
6307   
6308   /* A scalar assignment  */
6309   if (!expr->ref || *f == 1)
6310     {
6311       if (expr->symtree->n.sym == sym)
6312         return true;
6313       else
6314         return false;
6315     }
6316
6317   if (*f == 2)
6318     *f = 1;
6319   return false;
6320 }
6321
6322
6323 /* Check whether the FORALL index appears in the expression or not.
6324    Returns SUCCESS if SYM is found in EXPR.  */
6325
6326 gfc_try
6327 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6328 {
6329   if (gfc_traverse_expr (expr, sym, forall_index, f))
6330     return SUCCESS;
6331   else
6332     return FAILURE;
6333 }
6334
6335
6336 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6337    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6338    INTEGERs, and if stride is a constant it must be nonzero.
6339    Furthermore "A subscript or stride in a forall-triplet-spec shall
6340    not contain a reference to any index-name in the
6341    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6342
6343 static void
6344 resolve_forall_iterators (gfc_forall_iterator *it)
6345 {
6346   gfc_forall_iterator *iter, *iter2;
6347
6348   for (iter = it; iter; iter = iter->next)
6349     {
6350       if (gfc_resolve_expr (iter->var) == SUCCESS
6351           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6352         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6353                    &iter->var->where);
6354
6355       if (gfc_resolve_expr (iter->start) == SUCCESS
6356           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6357         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6358                    &iter->start->where);
6359       if (iter->var->ts.kind != iter->start->ts.kind)
6360         gfc_convert_type (iter->start, &iter->var->ts, 2);
6361
6362       if (gfc_resolve_expr (iter->end) == SUCCESS
6363           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6364         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6365                    &iter->end->where);
6366       if (iter->var->ts.kind != iter->end->ts.kind)
6367         gfc_convert_type (iter->end, &iter->var->ts, 2);
6368
6369       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6370         {
6371           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6372             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6373                        &iter->stride->where, "INTEGER");
6374
6375           if (iter->stride->expr_type == EXPR_CONSTANT
6376               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6377             gfc_error ("FORALL stride expression at %L cannot be zero",
6378                        &iter->stride->where);
6379         }
6380       if (iter->var->ts.kind != iter->stride->ts.kind)
6381         gfc_convert_type (iter->stride, &iter->var->ts, 2);
6382     }
6383
6384   for (iter = it; iter; iter = iter->next)
6385     for (iter2 = iter; iter2; iter2 = iter2->next)
6386       {
6387         if (find_forall_index (iter2->start,
6388                                iter->var->symtree->n.sym, 0) == SUCCESS
6389             || find_forall_index (iter2->end,
6390                                   iter->var->symtree->n.sym, 0) == SUCCESS
6391             || find_forall_index (iter2->stride,
6392                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6393           gfc_error ("FORALL index '%s' may not appear in triplet "
6394                      "specification at %L", iter->var->symtree->name,
6395                      &iter2->start->where);
6396       }
6397 }
6398
6399
6400 /* Given a pointer to a symbol that is a derived type, see if it's
6401    inaccessible, i.e. if it's defined in another module and the components are
6402    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6403    inaccessible components are found, nonzero otherwise.  */
6404
6405 static int
6406 derived_inaccessible (gfc_symbol *sym)
6407 {
6408   gfc_component *c;
6409
6410   if (sym->attr.use_assoc && sym->attr.private_comp)
6411     return 1;
6412
6413   for (c = sym->components; c; c = c->next)
6414     {
6415         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6416           return 1;
6417     }
6418
6419   return 0;
6420 }
6421
6422
6423 /* Resolve the argument of a deallocate expression.  The expression must be
6424    a pointer or a full array.  */
6425
6426 static gfc_try
6427 resolve_deallocate_expr (gfc_expr *e)
6428 {
6429   symbol_attribute attr;
6430   int allocatable, pointer;
6431   gfc_ref *ref;
6432   gfc_symbol *sym;
6433   gfc_component *c;
6434
6435   if (gfc_resolve_expr (e) == FAILURE)
6436     return FAILURE;
6437
6438   if (e->expr_type != EXPR_VARIABLE)
6439     goto bad;
6440
6441   sym = e->symtree->n.sym;
6442
6443   if (sym->ts.type == BT_CLASS)
6444     {
6445       allocatable = CLASS_DATA (sym)->attr.allocatable;
6446       pointer = CLASS_DATA (sym)->attr.class_pointer;
6447     }
6448   else
6449     {
6450       allocatable = sym->attr.allocatable;
6451       pointer = sym->attr.pointer;
6452     }
6453   for (ref = e->ref; ref; ref = ref->next)
6454     {
6455       switch (ref->type)
6456         {
6457         case REF_ARRAY:
6458           if (ref->u.ar.type != AR_FULL)
6459             allocatable = 0;
6460           break;
6461
6462         case REF_COMPONENT:
6463           c = ref->u.c.component;
6464           if (c->ts.type == BT_CLASS)
6465             {
6466               allocatable = CLASS_DATA (c)->attr.allocatable;
6467               pointer = CLASS_DATA (c)->attr.class_pointer;
6468             }
6469           else
6470             {
6471               allocatable = c->attr.allocatable;
6472               pointer = c->attr.pointer;
6473             }
6474           break;
6475
6476         case REF_SUBSTRING:
6477           allocatable = 0;
6478           break;
6479         }
6480     }
6481
6482   attr = gfc_expr_attr (e);
6483
6484   if (allocatable == 0 && attr.pointer == 0)
6485     {
6486     bad:
6487       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6488                  &e->where);
6489       return FAILURE;
6490     }
6491
6492   if (pointer
6493       && gfc_check_vardef_context (e, true, _("DEALLOCATE object")) == FAILURE)
6494     return FAILURE;
6495   if (gfc_check_vardef_context (e, false, _("DEALLOCATE object")) == FAILURE)
6496     return FAILURE;
6497
6498   return SUCCESS;
6499 }
6500
6501
6502 /* Returns true if the expression e contains a reference to the symbol sym.  */
6503 static bool
6504 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6505 {
6506   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6507     return true;
6508
6509   return false;
6510 }
6511
6512 bool
6513 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6514 {
6515   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6516 }
6517
6518
6519 /* Given the expression node e for an allocatable/pointer of derived type to be
6520    allocated, get the expression node to be initialized afterwards (needed for
6521    derived types with default initializers, and derived types with allocatable
6522    components that need nullification.)  */
6523
6524 gfc_expr *
6525 gfc_expr_to_initialize (gfc_expr *e)
6526 {
6527   gfc_expr *result;
6528   gfc_ref *ref;
6529   int i;
6530
6531   result = gfc_copy_expr (e);
6532
6533   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6534   for (ref = result->ref; ref; ref = ref->next)
6535     if (ref->type == REF_ARRAY && ref->next == NULL)
6536       {
6537         ref->u.ar.type = AR_FULL;
6538
6539         for (i = 0; i < ref->u.ar.dimen; i++)
6540           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6541
6542         result->rank = ref->u.ar.dimen;
6543         break;
6544       }
6545
6546   return result;
6547 }
6548
6549
6550 /* If the last ref of an expression is an array ref, return a copy of the
6551    expression with that one removed.  Otherwise, a copy of the original
6552    expression.  This is used for allocate-expressions and pointer assignment
6553    LHS, where there may be an array specification that needs to be stripped
6554    off when using gfc_check_vardef_context.  */
6555
6556 static gfc_expr*
6557 remove_last_array_ref (gfc_expr* e)
6558 {
6559   gfc_expr* e2;
6560   gfc_ref** r;
6561
6562   e2 = gfc_copy_expr (e);
6563   for (r = &e2->ref; *r; r = &(*r)->next)
6564     if ((*r)->type == REF_ARRAY && !(*r)->next)
6565       {
6566         gfc_free_ref_list (*r);
6567         *r = NULL;
6568         break;
6569       }
6570
6571   return e2;
6572 }
6573
6574
6575 /* Used in resolve_allocate_expr to check that a allocation-object and
6576    a source-expr are conformable.  This does not catch all possible 
6577    cases; in particular a runtime checking is needed.  */
6578
6579 static gfc_try
6580 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6581 {
6582   gfc_ref *tail;
6583   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6584   
6585   /* First compare rank.  */
6586   if (tail && e1->rank != tail->u.ar.as->rank)
6587     {
6588       gfc_error ("Source-expr at %L must be scalar or have the "
6589                  "same rank as the allocate-object at %L",
6590                  &e1->where, &e2->where);
6591       return FAILURE;
6592     }
6593
6594   if (e1->shape)
6595     {
6596       int i;
6597       mpz_t s;
6598
6599       mpz_init (s);
6600
6601       for (i = 0; i < e1->rank; i++)
6602         {
6603           if (tail->u.ar.end[i])
6604             {
6605               mpz_set (s, tail->u.ar.end[i]->value.integer);
6606               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6607               mpz_add_ui (s, s, 1);
6608             }
6609           else
6610             {
6611               mpz_set (s, tail->u.ar.start[i]->value.integer);
6612             }
6613
6614           if (mpz_cmp (e1->shape[i], s) != 0)
6615             {
6616               gfc_error ("Source-expr at %L and allocate-object at %L must "
6617                          "have the same shape", &e1->where, &e2->where);
6618               mpz_clear (s);
6619               return FAILURE;
6620             }
6621         }
6622
6623       mpz_clear (s);
6624     }
6625
6626   return SUCCESS;
6627 }
6628
6629
6630 /* Resolve the expression in an ALLOCATE statement, doing the additional
6631    checks to see whether the expression is OK or not.  The expression must
6632    have a trailing array reference that gives the size of the array.  */
6633
6634 static gfc_try
6635 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6636 {
6637   int i, pointer, allocatable, dimension, is_abstract;
6638   int codimension;
6639   symbol_attribute attr;
6640   gfc_ref *ref, *ref2;
6641   gfc_expr *e2;
6642   gfc_array_ref *ar;
6643   gfc_symbol *sym = NULL;
6644   gfc_alloc *a;
6645   gfc_component *c;
6646   gfc_try t;
6647
6648   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6649      checking of coarrays.  */
6650   for (ref = e->ref; ref; ref = ref->next)
6651     if (ref->next == NULL)
6652       break;
6653
6654   if (ref && ref->type == REF_ARRAY)
6655     ref->u.ar.in_allocate = true;
6656
6657   if (gfc_resolve_expr (e) == FAILURE)
6658     goto failure;
6659
6660   /* Make sure the expression is allocatable or a pointer.  If it is
6661      pointer, the next-to-last reference must be a pointer.  */
6662
6663   ref2 = NULL;
6664   if (e->symtree)
6665     sym = e->symtree->n.sym;
6666
6667   /* Check whether ultimate component is abstract and CLASS.  */
6668   is_abstract = 0;
6669
6670   if (e->expr_type != EXPR_VARIABLE)
6671     {
6672       allocatable = 0;
6673       attr = gfc_expr_attr (e);
6674       pointer = attr.pointer;
6675       dimension = attr.dimension;
6676       codimension = attr.codimension;
6677     }
6678   else
6679     {
6680       if (sym->ts.type == BT_CLASS)
6681         {
6682           allocatable = CLASS_DATA (sym)->attr.allocatable;
6683           pointer = CLASS_DATA (sym)->attr.class_pointer;
6684           dimension = CLASS_DATA (sym)->attr.dimension;
6685           codimension = CLASS_DATA (sym)->attr.codimension;
6686           is_abstract = CLASS_DATA (sym)->attr.abstract;
6687         }
6688       else
6689         {
6690           allocatable = sym->attr.allocatable;
6691           pointer = sym->attr.pointer;
6692           dimension = sym->attr.dimension;
6693           codimension = sym->attr.codimension;
6694         }
6695
6696       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6697         {
6698           switch (ref->type)
6699             {
6700               case REF_ARRAY:
6701                 if (ref->next != NULL)
6702                   pointer = 0;
6703                 break;
6704
6705               case REF_COMPONENT:
6706                 /* F2008, C644.  */
6707                 if (gfc_is_coindexed (e))
6708                   {
6709                     gfc_error ("Coindexed allocatable object at %L",
6710                                &e->where);
6711                     goto failure;
6712                   }
6713
6714                 c = ref->u.c.component;
6715                 if (c->ts.type == BT_CLASS)
6716                   {
6717                     allocatable = CLASS_DATA (c)->attr.allocatable;
6718                     pointer = CLASS_DATA (c)->attr.class_pointer;
6719                     dimension = CLASS_DATA (c)->attr.dimension;
6720                     codimension = CLASS_DATA (c)->attr.codimension;
6721                     is_abstract = CLASS_DATA (c)->attr.abstract;
6722                   }
6723                 else
6724                   {
6725                     allocatable = c->attr.allocatable;
6726                     pointer = c->attr.pointer;
6727                     dimension = c->attr.dimension;
6728                     codimension = c->attr.codimension;
6729                     is_abstract = c->attr.abstract;
6730                   }
6731                 break;
6732
6733               case REF_SUBSTRING:
6734                 allocatable = 0;
6735                 pointer = 0;
6736                 break;
6737             }
6738         }
6739     }
6740
6741   if (allocatable == 0 && pointer == 0)
6742     {
6743       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6744                  &e->where);
6745       goto failure;
6746     }
6747
6748   /* Some checks for the SOURCE tag.  */
6749   if (code->expr3)
6750     {
6751       /* Check F03:C631.  */
6752       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6753         {
6754           gfc_error ("Type of entity at %L is type incompatible with "
6755                       "source-expr at %L", &e->where, &code->expr3->where);
6756           goto failure;
6757         }
6758
6759       /* Check F03:C632 and restriction following Note 6.18.  */
6760       if (code->expr3->rank > 0
6761           && conformable_arrays (code->expr3, e) == FAILURE)
6762         goto failure;
6763
6764       /* Check F03:C633.  */
6765       if (code->expr3->ts.kind != e->ts.kind)
6766         {
6767           gfc_error ("The allocate-object at %L and the source-expr at %L "
6768                       "shall have the same kind type parameter",
6769                       &e->where, &code->expr3->where);
6770           goto failure;
6771         }
6772     }
6773
6774   /* Check F08:C629.  */
6775   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
6776       && !code->expr3)
6777     {
6778       gcc_assert (e->ts.type == BT_CLASS);
6779       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6780                  "type-spec or source-expr", sym->name, &e->where);
6781       goto failure;
6782     }
6783
6784   /* In the variable definition context checks, gfc_expr_attr is used
6785      on the expression.  This is fooled by the array specification
6786      present in e, thus we have to eliminate that one temporarily.  */
6787   e2 = remove_last_array_ref (e);
6788   t = SUCCESS;
6789   if (t == SUCCESS && pointer)
6790     t = gfc_check_vardef_context (e2, true, _("ALLOCATE object"));
6791   if (t == SUCCESS)
6792     t = gfc_check_vardef_context (e2, false, _("ALLOCATE object"));
6793   gfc_free_expr (e2);
6794   if (t == FAILURE)
6795     goto failure;
6796
6797   if (!code->expr3)
6798     {
6799       /* Set up default initializer if needed.  */
6800       gfc_typespec ts;
6801       gfc_expr *init_e;
6802
6803       if (code->ext.alloc.ts.type == BT_DERIVED)
6804         ts = code->ext.alloc.ts;
6805       else
6806         ts = e->ts;
6807
6808       if (ts.type == BT_CLASS)
6809         ts = ts.u.derived->components->ts;
6810
6811       if (ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&ts)))
6812         {
6813           gfc_code *init_st = gfc_get_code ();
6814           init_st->loc = code->loc;
6815           init_st->op = EXEC_INIT_ASSIGN;
6816           init_st->expr1 = gfc_expr_to_initialize (e);
6817           init_st->expr2 = init_e;
6818           init_st->next = code->next;
6819           code->next = init_st;
6820         }
6821     }
6822   else if (code->expr3->mold && code->expr3->ts.type == BT_DERIVED)
6823     {
6824       /* Default initialization via MOLD (non-polymorphic).  */
6825       gfc_expr *rhs = gfc_default_initializer (&code->expr3->ts);
6826       gfc_resolve_expr (rhs);
6827       gfc_free_expr (code->expr3);
6828       code->expr3 = rhs;
6829     }
6830
6831   if (e->ts.type == BT_CLASS)
6832     {
6833       /* Make sure the vtab symbol is present when
6834          the module variables are generated.  */
6835       gfc_typespec ts = e->ts;
6836       if (code->expr3)
6837         ts = code->expr3->ts;
6838       else if (code->ext.alloc.ts.type == BT_DERIVED)
6839         ts = code->ext.alloc.ts;
6840       gfc_find_derived_vtab (ts.u.derived);
6841     }
6842
6843   if (pointer || (dimension == 0 && codimension == 0))
6844     goto success;
6845
6846   /* Make sure the last reference node is an array specifiction.  */
6847
6848   if (!ref2 || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
6849       || (dimension && ref2->u.ar.dimen == 0))
6850     {
6851       gfc_error ("Array specification required in ALLOCATE statement "
6852                  "at %L", &e->where);
6853       goto failure;
6854     }
6855
6856   /* Make sure that the array section reference makes sense in the
6857     context of an ALLOCATE specification.  */
6858
6859   ar = &ref2->u.ar;
6860
6861   if (codimension)
6862     for (i = ar->dimen; i < ar->dimen + ar->codimen; i++)
6863       if (ar->dimen_type[i] == DIMEN_THIS_IMAGE)
6864         {
6865           gfc_error ("Coarray specification required in ALLOCATE statement "
6866                      "at %L", &e->where);
6867           goto failure;
6868         }
6869
6870   for (i = 0; i < ar->dimen; i++)
6871     {
6872       if (ref2->u.ar.type == AR_ELEMENT)
6873         goto check_symbols;
6874
6875       switch (ar->dimen_type[i])
6876         {
6877         case DIMEN_ELEMENT:
6878           break;
6879
6880         case DIMEN_RANGE:
6881           if (ar->start[i] != NULL
6882               && ar->end[i] != NULL
6883               && ar->stride[i] == NULL)
6884             break;
6885
6886           /* Fall Through...  */
6887
6888         case DIMEN_UNKNOWN:
6889         case DIMEN_VECTOR:
6890         case DIMEN_STAR:
6891         case DIMEN_THIS_IMAGE:
6892           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6893                      &e->where);
6894           goto failure;
6895         }
6896
6897 check_symbols:
6898       for (a = code->ext.alloc.list; a; a = a->next)
6899         {
6900           sym = a->expr->symtree->n.sym;
6901
6902           /* TODO - check derived type components.  */
6903           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6904             continue;
6905
6906           if ((ar->start[i] != NULL
6907                && gfc_find_sym_in_expr (sym, ar->start[i]))
6908               || (ar->end[i] != NULL
6909                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6910             {
6911               gfc_error ("'%s' must not appear in the array specification at "
6912                          "%L in the same ALLOCATE statement where it is "
6913                          "itself allocated", sym->name, &ar->where);
6914               goto failure;
6915             }
6916         }
6917     }
6918
6919   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
6920     {
6921       if (ar->dimen_type[i] == DIMEN_ELEMENT
6922           || ar->dimen_type[i] == DIMEN_RANGE)
6923         {
6924           if (i == (ar->dimen + ar->codimen - 1))
6925             {
6926               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
6927                          "statement at %L", &e->where);
6928               goto failure;
6929             }
6930           break;
6931         }
6932
6933       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
6934           && ar->stride[i] == NULL)
6935         break;
6936
6937       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
6938                  &e->where);
6939       goto failure;
6940     }
6941
6942   if (codimension && ar->as->rank == 0)
6943     {
6944       gfc_error ("Sorry, allocatable scalar coarrays are not yet supported "
6945                  "at %L", &e->where);
6946       goto failure;
6947     }
6948
6949 success:
6950   return SUCCESS;
6951
6952 failure:
6953   return FAILURE;
6954 }
6955
6956 static void
6957 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6958 {
6959   gfc_expr *stat, *errmsg, *pe, *qe;
6960   gfc_alloc *a, *p, *q;
6961
6962   stat = code->expr1;
6963   errmsg = code->expr2;
6964
6965   /* Check the stat variable.  */
6966   if (stat)
6967     {
6968       gfc_check_vardef_context (stat, false, _("STAT variable"));
6969
6970       if ((stat->ts.type != BT_INTEGER
6971            && !(stat->ref && (stat->ref->type == REF_ARRAY
6972                               || stat->ref->type == REF_COMPONENT)))
6973           || stat->rank > 0)
6974         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6975                    "variable", &stat->where);
6976
6977       for (p = code->ext.alloc.list; p; p = p->next)
6978         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6979           {
6980             gfc_ref *ref1, *ref2;
6981             bool found = true;
6982
6983             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
6984                  ref1 = ref1->next, ref2 = ref2->next)
6985               {
6986                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
6987                   continue;
6988                 if (ref1->u.c.component->name != ref2->u.c.component->name)
6989                   {
6990                     found = false;
6991                     break;
6992                   }
6993               }
6994
6995             if (found)
6996               {
6997                 gfc_error ("Stat-variable at %L shall not be %sd within "
6998                            "the same %s statement", &stat->where, fcn, fcn);
6999                 break;
7000               }
7001           }
7002     }
7003
7004   /* Check the errmsg variable.  */
7005   if (errmsg)
7006     {
7007       if (!stat)
7008         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
7009                      &errmsg->where);
7010
7011       gfc_check_vardef_context (errmsg, false, _("ERRMSG variable"));
7012
7013       if ((errmsg->ts.type != BT_CHARACTER
7014            && !(errmsg->ref
7015                 && (errmsg->ref->type == REF_ARRAY
7016                     || errmsg->ref->type == REF_COMPONENT)))
7017           || errmsg->rank > 0 )
7018         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
7019                    "variable", &errmsg->where);
7020
7021       for (p = code->ext.alloc.list; p; p = p->next)
7022         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
7023           {
7024             gfc_ref *ref1, *ref2;
7025             bool found = true;
7026
7027             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
7028                  ref1 = ref1->next, ref2 = ref2->next)
7029               {
7030                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7031                   continue;
7032                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7033                   {
7034                     found = false;
7035                     break;
7036                   }
7037               }
7038
7039             if (found)
7040               {
7041                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
7042                            "the same %s statement", &errmsg->where, fcn, fcn);
7043                 break;
7044               }
7045           }
7046     }
7047
7048   /* Check that an allocate-object appears only once in the statement.  
7049      FIXME: Checking derived types is disabled.  */
7050   for (p = code->ext.alloc.list; p; p = p->next)
7051     {
7052       pe = p->expr;
7053       for (q = p->next; q; q = q->next)
7054         {
7055           qe = q->expr;
7056           if (pe->symtree->n.sym->name == qe->symtree->n.sym->name)
7057             {
7058               /* This is a potential collision.  */
7059               gfc_ref *pr = pe->ref;
7060               gfc_ref *qr = qe->ref;
7061               
7062               /* Follow the references  until
7063                  a) They start to differ, in which case there is no error;
7064                  you can deallocate a%b and a%c in a single statement
7065                  b) Both of them stop, which is an error
7066                  c) One of them stops, which is also an error.  */
7067               while (1)
7068                 {
7069                   if (pr == NULL && qr == NULL)
7070                     {
7071                       gfc_error ("Allocate-object at %L also appears at %L",
7072                                  &pe->where, &qe->where);
7073                       break;
7074                     }
7075                   else if (pr != NULL && qr == NULL)
7076                     {
7077                       gfc_error ("Allocate-object at %L is subobject of"
7078                                  " object at %L", &pe->where, &qe->where);
7079                       break;
7080                     }
7081                   else if (pr == NULL && qr != NULL)
7082                     {
7083                       gfc_error ("Allocate-object at %L is subobject of"
7084                                  " object at %L", &qe->where, &pe->where);
7085                       break;
7086                     }
7087                   /* Here, pr != NULL && qr != NULL  */
7088                   gcc_assert(pr->type == qr->type);
7089                   if (pr->type == REF_ARRAY)
7090                     {
7091                       /* Handle cases like allocate(v(3)%x(3), v(2)%x(3)),
7092                          which are legal.  */
7093                       gcc_assert (qr->type == REF_ARRAY);
7094
7095                       if (pr->next && qr->next)
7096                         {
7097                           gfc_array_ref *par = &(pr->u.ar);
7098                           gfc_array_ref *qar = &(qr->u.ar);
7099                           if (gfc_dep_compare_expr (par->start[0],
7100                                                     qar->start[0]) != 0)
7101                               break;
7102                         }
7103                     }
7104                   else
7105                     {
7106                       if (pr->u.c.component->name != qr->u.c.component->name)
7107                         break;
7108                     }
7109                   
7110                   pr = pr->next;
7111                   qr = qr->next;
7112                 }
7113             }
7114         }
7115     }
7116
7117   if (strcmp (fcn, "ALLOCATE") == 0)
7118     {
7119       for (a = code->ext.alloc.list; a; a = a->next)
7120         resolve_allocate_expr (a->expr, code);
7121     }
7122   else
7123     {
7124       for (a = code->ext.alloc.list; a; a = a->next)
7125         resolve_deallocate_expr (a->expr);
7126     }
7127 }
7128
7129
7130 /************ SELECT CASE resolution subroutines ************/
7131
7132 /* Callback function for our mergesort variant.  Determines interval
7133    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7134    op1 > op2.  Assumes we're not dealing with the default case.  
7135    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7136    There are nine situations to check.  */
7137
7138 static int
7139 compare_cases (const gfc_case *op1, const gfc_case *op2)
7140 {
7141   int retval;
7142
7143   if (op1->low == NULL) /* op1 = (:L)  */
7144     {
7145       /* op2 = (:N), so overlap.  */
7146       retval = 0;
7147       /* op2 = (M:) or (M:N),  L < M  */
7148       if (op2->low != NULL
7149           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7150         retval = -1;
7151     }
7152   else if (op1->high == NULL) /* op1 = (K:)  */
7153     {
7154       /* op2 = (M:), so overlap.  */
7155       retval = 0;
7156       /* op2 = (:N) or (M:N), K > N  */
7157       if (op2->high != NULL
7158           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7159         retval = 1;
7160     }
7161   else /* op1 = (K:L)  */
7162     {
7163       if (op2->low == NULL)       /* op2 = (:N), K > N  */
7164         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7165                  ? 1 : 0;
7166       else if (op2->high == NULL) /* op2 = (M:), L < M  */
7167         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7168                  ? -1 : 0;
7169       else                      /* op2 = (M:N)  */
7170         {
7171           retval =  0;
7172           /* L < M  */
7173           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7174             retval =  -1;
7175           /* K > N  */
7176           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7177             retval =  1;
7178         }
7179     }
7180
7181   return retval;
7182 }
7183
7184
7185 /* Merge-sort a double linked case list, detecting overlap in the
7186    process.  LIST is the head of the double linked case list before it
7187    is sorted.  Returns the head of the sorted list if we don't see any
7188    overlap, or NULL otherwise.  */
7189
7190 static gfc_case *
7191 check_case_overlap (gfc_case *list)
7192 {
7193   gfc_case *p, *q, *e, *tail;
7194   int insize, nmerges, psize, qsize, cmp, overlap_seen;
7195
7196   /* If the passed list was empty, return immediately.  */
7197   if (!list)
7198     return NULL;
7199
7200   overlap_seen = 0;
7201   insize = 1;
7202
7203   /* Loop unconditionally.  The only exit from this loop is a return
7204      statement, when we've finished sorting the case list.  */
7205   for (;;)
7206     {
7207       p = list;
7208       list = NULL;
7209       tail = NULL;
7210
7211       /* Count the number of merges we do in this pass.  */
7212       nmerges = 0;
7213
7214       /* Loop while there exists a merge to be done.  */
7215       while (p)
7216         {
7217           int i;
7218
7219           /* Count this merge.  */
7220           nmerges++;
7221
7222           /* Cut the list in two pieces by stepping INSIZE places
7223              forward in the list, starting from P.  */
7224           psize = 0;
7225           q = p;
7226           for (i = 0; i < insize; i++)
7227             {
7228               psize++;
7229               q = q->right;
7230               if (!q)
7231                 break;
7232             }
7233           qsize = insize;
7234
7235           /* Now we have two lists.  Merge them!  */
7236           while (psize > 0 || (qsize > 0 && q != NULL))
7237             {
7238               /* See from which the next case to merge comes from.  */
7239               if (psize == 0)
7240                 {
7241                   /* P is empty so the next case must come from Q.  */
7242                   e = q;
7243                   q = q->right;
7244                   qsize--;
7245                 }
7246               else if (qsize == 0 || q == NULL)
7247                 {
7248                   /* Q is empty.  */
7249                   e = p;
7250                   p = p->right;
7251                   psize--;
7252                 }
7253               else
7254                 {
7255                   cmp = compare_cases (p, q);
7256                   if (cmp < 0)
7257                     {
7258                       /* The whole case range for P is less than the
7259                          one for Q.  */
7260                       e = p;
7261                       p = p->right;
7262                       psize--;
7263                     }
7264                   else if (cmp > 0)
7265                     {
7266                       /* The whole case range for Q is greater than
7267                          the case range for P.  */
7268                       e = q;
7269                       q = q->right;
7270                       qsize--;
7271                     }
7272                   else
7273                     {
7274                       /* The cases overlap, or they are the same
7275                          element in the list.  Either way, we must
7276                          issue an error and get the next case from P.  */
7277                       /* FIXME: Sort P and Q by line number.  */
7278                       gfc_error ("CASE label at %L overlaps with CASE "
7279                                  "label at %L", &p->where, &q->where);
7280                       overlap_seen = 1;
7281                       e = p;
7282                       p = p->right;
7283                       psize--;
7284                     }
7285                 }
7286
7287                 /* Add the next element to the merged list.  */
7288               if (tail)
7289                 tail->right = e;
7290               else
7291                 list = e;
7292               e->left = tail;
7293               tail = e;
7294             }
7295
7296           /* P has now stepped INSIZE places along, and so has Q.  So
7297              they're the same.  */
7298           p = q;
7299         }
7300       tail->right = NULL;
7301
7302       /* If we have done only one merge or none at all, we've
7303          finished sorting the cases.  */
7304       if (nmerges <= 1)
7305         {
7306           if (!overlap_seen)
7307             return list;
7308           else
7309             return NULL;
7310         }
7311
7312       /* Otherwise repeat, merging lists twice the size.  */
7313       insize *= 2;
7314     }
7315 }
7316
7317
7318 /* Check to see if an expression is suitable for use in a CASE statement.
7319    Makes sure that all case expressions are scalar constants of the same
7320    type.  Return FAILURE if anything is wrong.  */
7321
7322 static gfc_try
7323 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7324 {
7325   if (e == NULL) return SUCCESS;
7326
7327   if (e->ts.type != case_expr->ts.type)
7328     {
7329       gfc_error ("Expression in CASE statement at %L must be of type %s",
7330                  &e->where, gfc_basic_typename (case_expr->ts.type));
7331       return FAILURE;
7332     }
7333
7334   /* C805 (R808) For a given case-construct, each case-value shall be of
7335      the same type as case-expr.  For character type, length differences
7336      are allowed, but the kind type parameters shall be the same.  */
7337
7338   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7339     {
7340       gfc_error ("Expression in CASE statement at %L must be of kind %d",
7341                  &e->where, case_expr->ts.kind);
7342       return FAILURE;
7343     }
7344
7345   /* Convert the case value kind to that of case expression kind,
7346      if needed */
7347
7348   if (e->ts.kind != case_expr->ts.kind)
7349     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7350
7351   if (e->rank != 0)
7352     {
7353       gfc_error ("Expression in CASE statement at %L must be scalar",
7354                  &e->where);
7355       return FAILURE;
7356     }
7357
7358   return SUCCESS;
7359 }
7360
7361
7362 /* Given a completely parsed select statement, we:
7363
7364      - Validate all expressions and code within the SELECT.
7365      - Make sure that the selection expression is not of the wrong type.
7366      - Make sure that no case ranges overlap.
7367      - Eliminate unreachable cases and unreachable code resulting from
7368        removing case labels.
7369
7370    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7371    they are a hassle for code generation, and to prevent that, we just
7372    cut them out here.  This is not necessary for overlapping cases
7373    because they are illegal and we never even try to generate code.
7374
7375    We have the additional caveat that a SELECT construct could have
7376    been a computed GOTO in the source code. Fortunately we can fairly
7377    easily work around that here: The case_expr for a "real" SELECT CASE
7378    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7379    we have to do is make sure that the case_expr is a scalar integer
7380    expression.  */
7381
7382 static void
7383 resolve_select (gfc_code *code)
7384 {
7385   gfc_code *body;
7386   gfc_expr *case_expr;
7387   gfc_case *cp, *default_case, *tail, *head;
7388   int seen_unreachable;
7389   int seen_logical;
7390   int ncases;
7391   bt type;
7392   gfc_try t;
7393
7394   if (code->expr1 == NULL)
7395     {
7396       /* This was actually a computed GOTO statement.  */
7397       case_expr = code->expr2;
7398       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7399         gfc_error ("Selection expression in computed GOTO statement "
7400                    "at %L must be a scalar integer expression",
7401                    &case_expr->where);
7402
7403       /* Further checking is not necessary because this SELECT was built
7404          by the compiler, so it should always be OK.  Just move the
7405          case_expr from expr2 to expr so that we can handle computed
7406          GOTOs as normal SELECTs from here on.  */
7407       code->expr1 = code->expr2;
7408       code->expr2 = NULL;
7409       return;
7410     }
7411
7412   case_expr = code->expr1;
7413
7414   type = case_expr->ts.type;
7415   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7416     {
7417       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7418                  &case_expr->where, gfc_typename (&case_expr->ts));
7419
7420       /* Punt. Going on here just produce more garbage error messages.  */
7421       return;
7422     }
7423
7424   if (case_expr->rank != 0)
7425     {
7426       gfc_error ("Argument of SELECT statement at %L must be a scalar "
7427                  "expression", &case_expr->where);
7428
7429       /* Punt.  */
7430       return;
7431     }
7432
7433
7434   /* Raise a warning if an INTEGER case value exceeds the range of
7435      the case-expr. Later, all expressions will be promoted to the
7436      largest kind of all case-labels.  */
7437
7438   if (type == BT_INTEGER)
7439     for (body = code->block; body; body = body->block)
7440       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7441         {
7442           if (cp->low
7443               && gfc_check_integer_range (cp->low->value.integer,
7444                                           case_expr->ts.kind) != ARITH_OK)
7445             gfc_warning ("Expression in CASE statement at %L is "
7446                          "not in the range of %s", &cp->low->where,
7447                          gfc_typename (&case_expr->ts));
7448
7449           if (cp->high
7450               && cp->low != cp->high
7451               && gfc_check_integer_range (cp->high->value.integer,
7452                                           case_expr->ts.kind) != ARITH_OK)
7453             gfc_warning ("Expression in CASE statement at %L is "
7454                          "not in the range of %s", &cp->high->where,
7455                          gfc_typename (&case_expr->ts));
7456         }
7457
7458   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7459      of the SELECT CASE expression and its CASE values.  Walk the lists
7460      of case values, and if we find a mismatch, promote case_expr to
7461      the appropriate kind.  */
7462
7463   if (type == BT_LOGICAL || type == BT_INTEGER)
7464     {
7465       for (body = code->block; body; body = body->block)
7466         {
7467           /* Walk the case label list.  */
7468           for (cp = body->ext.block.case_list; cp; cp = cp->next)
7469             {
7470               /* Intercept the DEFAULT case.  It does not have a kind.  */
7471               if (cp->low == NULL && cp->high == NULL)
7472                 continue;
7473
7474               /* Unreachable case ranges are discarded, so ignore.  */
7475               if (cp->low != NULL && cp->high != NULL
7476                   && cp->low != cp->high
7477                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7478                 continue;
7479
7480               if (cp->low != NULL
7481                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7482                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7483
7484               if (cp->high != NULL
7485                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7486                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7487             }
7488          }
7489     }
7490
7491   /* Assume there is no DEFAULT case.  */
7492   default_case = NULL;
7493   head = tail = NULL;
7494   ncases = 0;
7495   seen_logical = 0;
7496
7497   for (body = code->block; body; body = body->block)
7498     {
7499       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7500       t = SUCCESS;
7501       seen_unreachable = 0;
7502
7503       /* Walk the case label list, making sure that all case labels
7504          are legal.  */
7505       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7506         {
7507           /* Count the number of cases in the whole construct.  */
7508           ncases++;
7509
7510           /* Intercept the DEFAULT case.  */
7511           if (cp->low == NULL && cp->high == NULL)
7512             {
7513               if (default_case != NULL)
7514                 {
7515                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7516                              "by a second DEFAULT CASE at %L",
7517                              &default_case->where, &cp->where);
7518                   t = FAILURE;
7519                   break;
7520                 }
7521               else
7522                 {
7523                   default_case = cp;
7524                   continue;
7525                 }
7526             }
7527
7528           /* Deal with single value cases and case ranges.  Errors are
7529              issued from the validation function.  */
7530           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7531               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7532             {
7533               t = FAILURE;
7534               break;
7535             }
7536
7537           if (type == BT_LOGICAL
7538               && ((cp->low == NULL || cp->high == NULL)
7539                   || cp->low != cp->high))
7540             {
7541               gfc_error ("Logical range in CASE statement at %L is not "
7542                          "allowed", &cp->low->where);
7543               t = FAILURE;
7544               break;
7545             }
7546
7547           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7548             {
7549               int value;
7550               value = cp->low->value.logical == 0 ? 2 : 1;
7551               if (value & seen_logical)
7552                 {
7553                   gfc_error ("Constant logical value in CASE statement "
7554                              "is repeated at %L",
7555                              &cp->low->where);
7556                   t = FAILURE;
7557                   break;
7558                 }
7559               seen_logical |= value;
7560             }
7561
7562           if (cp->low != NULL && cp->high != NULL
7563               && cp->low != cp->high
7564               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7565             {
7566               if (gfc_option.warn_surprising)
7567                 gfc_warning ("Range specification at %L can never "
7568                              "be matched", &cp->where);
7569
7570               cp->unreachable = 1;
7571               seen_unreachable = 1;
7572             }
7573           else
7574             {
7575               /* If the case range can be matched, it can also overlap with
7576                  other cases.  To make sure it does not, we put it in a
7577                  double linked list here.  We sort that with a merge sort
7578                  later on to detect any overlapping cases.  */
7579               if (!head)
7580                 {
7581                   head = tail = cp;
7582                   head->right = head->left = NULL;
7583                 }
7584               else
7585                 {
7586                   tail->right = cp;
7587                   tail->right->left = tail;
7588                   tail = tail->right;
7589                   tail->right = NULL;
7590                 }
7591             }
7592         }
7593
7594       /* It there was a failure in the previous case label, give up
7595          for this case label list.  Continue with the next block.  */
7596       if (t == FAILURE)
7597         continue;
7598
7599       /* See if any case labels that are unreachable have been seen.
7600          If so, we eliminate them.  This is a bit of a kludge because
7601          the case lists for a single case statement (label) is a
7602          single forward linked lists.  */
7603       if (seen_unreachable)
7604       {
7605         /* Advance until the first case in the list is reachable.  */
7606         while (body->ext.block.case_list != NULL
7607                && body->ext.block.case_list->unreachable)
7608           {
7609             gfc_case *n = body->ext.block.case_list;
7610             body->ext.block.case_list = body->ext.block.case_list->next;
7611             n->next = NULL;
7612             gfc_free_case_list (n);
7613           }
7614
7615         /* Strip all other unreachable cases.  */
7616         if (body->ext.block.case_list)
7617           {
7618             for (cp = body->ext.block.case_list; cp->next; cp = cp->next)
7619               {
7620                 if (cp->next->unreachable)
7621                   {
7622                     gfc_case *n = cp->next;
7623                     cp->next = cp->next->next;
7624                     n->next = NULL;
7625                     gfc_free_case_list (n);
7626                   }
7627               }
7628           }
7629       }
7630     }
7631
7632   /* See if there were overlapping cases.  If the check returns NULL,
7633      there was overlap.  In that case we don't do anything.  If head
7634      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7635      then used during code generation for SELECT CASE constructs with
7636      a case expression of a CHARACTER type.  */
7637   if (head)
7638     {
7639       head = check_case_overlap (head);
7640
7641       /* Prepend the default_case if it is there.  */
7642       if (head != NULL && default_case)
7643         {
7644           default_case->left = NULL;
7645           default_case->right = head;
7646           head->left = default_case;
7647         }
7648     }
7649
7650   /* Eliminate dead blocks that may be the result if we've seen
7651      unreachable case labels for a block.  */
7652   for (body = code; body && body->block; body = body->block)
7653     {
7654       if (body->block->ext.block.case_list == NULL)
7655         {
7656           /* Cut the unreachable block from the code chain.  */
7657           gfc_code *c = body->block;
7658           body->block = c->block;
7659
7660           /* Kill the dead block, but not the blocks below it.  */
7661           c->block = NULL;
7662           gfc_free_statements (c);
7663         }
7664     }
7665
7666   /* More than two cases is legal but insane for logical selects.
7667      Issue a warning for it.  */
7668   if (gfc_option.warn_surprising && type == BT_LOGICAL
7669       && ncases > 2)
7670     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7671                  &code->loc);
7672 }
7673
7674
7675 /* Check if a derived type is extensible.  */
7676
7677 bool
7678 gfc_type_is_extensible (gfc_symbol *sym)
7679 {
7680   return !(sym->attr.is_bind_c || sym->attr.sequence);
7681 }
7682
7683
7684 /* Resolve an associate name:  Resolve target and ensure the type-spec is
7685    correct as well as possibly the array-spec.  */
7686
7687 static void
7688 resolve_assoc_var (gfc_symbol* sym, bool resolve_target)
7689 {
7690   gfc_expr* target;
7691
7692   gcc_assert (sym->assoc);
7693   gcc_assert (sym->attr.flavor == FL_VARIABLE);
7694
7695   /* If this is for SELECT TYPE, the target may not yet be set.  In that
7696      case, return.  Resolution will be called later manually again when
7697      this is done.  */
7698   target = sym->assoc->target;
7699   if (!target)
7700     return;
7701   gcc_assert (!sym->assoc->dangling);
7702
7703   if (resolve_target && gfc_resolve_expr (target) != SUCCESS)
7704     return;
7705
7706   /* For variable targets, we get some attributes from the target.  */
7707   if (target->expr_type == EXPR_VARIABLE)
7708     {
7709       gfc_symbol* tsym;
7710
7711       gcc_assert (target->symtree);
7712       tsym = target->symtree->n.sym;
7713
7714       sym->attr.asynchronous = tsym->attr.asynchronous;
7715       sym->attr.volatile_ = tsym->attr.volatile_;
7716
7717       sym->attr.target = (tsym->attr.target || tsym->attr.pointer);
7718     }
7719
7720   /* Get type if this was not already set.  Note that it can be
7721      some other type than the target in case this is a SELECT TYPE
7722      selector!  So we must not update when the type is already there.  */
7723   if (sym->ts.type == BT_UNKNOWN)
7724     sym->ts = target->ts;
7725   gcc_assert (sym->ts.type != BT_UNKNOWN);
7726
7727   /* See if this is a valid association-to-variable.  */
7728   sym->assoc->variable = (target->expr_type == EXPR_VARIABLE
7729                           && !gfc_has_vector_subscript (target));
7730
7731   /* Finally resolve if this is an array or not.  */
7732   if (sym->attr.dimension && target->rank == 0)
7733     {
7734       gfc_error ("Associate-name '%s' at %L is used as array",
7735                  sym->name, &sym->declared_at);
7736       sym->attr.dimension = 0;
7737       return;
7738     }
7739   if (target->rank > 0)
7740     sym->attr.dimension = 1;
7741
7742   if (sym->attr.dimension)
7743     {
7744       sym->as = gfc_get_array_spec ();
7745       sym->as->rank = target->rank;
7746       sym->as->type = AS_DEFERRED;
7747
7748       /* Target must not be coindexed, thus the associate-variable
7749          has no corank.  */
7750       sym->as->corank = 0;
7751     }
7752 }
7753
7754
7755 /* Resolve a SELECT TYPE statement.  */
7756
7757 static void
7758 resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
7759 {
7760   gfc_symbol *selector_type;
7761   gfc_code *body, *new_st, *if_st, *tail;
7762   gfc_code *class_is = NULL, *default_case = NULL;
7763   gfc_case *c;
7764   gfc_symtree *st;
7765   char name[GFC_MAX_SYMBOL_LEN];
7766   gfc_namespace *ns;
7767   int error = 0;
7768
7769   ns = code->ext.block.ns;
7770   gfc_resolve (ns);
7771
7772   /* Check for F03:C813.  */
7773   if (code->expr1->ts.type != BT_CLASS
7774       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
7775     {
7776       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
7777                  "at %L", &code->loc);
7778       return;
7779     }
7780
7781   if (code->expr2)
7782     {
7783       if (code->expr1->symtree->n.sym->attr.untyped)
7784         code->expr1->symtree->n.sym->ts = code->expr2->ts;
7785       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
7786     }
7787   else
7788     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
7789
7790   /* Loop over TYPE IS / CLASS IS cases.  */
7791   for (body = code->block; body; body = body->block)
7792     {
7793       c = body->ext.block.case_list;
7794
7795       /* Check F03:C815.  */
7796       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7797           && !gfc_type_is_extensible (c->ts.u.derived))
7798         {
7799           gfc_error ("Derived type '%s' at %L must be extensible",
7800                      c->ts.u.derived->name, &c->where);
7801           error++;
7802           continue;
7803         }
7804
7805       /* Check F03:C816.  */
7806       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7807           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
7808         {
7809           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
7810                      c->ts.u.derived->name, &c->where, selector_type->name);
7811           error++;
7812           continue;
7813         }
7814
7815       /* Intercept the DEFAULT case.  */
7816       if (c->ts.type == BT_UNKNOWN)
7817         {
7818           /* Check F03:C818.  */
7819           if (default_case)
7820             {
7821               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7822                          "by a second DEFAULT CASE at %L",
7823                          &default_case->ext.block.case_list->where, &c->where);
7824               error++;
7825               continue;
7826             }
7827
7828           default_case = body;
7829         }
7830     }
7831     
7832   if (error > 0)
7833     return;
7834
7835   /* Transform SELECT TYPE statement to BLOCK and associate selector to
7836      target if present.  If there are any EXIT statements referring to the
7837      SELECT TYPE construct, this is no problem because the gfc_code
7838      reference stays the same and EXIT is equally possible from the BLOCK
7839      it is changed to.  */
7840   code->op = EXEC_BLOCK;
7841   if (code->expr2)
7842     {
7843       gfc_association_list* assoc;
7844
7845       assoc = gfc_get_association_list ();
7846       assoc->st = code->expr1->symtree;
7847       assoc->target = gfc_copy_expr (code->expr2);
7848       /* assoc->variable will be set by resolve_assoc_var.  */
7849       
7850       code->ext.block.assoc = assoc;
7851       code->expr1->symtree->n.sym->assoc = assoc;
7852
7853       resolve_assoc_var (code->expr1->symtree->n.sym, false);
7854     }
7855   else
7856     code->ext.block.assoc = NULL;
7857
7858   /* Add EXEC_SELECT to switch on type.  */
7859   new_st = gfc_get_code ();
7860   new_st->op = code->op;
7861   new_st->expr1 = code->expr1;
7862   new_st->expr2 = code->expr2;
7863   new_st->block = code->block;
7864   code->expr1 = code->expr2 =  NULL;
7865   code->block = NULL;
7866   if (!ns->code)
7867     ns->code = new_st;
7868   else
7869     ns->code->next = new_st;
7870   code = new_st;
7871   code->op = EXEC_SELECT;
7872   gfc_add_vptr_component (code->expr1);
7873   gfc_add_hash_component (code->expr1);
7874
7875   /* Loop over TYPE IS / CLASS IS cases.  */
7876   for (body = code->block; body; body = body->block)
7877     {
7878       c = body->ext.block.case_list;
7879
7880       if (c->ts.type == BT_DERIVED)
7881         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
7882                                              c->ts.u.derived->hash_value);
7883
7884       else if (c->ts.type == BT_UNKNOWN)
7885         continue;
7886
7887       /* Associate temporary to selector.  This should only be done
7888          when this case is actually true, so build a new ASSOCIATE
7889          that does precisely this here (instead of using the
7890          'global' one).  */
7891
7892       if (c->ts.type == BT_CLASS)
7893         sprintf (name, "__tmp_class_%s", c->ts.u.derived->name);
7894       else
7895         sprintf (name, "__tmp_type_%s", c->ts.u.derived->name);
7896       st = gfc_find_symtree (ns->sym_root, name);
7897       gcc_assert (st->n.sym->assoc);
7898       st->n.sym->assoc->target = gfc_get_variable_expr (code->expr1->symtree);
7899       if (c->ts.type == BT_DERIVED)
7900         gfc_add_data_component (st->n.sym->assoc->target);
7901
7902       new_st = gfc_get_code ();
7903       new_st->op = EXEC_BLOCK;
7904       new_st->ext.block.ns = gfc_build_block_ns (ns);
7905       new_st->ext.block.ns->code = body->next;
7906       body->next = new_st;
7907
7908       /* Chain in the new list only if it is marked as dangling.  Otherwise
7909          there is a CASE label overlap and this is already used.  Just ignore,
7910          the error is diagonsed elsewhere.  */
7911       if (st->n.sym->assoc->dangling)
7912         {
7913           new_st->ext.block.assoc = st->n.sym->assoc;
7914           st->n.sym->assoc->dangling = 0;
7915         }
7916
7917       resolve_assoc_var (st->n.sym, false);
7918     }
7919     
7920   /* Take out CLASS IS cases for separate treatment.  */
7921   body = code;
7922   while (body && body->block)
7923     {
7924       if (body->block->ext.block.case_list->ts.type == BT_CLASS)
7925         {
7926           /* Add to class_is list.  */
7927           if (class_is == NULL)
7928             { 
7929               class_is = body->block;
7930               tail = class_is;
7931             }
7932           else
7933             {
7934               for (tail = class_is; tail->block; tail = tail->block) ;
7935               tail->block = body->block;
7936               tail = tail->block;
7937             }
7938           /* Remove from EXEC_SELECT list.  */
7939           body->block = body->block->block;
7940           tail->block = NULL;
7941         }
7942       else
7943         body = body->block;
7944     }
7945
7946   if (class_is)
7947     {
7948       gfc_symbol *vtab;
7949       
7950       if (!default_case)
7951         {
7952           /* Add a default case to hold the CLASS IS cases.  */
7953           for (tail = code; tail->block; tail = tail->block) ;
7954           tail->block = gfc_get_code ();
7955           tail = tail->block;
7956           tail->op = EXEC_SELECT_TYPE;
7957           tail->ext.block.case_list = gfc_get_case ();
7958           tail->ext.block.case_list->ts.type = BT_UNKNOWN;
7959           tail->next = NULL;
7960           default_case = tail;
7961         }
7962
7963       /* More than one CLASS IS block?  */
7964       if (class_is->block)
7965         {
7966           gfc_code **c1,*c2;
7967           bool swapped;
7968           /* Sort CLASS IS blocks by extension level.  */
7969           do
7970             {
7971               swapped = false;
7972               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
7973                 {
7974                   c2 = (*c1)->block;
7975                   /* F03:C817 (check for doubles).  */
7976                   if ((*c1)->ext.block.case_list->ts.u.derived->hash_value
7977                       == c2->ext.block.case_list->ts.u.derived->hash_value)
7978                     {
7979                       gfc_error ("Double CLASS IS block in SELECT TYPE "
7980                                  "statement at %L",
7981                                  &c2->ext.block.case_list->where);
7982                       return;
7983                     }
7984                   if ((*c1)->ext.block.case_list->ts.u.derived->attr.extension
7985                       < c2->ext.block.case_list->ts.u.derived->attr.extension)
7986                     {
7987                       /* Swap.  */
7988                       (*c1)->block = c2->block;
7989                       c2->block = *c1;
7990                       *c1 = c2;
7991                       swapped = true;
7992                     }
7993                 }
7994             }
7995           while (swapped);
7996         }
7997         
7998       /* Generate IF chain.  */
7999       if_st = gfc_get_code ();
8000       if_st->op = EXEC_IF;
8001       new_st = if_st;
8002       for (body = class_is; body; body = body->block)
8003         {
8004           new_st->block = gfc_get_code ();
8005           new_st = new_st->block;
8006           new_st->op = EXEC_IF;
8007           /* Set up IF condition: Call _gfortran_is_extension_of.  */
8008           new_st->expr1 = gfc_get_expr ();
8009           new_st->expr1->expr_type = EXPR_FUNCTION;
8010           new_st->expr1->ts.type = BT_LOGICAL;
8011           new_st->expr1->ts.kind = 4;
8012           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
8013           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
8014           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
8015           /* Set up arguments.  */
8016           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
8017           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
8018           new_st->expr1->value.function.actual->expr->where = code->loc;
8019           gfc_add_vptr_component (new_st->expr1->value.function.actual->expr);
8020           vtab = gfc_find_derived_vtab (body->ext.block.case_list->ts.u.derived);
8021           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
8022           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
8023           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
8024           new_st->next = body->next;
8025         }
8026         if (default_case->next)
8027           {
8028             new_st->block = gfc_get_code ();
8029             new_st = new_st->block;
8030             new_st->op = EXEC_IF;
8031             new_st->next = default_case->next;
8032           }
8033           
8034         /* Replace CLASS DEFAULT code by the IF chain.  */
8035         default_case->next = if_st;
8036     }
8037
8038   /* Resolve the internal code.  This can not be done earlier because
8039      it requires that the sym->assoc of selectors is set already.  */
8040   gfc_current_ns = ns;
8041   gfc_resolve_blocks (code->block, gfc_current_ns);
8042   gfc_current_ns = old_ns;
8043
8044   resolve_select (code);
8045 }
8046
8047
8048 /* Resolve a transfer statement. This is making sure that:
8049    -- a derived type being transferred has only non-pointer components
8050    -- a derived type being transferred doesn't have private components, unless 
8051       it's being transferred from the module where the type was defined
8052    -- we're not trying to transfer a whole assumed size array.  */
8053
8054 static void
8055 resolve_transfer (gfc_code *code)
8056 {
8057   gfc_typespec *ts;
8058   gfc_symbol *sym;
8059   gfc_ref *ref;
8060   gfc_expr *exp;
8061
8062   exp = code->expr1;
8063
8064   while (exp != NULL && exp->expr_type == EXPR_OP
8065          && exp->value.op.op == INTRINSIC_PARENTHESES)
8066     exp = exp->value.op.op1;
8067
8068   if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
8069                       && exp->expr_type != EXPR_FUNCTION))
8070     return;
8071
8072   /* If we are reading, the variable will be changed.  Note that
8073      code->ext.dt may be NULL if the TRANSFER is related to
8074      an INQUIRE statement -- but in this case, we are not reading, either.  */
8075   if (code->ext.dt && code->ext.dt->dt_io_kind->value.iokind == M_READ
8076       && gfc_check_vardef_context (exp, false, _("item in READ")) == FAILURE)
8077     return;
8078
8079   sym = exp->symtree->n.sym;
8080   ts = &sym->ts;
8081
8082   /* Go to actual component transferred.  */
8083   for (ref = exp->ref; ref; ref = ref->next)
8084     if (ref->type == REF_COMPONENT)
8085       ts = &ref->u.c.component->ts;
8086
8087   if (ts->type == BT_CLASS)
8088     {
8089       /* FIXME: Test for defined input/output.  */
8090       gfc_error ("Data transfer element at %L cannot be polymorphic unless "
8091                 "it is processed by a defined input/output procedure",
8092                 &code->loc);
8093       return;
8094     }
8095
8096   if (ts->type == BT_DERIVED)
8097     {
8098       /* Check that transferred derived type doesn't contain POINTER
8099          components.  */
8100       if (ts->u.derived->attr.pointer_comp)
8101         {
8102           gfc_error ("Data transfer element at %L cannot have "
8103                      "POINTER components", &code->loc);
8104           return;
8105         }
8106
8107       /* F08:C935.  */
8108       if (ts->u.derived->attr.proc_pointer_comp)
8109         {
8110           gfc_error ("Data transfer element at %L cannot have "
8111                      "procedure pointer components", &code->loc);
8112           return;
8113         }
8114
8115       if (ts->u.derived->attr.alloc_comp)
8116         {
8117           gfc_error ("Data transfer element at %L cannot have "
8118                      "ALLOCATABLE components", &code->loc);
8119           return;
8120         }
8121
8122       if (derived_inaccessible (ts->u.derived))
8123         {
8124           gfc_error ("Data transfer element at %L cannot have "
8125                      "PRIVATE components",&code->loc);
8126           return;
8127         }
8128     }
8129
8130   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
8131       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
8132     {
8133       gfc_error ("Data transfer element at %L cannot be a full reference to "
8134                  "an assumed-size array", &code->loc);
8135       return;
8136     }
8137 }
8138
8139
8140 /*********** Toplevel code resolution subroutines ***********/
8141
8142 /* Find the set of labels that are reachable from this block.  We also
8143    record the last statement in each block.  */
8144      
8145 static void
8146 find_reachable_labels (gfc_code *block)
8147 {
8148   gfc_code *c;
8149
8150   if (!block)
8151     return;
8152
8153   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
8154
8155   /* Collect labels in this block.  We don't keep those corresponding
8156      to END {IF|SELECT}, these are checked in resolve_branch by going
8157      up through the code_stack.  */
8158   for (c = block; c; c = c->next)
8159     {
8160       if (c->here && c->op != EXEC_END_BLOCK)
8161         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
8162     }
8163
8164   /* Merge with labels from parent block.  */
8165   if (cs_base->prev)
8166     {
8167       gcc_assert (cs_base->prev->reachable_labels);
8168       bitmap_ior_into (cs_base->reachable_labels,
8169                        cs_base->prev->reachable_labels);
8170     }
8171 }
8172
8173
8174 static void
8175 resolve_sync (gfc_code *code)
8176 {
8177   /* Check imageset. The * case matches expr1 == NULL.  */
8178   if (code->expr1)
8179     {
8180       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
8181         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
8182                    "INTEGER expression", &code->expr1->where);
8183       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
8184           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
8185         gfc_error ("Imageset argument at %L must between 1 and num_images()",
8186                    &code->expr1->where);
8187       else if (code->expr1->expr_type == EXPR_ARRAY
8188                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
8189         {
8190            gfc_constructor *cons;
8191            cons = gfc_constructor_first (code->expr1->value.constructor);
8192            for (; cons; cons = gfc_constructor_next (cons))
8193              if (cons->expr->expr_type == EXPR_CONSTANT
8194                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
8195                gfc_error ("Imageset argument at %L must between 1 and "
8196                           "num_images()", &cons->expr->where);
8197         }
8198     }
8199
8200   /* Check STAT.  */
8201   if (code->expr2
8202       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8203           || code->expr2->expr_type != EXPR_VARIABLE))
8204     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8205                &code->expr2->where);
8206
8207   /* Check ERRMSG.  */
8208   if (code->expr3
8209       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8210           || code->expr3->expr_type != EXPR_VARIABLE))
8211     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8212                &code->expr3->where);
8213 }
8214
8215
8216 /* Given a branch to a label, see if the branch is conforming.
8217    The code node describes where the branch is located.  */
8218
8219 static void
8220 resolve_branch (gfc_st_label *label, gfc_code *code)
8221 {
8222   code_stack *stack;
8223
8224   if (label == NULL)
8225     return;
8226
8227   /* Step one: is this a valid branching target?  */
8228
8229   if (label->defined == ST_LABEL_UNKNOWN)
8230     {
8231       gfc_error ("Label %d referenced at %L is never defined", label->value,
8232                  &label->where);
8233       return;
8234     }
8235
8236   if (label->defined != ST_LABEL_TARGET)
8237     {
8238       gfc_error ("Statement at %L is not a valid branch target statement "
8239                  "for the branch statement at %L", &label->where, &code->loc);
8240       return;
8241     }
8242
8243   /* Step two: make sure this branch is not a branch to itself ;-)  */
8244
8245   if (code->here == label)
8246     {
8247       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
8248       return;
8249     }
8250
8251   /* Step three:  See if the label is in the same block as the
8252      branching statement.  The hard work has been done by setting up
8253      the bitmap reachable_labels.  */
8254
8255   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8256     {
8257       /* Check now whether there is a CRITICAL construct; if so, check
8258          whether the label is still visible outside of the CRITICAL block,
8259          which is invalid.  */
8260       for (stack = cs_base; stack; stack = stack->prev)
8261         if (stack->current->op == EXEC_CRITICAL
8262             && bitmap_bit_p (stack->reachable_labels, label->value))
8263           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8264                       " at %L", &code->loc, &label->where);
8265
8266       return;
8267     }
8268
8269   /* Step four:  If we haven't found the label in the bitmap, it may
8270     still be the label of the END of the enclosing block, in which
8271     case we find it by going up the code_stack.  */
8272
8273   for (stack = cs_base; stack; stack = stack->prev)
8274     {
8275       if (stack->current->next && stack->current->next->here == label)
8276         break;
8277       if (stack->current->op == EXEC_CRITICAL)
8278         {
8279           /* Note: A label at END CRITICAL does not leave the CRITICAL
8280              construct as END CRITICAL is still part of it.  */
8281           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8282                       " at %L", &code->loc, &label->where);
8283           return;
8284         }
8285     }
8286
8287   if (stack)
8288     {
8289       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
8290       return;
8291     }
8292
8293   /* The label is not in an enclosing block, so illegal.  This was
8294      allowed in Fortran 66, so we allow it as extension.  No
8295      further checks are necessary in this case.  */
8296   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
8297                   "as the GOTO statement at %L", &label->where,
8298                   &code->loc);
8299   return;
8300 }
8301
8302
8303 /* Check whether EXPR1 has the same shape as EXPR2.  */
8304
8305 static gfc_try
8306 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8307 {
8308   mpz_t shape[GFC_MAX_DIMENSIONS];
8309   mpz_t shape2[GFC_MAX_DIMENSIONS];
8310   gfc_try result = FAILURE;
8311   int i;
8312
8313   /* Compare the rank.  */
8314   if (expr1->rank != expr2->rank)
8315     return result;
8316
8317   /* Compare the size of each dimension.  */
8318   for (i=0; i<expr1->rank; i++)
8319     {
8320       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
8321         goto ignore;
8322
8323       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
8324         goto ignore;
8325
8326       if (mpz_cmp (shape[i], shape2[i]))
8327         goto over;
8328     }
8329
8330   /* When either of the two expression is an assumed size array, we
8331      ignore the comparison of dimension sizes.  */
8332 ignore:
8333   result = SUCCESS;
8334
8335 over:
8336   for (i--; i >= 0; i--)
8337     {
8338       mpz_clear (shape[i]);
8339       mpz_clear (shape2[i]);
8340     }
8341   return result;
8342 }
8343
8344
8345 /* Check whether a WHERE assignment target or a WHERE mask expression
8346    has the same shape as the outmost WHERE mask expression.  */
8347
8348 static void
8349 resolve_where (gfc_code *code, gfc_expr *mask)
8350 {
8351   gfc_code *cblock;
8352   gfc_code *cnext;
8353   gfc_expr *e = NULL;
8354
8355   cblock = code->block;
8356
8357   /* Store the first WHERE mask-expr of the WHERE statement or construct.
8358      In case of nested WHERE, only the outmost one is stored.  */
8359   if (mask == NULL) /* outmost WHERE */
8360     e = cblock->expr1;
8361   else /* inner WHERE */
8362     e = mask;
8363
8364   while (cblock)
8365     {
8366       if (cblock->expr1)
8367         {
8368           /* Check if the mask-expr has a consistent shape with the
8369              outmost WHERE mask-expr.  */
8370           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
8371             gfc_error ("WHERE mask at %L has inconsistent shape",
8372                        &cblock->expr1->where);
8373          }
8374
8375       /* the assignment statement of a WHERE statement, or the first
8376          statement in where-body-construct of a WHERE construct */
8377       cnext = cblock->next;
8378       while (cnext)
8379         {
8380           switch (cnext->op)
8381             {
8382             /* WHERE assignment statement */
8383             case EXEC_ASSIGN:
8384
8385               /* Check shape consistent for WHERE assignment target.  */
8386               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
8387                gfc_error ("WHERE assignment target at %L has "
8388                           "inconsistent shape", &cnext->expr1->where);
8389               break;
8390
8391   
8392             case EXEC_ASSIGN_CALL:
8393               resolve_call (cnext);
8394               if (!cnext->resolved_sym->attr.elemental)
8395                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8396                           &cnext->ext.actual->expr->where);
8397               break;
8398
8399             /* WHERE or WHERE construct is part of a where-body-construct */
8400             case EXEC_WHERE:
8401               resolve_where (cnext, e);
8402               break;
8403
8404             default:
8405               gfc_error ("Unsupported statement inside WHERE at %L",
8406                          &cnext->loc);
8407             }
8408          /* the next statement within the same where-body-construct */
8409          cnext = cnext->next;
8410        }
8411     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8412     cblock = cblock->block;
8413   }
8414 }
8415
8416
8417 /* Resolve assignment in FORALL construct.
8418    NVAR is the number of FORALL index variables, and VAR_EXPR records the
8419    FORALL index variables.  */
8420
8421 static void
8422 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8423 {
8424   int n;
8425
8426   for (n = 0; n < nvar; n++)
8427     {
8428       gfc_symbol *forall_index;
8429
8430       forall_index = var_expr[n]->symtree->n.sym;
8431
8432       /* Check whether the assignment target is one of the FORALL index
8433          variable.  */
8434       if ((code->expr1->expr_type == EXPR_VARIABLE)
8435           && (code->expr1->symtree->n.sym == forall_index))
8436         gfc_error ("Assignment to a FORALL index variable at %L",
8437                    &code->expr1->where);
8438       else
8439         {
8440           /* If one of the FORALL index variables doesn't appear in the
8441              assignment variable, then there could be a many-to-one
8442              assignment.  Emit a warning rather than an error because the
8443              mask could be resolving this problem.  */
8444           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
8445             gfc_warning ("The FORALL with index '%s' is not used on the "
8446                          "left side of the assignment at %L and so might "
8447                          "cause multiple assignment to this object",
8448                          var_expr[n]->symtree->name, &code->expr1->where);
8449         }
8450     }
8451 }
8452
8453
8454 /* Resolve WHERE statement in FORALL construct.  */
8455
8456 static void
8457 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
8458                                   gfc_expr **var_expr)
8459 {
8460   gfc_code *cblock;
8461   gfc_code *cnext;
8462
8463   cblock = code->block;
8464   while (cblock)
8465     {
8466       /* the assignment statement of a WHERE statement, or the first
8467          statement in where-body-construct of a WHERE construct */
8468       cnext = cblock->next;
8469       while (cnext)
8470         {
8471           switch (cnext->op)
8472             {
8473             /* WHERE assignment statement */
8474             case EXEC_ASSIGN:
8475               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
8476               break;
8477   
8478             /* WHERE operator assignment statement */
8479             case EXEC_ASSIGN_CALL:
8480               resolve_call (cnext);
8481               if (!cnext->resolved_sym->attr.elemental)
8482                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8483                           &cnext->ext.actual->expr->where);
8484               break;
8485
8486             /* WHERE or WHERE construct is part of a where-body-construct */
8487             case EXEC_WHERE:
8488               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
8489               break;
8490
8491             default:
8492               gfc_error ("Unsupported statement inside WHERE at %L",
8493                          &cnext->loc);
8494             }
8495           /* the next statement within the same where-body-construct */
8496           cnext = cnext->next;
8497         }
8498       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8499       cblock = cblock->block;
8500     }
8501 }
8502
8503
8504 /* Traverse the FORALL body to check whether the following errors exist:
8505    1. For assignment, check if a many-to-one assignment happens.
8506    2. For WHERE statement, check the WHERE body to see if there is any
8507       many-to-one assignment.  */
8508
8509 static void
8510 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
8511 {
8512   gfc_code *c;
8513
8514   c = code->block->next;
8515   while (c)
8516     {
8517       switch (c->op)
8518         {
8519         case EXEC_ASSIGN:
8520         case EXEC_POINTER_ASSIGN:
8521           gfc_resolve_assign_in_forall (c, nvar, var_expr);
8522           break;
8523
8524         case EXEC_ASSIGN_CALL:
8525           resolve_call (c);
8526           break;
8527
8528         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
8529            there is no need to handle it here.  */
8530         case EXEC_FORALL:
8531           break;
8532         case EXEC_WHERE:
8533           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
8534           break;
8535         default:
8536           break;
8537         }
8538       /* The next statement in the FORALL body.  */
8539       c = c->next;
8540     }
8541 }
8542
8543
8544 /* Counts the number of iterators needed inside a forall construct, including
8545    nested forall constructs. This is used to allocate the needed memory 
8546    in gfc_resolve_forall.  */
8547
8548 static int 
8549 gfc_count_forall_iterators (gfc_code *code)
8550 {
8551   int max_iters, sub_iters, current_iters;
8552   gfc_forall_iterator *fa;
8553
8554   gcc_assert(code->op == EXEC_FORALL);
8555   max_iters = 0;
8556   current_iters = 0;
8557
8558   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8559     current_iters ++;
8560   
8561   code = code->block->next;
8562
8563   while (code)
8564     {          
8565       if (code->op == EXEC_FORALL)
8566         {
8567           sub_iters = gfc_count_forall_iterators (code);
8568           if (sub_iters > max_iters)
8569             max_iters = sub_iters;
8570         }
8571       code = code->next;
8572     }
8573
8574   return current_iters + max_iters;
8575 }
8576
8577
8578 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8579    gfc_resolve_forall_body to resolve the FORALL body.  */
8580
8581 static void
8582 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8583 {
8584   static gfc_expr **var_expr;
8585   static int total_var = 0;
8586   static int nvar = 0;
8587   int old_nvar, tmp;
8588   gfc_forall_iterator *fa;
8589   int i;
8590
8591   old_nvar = nvar;
8592
8593   /* Start to resolve a FORALL construct   */
8594   if (forall_save == 0)
8595     {
8596       /* Count the total number of FORALL index in the nested FORALL
8597          construct in order to allocate the VAR_EXPR with proper size.  */
8598       total_var = gfc_count_forall_iterators (code);
8599
8600       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8601       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
8602     }
8603
8604   /* The information about FORALL iterator, including FORALL index start, end
8605      and stride. The FORALL index can not appear in start, end or stride.  */
8606   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8607     {
8608       /* Check if any outer FORALL index name is the same as the current
8609          one.  */
8610       for (i = 0; i < nvar; i++)
8611         {
8612           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8613             {
8614               gfc_error ("An outer FORALL construct already has an index "
8615                          "with this name %L", &fa->var->where);
8616             }
8617         }
8618
8619       /* Record the current FORALL index.  */
8620       var_expr[nvar] = gfc_copy_expr (fa->var);
8621
8622       nvar++;
8623
8624       /* No memory leak.  */
8625       gcc_assert (nvar <= total_var);
8626     }
8627
8628   /* Resolve the FORALL body.  */
8629   gfc_resolve_forall_body (code, nvar, var_expr);
8630
8631   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8632   gfc_resolve_blocks (code->block, ns);
8633
8634   tmp = nvar;
8635   nvar = old_nvar;
8636   /* Free only the VAR_EXPRs allocated in this frame.  */
8637   for (i = nvar; i < tmp; i++)
8638      gfc_free_expr (var_expr[i]);
8639
8640   if (nvar == 0)
8641     {
8642       /* We are in the outermost FORALL construct.  */
8643       gcc_assert (forall_save == 0);
8644
8645       /* VAR_EXPR is not needed any more.  */
8646       gfc_free (var_expr);
8647       total_var = 0;
8648     }
8649 }
8650
8651
8652 /* Resolve a BLOCK construct statement.  */
8653
8654 static void
8655 resolve_block_construct (gfc_code* code)
8656 {
8657   /* Resolve the BLOCK's namespace.  */
8658   gfc_resolve (code->ext.block.ns);
8659
8660   /* For an ASSOCIATE block, the associations (and their targets) are already
8661      resolved during resolve_symbol.  */
8662 }
8663
8664
8665 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
8666    DO code nodes.  */
8667
8668 static void resolve_code (gfc_code *, gfc_namespace *);
8669
8670 void
8671 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8672 {
8673   gfc_try t;
8674
8675   for (; b; b = b->block)
8676     {
8677       t = gfc_resolve_expr (b->expr1);
8678       if (gfc_resolve_expr (b->expr2) == FAILURE)
8679         t = FAILURE;
8680
8681       switch (b->op)
8682         {
8683         case EXEC_IF:
8684           if (t == SUCCESS && b->expr1 != NULL
8685               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8686             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8687                        &b->expr1->where);
8688           break;
8689
8690         case EXEC_WHERE:
8691           if (t == SUCCESS
8692               && b->expr1 != NULL
8693               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8694             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8695                        &b->expr1->where);
8696           break;
8697
8698         case EXEC_GOTO:
8699           resolve_branch (b->label1, b);
8700           break;
8701
8702         case EXEC_BLOCK:
8703           resolve_block_construct (b);
8704           break;
8705
8706         case EXEC_SELECT:
8707         case EXEC_SELECT_TYPE:
8708         case EXEC_FORALL:
8709         case EXEC_DO:
8710         case EXEC_DO_WHILE:
8711         case EXEC_CRITICAL:
8712         case EXEC_READ:
8713         case EXEC_WRITE:
8714         case EXEC_IOLENGTH:
8715         case EXEC_WAIT:
8716           break;
8717
8718         case EXEC_OMP_ATOMIC:
8719         case EXEC_OMP_CRITICAL:
8720         case EXEC_OMP_DO:
8721         case EXEC_OMP_MASTER:
8722         case EXEC_OMP_ORDERED:
8723         case EXEC_OMP_PARALLEL:
8724         case EXEC_OMP_PARALLEL_DO:
8725         case EXEC_OMP_PARALLEL_SECTIONS:
8726         case EXEC_OMP_PARALLEL_WORKSHARE:
8727         case EXEC_OMP_SECTIONS:
8728         case EXEC_OMP_SINGLE:
8729         case EXEC_OMP_TASK:
8730         case EXEC_OMP_TASKWAIT:
8731         case EXEC_OMP_WORKSHARE:
8732           break;
8733
8734         default:
8735           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
8736         }
8737
8738       resolve_code (b->next, ns);
8739     }
8740 }
8741
8742
8743 /* Does everything to resolve an ordinary assignment.  Returns true
8744    if this is an interface assignment.  */
8745 static bool
8746 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
8747 {
8748   bool rval = false;
8749   gfc_expr *lhs;
8750   gfc_expr *rhs;
8751   int llen = 0;
8752   int rlen = 0;
8753   int n;
8754   gfc_ref *ref;
8755
8756   if (gfc_extend_assign (code, ns) == SUCCESS)
8757     {
8758       gfc_expr** rhsptr;
8759
8760       if (code->op == EXEC_ASSIGN_CALL)
8761         {
8762           lhs = code->ext.actual->expr;
8763           rhsptr = &code->ext.actual->next->expr;
8764         }
8765       else
8766         {
8767           gfc_actual_arglist* args;
8768           gfc_typebound_proc* tbp;
8769
8770           gcc_assert (code->op == EXEC_COMPCALL);
8771
8772           args = code->expr1->value.compcall.actual;
8773           lhs = args->expr;
8774           rhsptr = &args->next->expr;
8775
8776           tbp = code->expr1->value.compcall.tbp;
8777           gcc_assert (!tbp->is_generic);
8778         }
8779
8780       /* Make a temporary rhs when there is a default initializer
8781          and rhs is the same symbol as the lhs.  */
8782       if ((*rhsptr)->expr_type == EXPR_VARIABLE
8783             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
8784             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
8785             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
8786         *rhsptr = gfc_get_parentheses (*rhsptr);
8787
8788       return true;
8789     }
8790
8791   lhs = code->expr1;
8792   rhs = code->expr2;
8793
8794   if (rhs->is_boz
8795       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
8796                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
8797                          &code->loc) == FAILURE)
8798     return false;
8799
8800   /* Handle the case of a BOZ literal on the RHS.  */
8801   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
8802     {
8803       int rc;
8804       if (gfc_option.warn_surprising)
8805         gfc_warning ("BOZ literal at %L is bitwise transferred "
8806                      "non-integer symbol '%s'", &code->loc,
8807                      lhs->symtree->n.sym->name);
8808
8809       if (!gfc_convert_boz (rhs, &lhs->ts))
8810         return false;
8811       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
8812         {
8813           if (rc == ARITH_UNDERFLOW)
8814             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
8815                        ". This check can be disabled with the option "
8816                        "-fno-range-check", &rhs->where);
8817           else if (rc == ARITH_OVERFLOW)
8818             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
8819                        ". This check can be disabled with the option "
8820                        "-fno-range-check", &rhs->where);
8821           else if (rc == ARITH_NAN)
8822             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
8823                        ". This check can be disabled with the option "
8824                        "-fno-range-check", &rhs->where);
8825           return false;
8826         }
8827     }
8828
8829   if (lhs->ts.type == BT_CHARACTER
8830         && gfc_option.warn_character_truncation)
8831     {
8832       if (lhs->ts.u.cl != NULL
8833             && lhs->ts.u.cl->length != NULL
8834             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8835         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
8836
8837       if (rhs->expr_type == EXPR_CONSTANT)
8838         rlen = rhs->value.character.length;
8839
8840       else if (rhs->ts.u.cl != NULL
8841                  && rhs->ts.u.cl->length != NULL
8842                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8843         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
8844
8845       if (rlen && llen && rlen > llen)
8846         gfc_warning_now ("CHARACTER expression will be truncated "
8847                          "in assignment (%d/%d) at %L",
8848                          llen, rlen, &code->loc);
8849     }
8850
8851   /* Ensure that a vector index expression for the lvalue is evaluated
8852      to a temporary if the lvalue symbol is referenced in it.  */
8853   if (lhs->rank)
8854     {
8855       for (ref = lhs->ref; ref; ref= ref->next)
8856         if (ref->type == REF_ARRAY)
8857           {
8858             for (n = 0; n < ref->u.ar.dimen; n++)
8859               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
8860                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
8861                                            ref->u.ar.start[n]))
8862                 ref->u.ar.start[n]
8863                         = gfc_get_parentheses (ref->u.ar.start[n]);
8864           }
8865     }
8866
8867   if (gfc_pure (NULL))
8868     {
8869       if (lhs->ts.type == BT_DERIVED
8870             && lhs->expr_type == EXPR_VARIABLE
8871             && lhs->ts.u.derived->attr.pointer_comp
8872             && rhs->expr_type == EXPR_VARIABLE
8873             && (gfc_impure_variable (rhs->symtree->n.sym)
8874                 || gfc_is_coindexed (rhs)))
8875         {
8876           /* F2008, C1283.  */
8877           if (gfc_is_coindexed (rhs))
8878             gfc_error ("Coindexed expression at %L is assigned to "
8879                         "a derived type variable with a POINTER "
8880                         "component in a PURE procedure",
8881                         &rhs->where);
8882           else
8883             gfc_error ("The impure variable at %L is assigned to "
8884                         "a derived type variable with a POINTER "
8885                         "component in a PURE procedure (12.6)",
8886                         &rhs->where);
8887           return rval;
8888         }
8889
8890       /* Fortran 2008, C1283.  */
8891       if (gfc_is_coindexed (lhs))
8892         {
8893           gfc_error ("Assignment to coindexed variable at %L in a PURE "
8894                      "procedure", &rhs->where);
8895           return rval;
8896         }
8897     }
8898
8899   if (gfc_implicit_pure (NULL))
8900     {
8901       if (lhs->expr_type == EXPR_VARIABLE
8902             && lhs->symtree->n.sym != gfc_current_ns->proc_name
8903             && lhs->symtree->n.sym->ns != gfc_current_ns)
8904         gfc_current_ns->proc_name->attr.implicit_pure = 0;
8905
8906       if (lhs->ts.type == BT_DERIVED
8907             && lhs->expr_type == EXPR_VARIABLE
8908             && lhs->ts.u.derived->attr.pointer_comp
8909             && rhs->expr_type == EXPR_VARIABLE
8910             && (gfc_impure_variable (rhs->symtree->n.sym)
8911                 || gfc_is_coindexed (rhs)))
8912         gfc_current_ns->proc_name->attr.implicit_pure = 0;
8913
8914       /* Fortran 2008, C1283.  */
8915       if (gfc_is_coindexed (lhs))
8916         gfc_current_ns->proc_name->attr.implicit_pure = 0;
8917     }
8918
8919   /* F03:7.4.1.2.  */
8920   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
8921      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
8922   if (lhs->ts.type == BT_CLASS)
8923     {
8924       gfc_error ("Variable must not be polymorphic in assignment at %L",
8925                  &lhs->where);
8926       return false;
8927     }
8928
8929   /* F2008, Section 7.2.1.2.  */
8930   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
8931     {
8932       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
8933                  "component in assignment at %L", &lhs->where);
8934       return false;
8935     }
8936
8937   gfc_check_assign (lhs, rhs, 1);
8938   return false;
8939 }
8940
8941
8942 /* Given a block of code, recursively resolve everything pointed to by this
8943    code block.  */
8944
8945 static void
8946 resolve_code (gfc_code *code, gfc_namespace *ns)
8947 {
8948   int omp_workshare_save;
8949   int forall_save;
8950   code_stack frame;
8951   gfc_try t;
8952
8953   frame.prev = cs_base;
8954   frame.head = code;
8955   cs_base = &frame;
8956
8957   find_reachable_labels (code);
8958
8959   for (; code; code = code->next)
8960     {
8961       frame.current = code;
8962       forall_save = forall_flag;
8963
8964       if (code->op == EXEC_FORALL)
8965         {
8966           forall_flag = 1;
8967           gfc_resolve_forall (code, ns, forall_save);
8968           forall_flag = 2;
8969         }
8970       else if (code->block)
8971         {
8972           omp_workshare_save = -1;
8973           switch (code->op)
8974             {
8975             case EXEC_OMP_PARALLEL_WORKSHARE:
8976               omp_workshare_save = omp_workshare_flag;
8977               omp_workshare_flag = 1;
8978               gfc_resolve_omp_parallel_blocks (code, ns);
8979               break;
8980             case EXEC_OMP_PARALLEL:
8981             case EXEC_OMP_PARALLEL_DO:
8982             case EXEC_OMP_PARALLEL_SECTIONS:
8983             case EXEC_OMP_TASK:
8984               omp_workshare_save = omp_workshare_flag;
8985               omp_workshare_flag = 0;
8986               gfc_resolve_omp_parallel_blocks (code, ns);
8987               break;
8988             case EXEC_OMP_DO:
8989               gfc_resolve_omp_do_blocks (code, ns);
8990               break;
8991             case EXEC_SELECT_TYPE:
8992               /* Blocks are handled in resolve_select_type because we have
8993                  to transform the SELECT TYPE into ASSOCIATE first.  */
8994               break;
8995             case EXEC_OMP_WORKSHARE:
8996               omp_workshare_save = omp_workshare_flag;
8997               omp_workshare_flag = 1;
8998               /* FALLTHROUGH */
8999             default:
9000               gfc_resolve_blocks (code->block, ns);
9001               break;
9002             }
9003
9004           if (omp_workshare_save != -1)
9005             omp_workshare_flag = omp_workshare_save;
9006         }
9007
9008       t = SUCCESS;
9009       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
9010         t = gfc_resolve_expr (code->expr1);
9011       forall_flag = forall_save;
9012
9013       if (gfc_resolve_expr (code->expr2) == FAILURE)
9014         t = FAILURE;
9015
9016       if (code->op == EXEC_ALLOCATE
9017           && gfc_resolve_expr (code->expr3) == FAILURE)
9018         t = FAILURE;
9019
9020       switch (code->op)
9021         {
9022         case EXEC_NOP:
9023         case EXEC_END_BLOCK:
9024         case EXEC_CYCLE:
9025         case EXEC_PAUSE:
9026         case EXEC_STOP:
9027         case EXEC_ERROR_STOP:
9028         case EXEC_EXIT:
9029         case EXEC_CONTINUE:
9030         case EXEC_DT_END:
9031         case EXEC_ASSIGN_CALL:
9032         case EXEC_CRITICAL:
9033           break;
9034
9035         case EXEC_SYNC_ALL:
9036         case EXEC_SYNC_IMAGES:
9037         case EXEC_SYNC_MEMORY:
9038           resolve_sync (code);
9039           break;
9040
9041         case EXEC_ENTRY:
9042           /* Keep track of which entry we are up to.  */
9043           current_entry_id = code->ext.entry->id;
9044           break;
9045
9046         case EXEC_WHERE:
9047           resolve_where (code, NULL);
9048           break;
9049
9050         case EXEC_GOTO:
9051           if (code->expr1 != NULL)
9052             {
9053               if (code->expr1->ts.type != BT_INTEGER)
9054                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
9055                            "INTEGER variable", &code->expr1->where);
9056               else if (code->expr1->symtree->n.sym->attr.assign != 1)
9057                 gfc_error ("Variable '%s' has not been assigned a target "
9058                            "label at %L", code->expr1->symtree->n.sym->name,
9059                            &code->expr1->where);
9060             }
9061           else
9062             resolve_branch (code->label1, code);
9063           break;
9064
9065         case EXEC_RETURN:
9066           if (code->expr1 != NULL
9067                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
9068             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
9069                        "INTEGER return specifier", &code->expr1->where);
9070           break;
9071
9072         case EXEC_INIT_ASSIGN:
9073         case EXEC_END_PROCEDURE:
9074           break;
9075
9076         case EXEC_ASSIGN:
9077           if (t == FAILURE)
9078             break;
9079
9080           if (gfc_check_vardef_context (code->expr1, false, _("assignment"))
9081                 == FAILURE)
9082             break;
9083
9084           if (resolve_ordinary_assign (code, ns))
9085             {
9086               if (code->op == EXEC_COMPCALL)
9087                 goto compcall;
9088               else
9089                 goto call;
9090             }
9091           break;
9092
9093         case EXEC_LABEL_ASSIGN:
9094           if (code->label1->defined == ST_LABEL_UNKNOWN)
9095             gfc_error ("Label %d referenced at %L is never defined",
9096                        code->label1->value, &code->label1->where);
9097           if (t == SUCCESS
9098               && (code->expr1->expr_type != EXPR_VARIABLE
9099                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
9100                   || code->expr1->symtree->n.sym->ts.kind
9101                      != gfc_default_integer_kind
9102                   || code->expr1->symtree->n.sym->as != NULL))
9103             gfc_error ("ASSIGN statement at %L requires a scalar "
9104                        "default INTEGER variable", &code->expr1->where);
9105           break;
9106
9107         case EXEC_POINTER_ASSIGN:
9108           {
9109             gfc_expr* e;
9110
9111             if (t == FAILURE)
9112               break;
9113
9114             /* This is both a variable definition and pointer assignment
9115                context, so check both of them.  For rank remapping, a final
9116                array ref may be present on the LHS and fool gfc_expr_attr
9117                used in gfc_check_vardef_context.  Remove it.  */
9118             e = remove_last_array_ref (code->expr1);
9119             t = gfc_check_vardef_context (e, true, _("pointer assignment"));
9120             if (t == SUCCESS)
9121               t = gfc_check_vardef_context (e, false, _("pointer assignment"));
9122             gfc_free_expr (e);
9123             if (t == FAILURE)
9124               break;
9125
9126             gfc_check_pointer_assign (code->expr1, code->expr2);
9127             break;
9128           }
9129
9130         case EXEC_ARITHMETIC_IF:
9131           if (t == SUCCESS
9132               && code->expr1->ts.type != BT_INTEGER
9133               && code->expr1->ts.type != BT_REAL)
9134             gfc_error ("Arithmetic IF statement at %L requires a numeric "
9135                        "expression", &code->expr1->where);
9136
9137           resolve_branch (code->label1, code);
9138           resolve_branch (code->label2, code);
9139           resolve_branch (code->label3, code);
9140           break;
9141
9142         case EXEC_IF:
9143           if (t == SUCCESS && code->expr1 != NULL
9144               && (code->expr1->ts.type != BT_LOGICAL
9145                   || code->expr1->rank != 0))
9146             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9147                        &code->expr1->where);
9148           break;
9149
9150         case EXEC_CALL:
9151         call:
9152           resolve_call (code);
9153           break;
9154
9155         case EXEC_COMPCALL:
9156         compcall:
9157           resolve_typebound_subroutine (code);
9158           break;
9159
9160         case EXEC_CALL_PPC:
9161           resolve_ppc_call (code);
9162           break;
9163
9164         case EXEC_SELECT:
9165           /* Select is complicated. Also, a SELECT construct could be
9166              a transformed computed GOTO.  */
9167           resolve_select (code);
9168           break;
9169
9170         case EXEC_SELECT_TYPE:
9171           resolve_select_type (code, ns);
9172           break;
9173
9174         case EXEC_BLOCK:
9175           resolve_block_construct (code);
9176           break;
9177
9178         case EXEC_DO:
9179           if (code->ext.iterator != NULL)
9180             {
9181               gfc_iterator *iter = code->ext.iterator;
9182               if (gfc_resolve_iterator (iter, true) != FAILURE)
9183                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
9184             }
9185           break;
9186
9187         case EXEC_DO_WHILE:
9188           if (code->expr1 == NULL)
9189             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
9190           if (t == SUCCESS
9191               && (code->expr1->rank != 0
9192                   || code->expr1->ts.type != BT_LOGICAL))
9193             gfc_error ("Exit condition of DO WHILE loop at %L must be "
9194                        "a scalar LOGICAL expression", &code->expr1->where);
9195           break;
9196
9197         case EXEC_ALLOCATE:
9198           if (t == SUCCESS)
9199             resolve_allocate_deallocate (code, "ALLOCATE");
9200
9201           break;
9202
9203         case EXEC_DEALLOCATE:
9204           if (t == SUCCESS)
9205             resolve_allocate_deallocate (code, "DEALLOCATE");
9206
9207           break;
9208
9209         case EXEC_OPEN:
9210           if (gfc_resolve_open (code->ext.open) == FAILURE)
9211             break;
9212
9213           resolve_branch (code->ext.open->err, code);
9214           break;
9215
9216         case EXEC_CLOSE:
9217           if (gfc_resolve_close (code->ext.close) == FAILURE)
9218             break;
9219
9220           resolve_branch (code->ext.close->err, code);
9221           break;
9222
9223         case EXEC_BACKSPACE:
9224         case EXEC_ENDFILE:
9225         case EXEC_REWIND:
9226         case EXEC_FLUSH:
9227           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
9228             break;
9229
9230           resolve_branch (code->ext.filepos->err, code);
9231           break;
9232
9233         case EXEC_INQUIRE:
9234           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9235               break;
9236
9237           resolve_branch (code->ext.inquire->err, code);
9238           break;
9239
9240         case EXEC_IOLENGTH:
9241           gcc_assert (code->ext.inquire != NULL);
9242           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9243             break;
9244
9245           resolve_branch (code->ext.inquire->err, code);
9246           break;
9247
9248         case EXEC_WAIT:
9249           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
9250             break;
9251
9252           resolve_branch (code->ext.wait->err, code);
9253           resolve_branch (code->ext.wait->end, code);
9254           resolve_branch (code->ext.wait->eor, code);
9255           break;
9256
9257         case EXEC_READ:
9258         case EXEC_WRITE:
9259           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
9260             break;
9261
9262           resolve_branch (code->ext.dt->err, code);
9263           resolve_branch (code->ext.dt->end, code);
9264           resolve_branch (code->ext.dt->eor, code);
9265           break;
9266
9267         case EXEC_TRANSFER:
9268           resolve_transfer (code);
9269           break;
9270
9271         case EXEC_FORALL:
9272           resolve_forall_iterators (code->ext.forall_iterator);
9273
9274           if (code->expr1 != NULL
9275               && (code->expr1->ts.type != BT_LOGICAL || code->expr1->rank))
9276             gfc_error ("FORALL mask clause at %L requires a scalar LOGICAL "
9277                        "expression", &code->expr1->where);
9278           break;
9279
9280         case EXEC_OMP_ATOMIC:
9281         case EXEC_OMP_BARRIER:
9282         case EXEC_OMP_CRITICAL:
9283         case EXEC_OMP_FLUSH:
9284         case EXEC_OMP_DO:
9285         case EXEC_OMP_MASTER:
9286         case EXEC_OMP_ORDERED:
9287         case EXEC_OMP_SECTIONS:
9288         case EXEC_OMP_SINGLE:
9289         case EXEC_OMP_TASKWAIT:
9290         case EXEC_OMP_WORKSHARE:
9291           gfc_resolve_omp_directive (code, ns);
9292           break;
9293
9294         case EXEC_OMP_PARALLEL:
9295         case EXEC_OMP_PARALLEL_DO:
9296         case EXEC_OMP_PARALLEL_SECTIONS:
9297         case EXEC_OMP_PARALLEL_WORKSHARE:
9298         case EXEC_OMP_TASK:
9299           omp_workshare_save = omp_workshare_flag;
9300           omp_workshare_flag = 0;
9301           gfc_resolve_omp_directive (code, ns);
9302           omp_workshare_flag = omp_workshare_save;
9303           break;
9304
9305         default:
9306           gfc_internal_error ("resolve_code(): Bad statement code");
9307         }
9308     }
9309
9310   cs_base = frame.prev;
9311 }
9312
9313
9314 /* Resolve initial values and make sure they are compatible with
9315    the variable.  */
9316
9317 static void
9318 resolve_values (gfc_symbol *sym)
9319 {
9320   gfc_try t;
9321
9322   if (sym->value == NULL)
9323     return;
9324
9325   if (sym->value->expr_type == EXPR_STRUCTURE)
9326     t= resolve_structure_cons (sym->value, 1);
9327   else 
9328     t = gfc_resolve_expr (sym->value);
9329
9330   if (t == FAILURE)
9331     return;
9332
9333   gfc_check_assign_symbol (sym, sym->value);
9334 }
9335
9336
9337 /* Verify the binding labels for common blocks that are BIND(C).  The label
9338    for a BIND(C) common block must be identical in all scoping units in which
9339    the common block is declared.  Further, the binding label can not collide
9340    with any other global entity in the program.  */
9341
9342 static void
9343 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
9344 {
9345   if (comm_block_tree->n.common->is_bind_c == 1)
9346     {
9347       gfc_gsymbol *binding_label_gsym;
9348       gfc_gsymbol *comm_name_gsym;
9349
9350       /* See if a global symbol exists by the common block's name.  It may
9351          be NULL if the common block is use-associated.  */
9352       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
9353                                          comm_block_tree->n.common->name);
9354       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
9355         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
9356                    "with the global entity '%s' at %L",
9357                    comm_block_tree->n.common->binding_label,
9358                    comm_block_tree->n.common->name,
9359                    &(comm_block_tree->n.common->where),
9360                    comm_name_gsym->name, &(comm_name_gsym->where));
9361       else if (comm_name_gsym != NULL
9362                && strcmp (comm_name_gsym->name,
9363                           comm_block_tree->n.common->name) == 0)
9364         {
9365           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
9366              as expected.  */
9367           if (comm_name_gsym->binding_label == NULL)
9368             /* No binding label for common block stored yet; save this one.  */
9369             comm_name_gsym->binding_label =
9370               comm_block_tree->n.common->binding_label;
9371           else
9372             if (strcmp (comm_name_gsym->binding_label,
9373                         comm_block_tree->n.common->binding_label) != 0)
9374               {
9375                 /* Common block names match but binding labels do not.  */
9376                 gfc_error ("Binding label '%s' for common block '%s' at %L "
9377                            "does not match the binding label '%s' for common "
9378                            "block '%s' at %L",
9379                            comm_block_tree->n.common->binding_label,
9380                            comm_block_tree->n.common->name,
9381                            &(comm_block_tree->n.common->where),
9382                            comm_name_gsym->binding_label,
9383                            comm_name_gsym->name,
9384                            &(comm_name_gsym->where));
9385                 return;
9386               }
9387         }
9388
9389       /* There is no binding label (NAME="") so we have nothing further to
9390          check and nothing to add as a global symbol for the label.  */
9391       if (comm_block_tree->n.common->binding_label[0] == '\0' )
9392         return;
9393       
9394       binding_label_gsym =
9395         gfc_find_gsymbol (gfc_gsym_root,
9396                           comm_block_tree->n.common->binding_label);
9397       if (binding_label_gsym == NULL)
9398         {
9399           /* Need to make a global symbol for the binding label to prevent
9400              it from colliding with another.  */
9401           binding_label_gsym =
9402             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
9403           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
9404           binding_label_gsym->type = GSYM_COMMON;
9405         }
9406       else
9407         {
9408           /* If comm_name_gsym is NULL, the name common block is use
9409              associated and the name could be colliding.  */
9410           if (binding_label_gsym->type != GSYM_COMMON)
9411             gfc_error ("Binding label '%s' for common block '%s' at %L "
9412                        "collides with the global entity '%s' at %L",
9413                        comm_block_tree->n.common->binding_label,
9414                        comm_block_tree->n.common->name,
9415                        &(comm_block_tree->n.common->where),
9416                        binding_label_gsym->name,
9417                        &(binding_label_gsym->where));
9418           else if (comm_name_gsym != NULL
9419                    && (strcmp (binding_label_gsym->name,
9420                                comm_name_gsym->binding_label) != 0)
9421                    && (strcmp (binding_label_gsym->sym_name,
9422                                comm_name_gsym->name) != 0))
9423             gfc_error ("Binding label '%s' for common block '%s' at %L "
9424                        "collides with global entity '%s' at %L",
9425                        binding_label_gsym->name, binding_label_gsym->sym_name,
9426                        &(comm_block_tree->n.common->where),
9427                        comm_name_gsym->name, &(comm_name_gsym->where));
9428         }
9429     }
9430   
9431   return;
9432 }
9433
9434
9435 /* Verify any BIND(C) derived types in the namespace so we can report errors
9436    for them once, rather than for each variable declared of that type.  */
9437
9438 static void
9439 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
9440 {
9441   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
9442       && derived_sym->attr.is_bind_c == 1)
9443     verify_bind_c_derived_type (derived_sym);
9444   
9445   return;
9446 }
9447
9448
9449 /* Verify that any binding labels used in a given namespace do not collide 
9450    with the names or binding labels of any global symbols.  */
9451
9452 static void
9453 gfc_verify_binding_labels (gfc_symbol *sym)
9454 {
9455   int has_error = 0;
9456   
9457   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
9458       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
9459     {
9460       gfc_gsymbol *bind_c_sym;
9461
9462       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
9463       if (bind_c_sym != NULL 
9464           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
9465         {
9466           if (sym->attr.if_source == IFSRC_DECL 
9467               && (bind_c_sym->type != GSYM_SUBROUTINE 
9468                   && bind_c_sym->type != GSYM_FUNCTION) 
9469               && ((sym->attr.contained == 1 
9470                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
9471                   || (sym->attr.use_assoc == 1 
9472                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
9473             {
9474               /* Make sure global procedures don't collide with anything.  */
9475               gfc_error ("Binding label '%s' at %L collides with the global "
9476                          "entity '%s' at %L", sym->binding_label,
9477                          &(sym->declared_at), bind_c_sym->name,
9478                          &(bind_c_sym->where));
9479               has_error = 1;
9480             }
9481           else if (sym->attr.contained == 0 
9482                    && (sym->attr.if_source == IFSRC_IFBODY 
9483                        && sym->attr.flavor == FL_PROCEDURE) 
9484                    && (bind_c_sym->sym_name != NULL 
9485                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
9486             {
9487               /* Make sure procedures in interface bodies don't collide.  */
9488               gfc_error ("Binding label '%s' in interface body at %L collides "
9489                          "with the global entity '%s' at %L",
9490                          sym->binding_label,
9491                          &(sym->declared_at), bind_c_sym->name,
9492                          &(bind_c_sym->where));
9493               has_error = 1;
9494             }
9495           else if (sym->attr.contained == 0 
9496                    && sym->attr.if_source == IFSRC_UNKNOWN)
9497             if ((sym->attr.use_assoc && bind_c_sym->mod_name
9498                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
9499                 || sym->attr.use_assoc == 0)
9500               {
9501                 gfc_error ("Binding label '%s' at %L collides with global "
9502                            "entity '%s' at %L", sym->binding_label,
9503                            &(sym->declared_at), bind_c_sym->name,
9504                            &(bind_c_sym->where));
9505                 has_error = 1;
9506               }
9507
9508           if (has_error != 0)
9509             /* Clear the binding label to prevent checking multiple times.  */
9510             sym->binding_label[0] = '\0';
9511         }
9512       else if (bind_c_sym == NULL)
9513         {
9514           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
9515           bind_c_sym->where = sym->declared_at;
9516           bind_c_sym->sym_name = sym->name;
9517
9518           if (sym->attr.use_assoc == 1)
9519             bind_c_sym->mod_name = sym->module;
9520           else
9521             if (sym->ns->proc_name != NULL)
9522               bind_c_sym->mod_name = sym->ns->proc_name->name;
9523
9524           if (sym->attr.contained == 0)
9525             {
9526               if (sym->attr.subroutine)
9527                 bind_c_sym->type = GSYM_SUBROUTINE;
9528               else if (sym->attr.function)
9529                 bind_c_sym->type = GSYM_FUNCTION;
9530             }
9531         }
9532     }
9533   return;
9534 }
9535
9536
9537 /* Resolve an index expression.  */
9538
9539 static gfc_try
9540 resolve_index_expr (gfc_expr *e)
9541 {
9542   if (gfc_resolve_expr (e) == FAILURE)
9543     return FAILURE;
9544
9545   if (gfc_simplify_expr (e, 0) == FAILURE)
9546     return FAILURE;
9547
9548   if (gfc_specification_expr (e) == FAILURE)
9549     return FAILURE;
9550
9551   return SUCCESS;
9552 }
9553
9554
9555 /* Resolve a charlen structure.  */
9556
9557 static gfc_try
9558 resolve_charlen (gfc_charlen *cl)
9559 {
9560   int i, k;
9561
9562   if (cl->resolved)
9563     return SUCCESS;
9564
9565   cl->resolved = 1;
9566
9567   specification_expr = 1;
9568
9569   if (resolve_index_expr (cl->length) == FAILURE)
9570     {
9571       specification_expr = 0;
9572       return FAILURE;
9573     }
9574
9575   /* "If the character length parameter value evaluates to a negative
9576      value, the length of character entities declared is zero."  */
9577   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
9578     {
9579       if (gfc_option.warn_surprising)
9580         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
9581                          " the length has been set to zero",
9582                          &cl->length->where, i);
9583       gfc_replace_expr (cl->length,
9584                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
9585     }
9586
9587   /* Check that the character length is not too large.  */
9588   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
9589   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
9590       && cl->length->ts.type == BT_INTEGER
9591       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
9592     {
9593       gfc_error ("String length at %L is too large", &cl->length->where);
9594       return FAILURE;
9595     }
9596
9597   return SUCCESS;
9598 }
9599
9600
9601 /* Test for non-constant shape arrays.  */
9602
9603 static bool
9604 is_non_constant_shape_array (gfc_symbol *sym)
9605 {
9606   gfc_expr *e;
9607   int i;
9608   bool not_constant;
9609
9610   not_constant = false;
9611   if (sym->as != NULL)
9612     {
9613       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
9614          has not been simplified; parameter array references.  Do the
9615          simplification now.  */
9616       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
9617         {
9618           e = sym->as->lower[i];
9619           if (e && (resolve_index_expr (e) == FAILURE
9620                     || !gfc_is_constant_expr (e)))
9621             not_constant = true;
9622           e = sym->as->upper[i];
9623           if (e && (resolve_index_expr (e) == FAILURE
9624                     || !gfc_is_constant_expr (e)))
9625             not_constant = true;
9626         }
9627     }
9628   return not_constant;
9629 }
9630
9631 /* Given a symbol and an initialization expression, add code to initialize
9632    the symbol to the function entry.  */
9633 static void
9634 build_init_assign (gfc_symbol *sym, gfc_expr *init)
9635 {
9636   gfc_expr *lval;
9637   gfc_code *init_st;
9638   gfc_namespace *ns = sym->ns;
9639
9640   /* Search for the function namespace if this is a contained
9641      function without an explicit result.  */
9642   if (sym->attr.function && sym == sym->result
9643       && sym->name != sym->ns->proc_name->name)
9644     {
9645       ns = ns->contained;
9646       for (;ns; ns = ns->sibling)
9647         if (strcmp (ns->proc_name->name, sym->name) == 0)
9648           break;
9649     }
9650
9651   if (ns == NULL)
9652     {
9653       gfc_free_expr (init);
9654       return;
9655     }
9656
9657   /* Build an l-value expression for the result.  */
9658   lval = gfc_lval_expr_from_sym (sym);
9659
9660   /* Add the code at scope entry.  */
9661   init_st = gfc_get_code ();
9662   init_st->next = ns->code;
9663   ns->code = init_st;
9664
9665   /* Assign the default initializer to the l-value.  */
9666   init_st->loc = sym->declared_at;
9667   init_st->op = EXEC_INIT_ASSIGN;
9668   init_st->expr1 = lval;
9669   init_st->expr2 = init;
9670 }
9671
9672 /* Assign the default initializer to a derived type variable or result.  */
9673
9674 static void
9675 apply_default_init (gfc_symbol *sym)
9676 {
9677   gfc_expr *init = NULL;
9678
9679   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9680     return;
9681
9682   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
9683     init = gfc_default_initializer (&sym->ts);
9684
9685   if (init == NULL && sym->ts.type != BT_CLASS)
9686     return;
9687
9688   build_init_assign (sym, init);
9689   sym->attr.referenced = 1;
9690 }
9691
9692 /* Build an initializer for a local integer, real, complex, logical, or
9693    character variable, based on the command line flags finit-local-zero,
9694    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
9695    null if the symbol should not have a default initialization.  */
9696 static gfc_expr *
9697 build_default_init_expr (gfc_symbol *sym)
9698 {
9699   int char_len;
9700   gfc_expr *init_expr;
9701   int i;
9702
9703   /* These symbols should never have a default initialization.  */
9704   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
9705       || sym->attr.external
9706       || sym->attr.dummy
9707       || sym->attr.pointer
9708       || sym->attr.in_equivalence
9709       || sym->attr.in_common
9710       || sym->attr.data
9711       || sym->module
9712       || sym->attr.cray_pointee
9713       || sym->attr.cray_pointer)
9714     return NULL;
9715
9716   /* Now we'll try to build an initializer expression.  */
9717   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
9718                                      &sym->declared_at);
9719
9720   /* We will only initialize integers, reals, complex, logicals, and
9721      characters, and only if the corresponding command-line flags
9722      were set.  Otherwise, we free init_expr and return null.  */
9723   switch (sym->ts.type)
9724     {    
9725     case BT_INTEGER:
9726       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
9727         mpz_set_si (init_expr->value.integer, 
9728                          gfc_option.flag_init_integer_value);
9729       else
9730         {
9731           gfc_free_expr (init_expr);
9732           init_expr = NULL;
9733         }
9734       break;
9735
9736     case BT_REAL:
9737       switch (gfc_option.flag_init_real)
9738         {
9739         case GFC_INIT_REAL_SNAN:
9740           init_expr->is_snan = 1;
9741           /* Fall through.  */
9742         case GFC_INIT_REAL_NAN:
9743           mpfr_set_nan (init_expr->value.real);
9744           break;
9745
9746         case GFC_INIT_REAL_INF:
9747           mpfr_set_inf (init_expr->value.real, 1);
9748           break;
9749
9750         case GFC_INIT_REAL_NEG_INF:
9751           mpfr_set_inf (init_expr->value.real, -1);
9752           break;
9753
9754         case GFC_INIT_REAL_ZERO:
9755           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
9756           break;
9757
9758         default:
9759           gfc_free_expr (init_expr);
9760           init_expr = NULL;
9761           break;
9762         }
9763       break;
9764           
9765     case BT_COMPLEX:
9766       switch (gfc_option.flag_init_real)
9767         {
9768         case GFC_INIT_REAL_SNAN:
9769           init_expr->is_snan = 1;
9770           /* Fall through.  */
9771         case GFC_INIT_REAL_NAN:
9772           mpfr_set_nan (mpc_realref (init_expr->value.complex));
9773           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
9774           break;
9775
9776         case GFC_INIT_REAL_INF:
9777           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
9778           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
9779           break;
9780
9781         case GFC_INIT_REAL_NEG_INF:
9782           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
9783           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
9784           break;
9785
9786         case GFC_INIT_REAL_ZERO:
9787           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
9788           break;
9789
9790         default:
9791           gfc_free_expr (init_expr);
9792           init_expr = NULL;
9793           break;
9794         }
9795       break;
9796           
9797     case BT_LOGICAL:
9798       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
9799         init_expr->value.logical = 0;
9800       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
9801         init_expr->value.logical = 1;
9802       else
9803         {
9804           gfc_free_expr (init_expr);
9805           init_expr = NULL;
9806         }
9807       break;
9808           
9809     case BT_CHARACTER:
9810       /* For characters, the length must be constant in order to 
9811          create a default initializer.  */
9812       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
9813           && sym->ts.u.cl->length
9814           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9815         {
9816           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
9817           init_expr->value.character.length = char_len;
9818           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
9819           for (i = 0; i < char_len; i++)
9820             init_expr->value.character.string[i]
9821               = (unsigned char) gfc_option.flag_init_character_value;
9822         }
9823       else
9824         {
9825           gfc_free_expr (init_expr);
9826           init_expr = NULL;
9827         }
9828       break;
9829           
9830     default:
9831      gfc_free_expr (init_expr);
9832      init_expr = NULL;
9833     }
9834   return init_expr;
9835 }
9836
9837 /* Add an initialization expression to a local variable.  */
9838 static void
9839 apply_default_init_local (gfc_symbol *sym)
9840 {
9841   gfc_expr *init = NULL;
9842
9843   /* The symbol should be a variable or a function return value.  */
9844   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9845       || (sym->attr.function && sym->result != sym))
9846     return;
9847
9848   /* Try to build the initializer expression.  If we can't initialize
9849      this symbol, then init will be NULL.  */
9850   init = build_default_init_expr (sym);
9851   if (init == NULL)
9852     return;
9853
9854   /* For saved variables, we don't want to add an initializer at 
9855      function entry, so we just add a static initializer.  */
9856   if (sym->attr.save || sym->ns->save_all 
9857       || gfc_option.flag_max_stack_var_size == 0)
9858     {
9859       /* Don't clobber an existing initializer!  */
9860       gcc_assert (sym->value == NULL);
9861       sym->value = init;
9862       return;
9863     }
9864
9865   build_init_assign (sym, init);
9866 }
9867
9868
9869 /* Resolution of common features of flavors variable and procedure.  */
9870
9871 static gfc_try
9872 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
9873 {
9874   /* Constraints on deferred shape variable.  */
9875   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
9876     {
9877       if (sym->attr.allocatable)
9878         {
9879           if (sym->attr.dimension)
9880             {
9881               gfc_error ("Allocatable array '%s' at %L must have "
9882                          "a deferred shape", sym->name, &sym->declared_at);
9883               return FAILURE;
9884             }
9885           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
9886                                    "may not be ALLOCATABLE", sym->name,
9887                                    &sym->declared_at) == FAILURE)
9888             return FAILURE;
9889         }
9890
9891       if (sym->attr.pointer && sym->attr.dimension)
9892         {
9893           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
9894                      sym->name, &sym->declared_at);
9895           return FAILURE;
9896         }
9897     }
9898   else
9899     {
9900       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
9901           && !sym->attr.dummy && sym->ts.type != BT_CLASS && !sym->assoc)
9902         {
9903           gfc_error ("Array '%s' at %L cannot have a deferred shape",
9904                      sym->name, &sym->declared_at);
9905           return FAILURE;
9906          }
9907     }
9908
9909   /* Constraints on polymorphic variables.  */
9910   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
9911     {
9912       /* F03:C502.  */
9913       if (sym->attr.class_ok
9914           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
9915         {
9916           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
9917                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
9918                      &sym->declared_at);
9919           return FAILURE;
9920         }
9921
9922       /* F03:C509.  */
9923       /* Assume that use associated symbols were checked in the module ns.
9924          Class-variables that are associate-names are also something special
9925          and excepted from the test.  */
9926       if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
9927         {
9928           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
9929                      "or pointer", sym->name, &sym->declared_at);
9930           return FAILURE;
9931         }
9932     }
9933     
9934   return SUCCESS;
9935 }
9936
9937
9938 /* Additional checks for symbols with flavor variable and derived
9939    type.  To be called from resolve_fl_variable.  */
9940
9941 static gfc_try
9942 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
9943 {
9944   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
9945
9946   /* Check to see if a derived type is blocked from being host
9947      associated by the presence of another class I symbol in the same
9948      namespace.  14.6.1.3 of the standard and the discussion on
9949      comp.lang.fortran.  */
9950   if (sym->ns != sym->ts.u.derived->ns
9951       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
9952     {
9953       gfc_symbol *s;
9954       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
9955       if (s && s->attr.flavor != FL_DERIVED)
9956         {
9957           gfc_error ("The type '%s' cannot be host associated at %L "
9958                      "because it is blocked by an incompatible object "
9959                      "of the same name declared at %L",
9960                      sym->ts.u.derived->name, &sym->declared_at,
9961                      &s->declared_at);
9962           return FAILURE;
9963         }
9964     }
9965
9966   /* 4th constraint in section 11.3: "If an object of a type for which
9967      component-initialization is specified (R429) appears in the
9968      specification-part of a module and does not have the ALLOCATABLE
9969      or POINTER attribute, the object shall have the SAVE attribute."
9970
9971      The check for initializers is performed with
9972      gfc_has_default_initializer because gfc_default_initializer generates
9973      a hidden default for allocatable components.  */
9974   if (!(sym->value || no_init_flag) && sym->ns->proc_name
9975       && sym->ns->proc_name->attr.flavor == FL_MODULE
9976       && !sym->ns->save_all && !sym->attr.save
9977       && !sym->attr.pointer && !sym->attr.allocatable
9978       && gfc_has_default_initializer (sym->ts.u.derived)
9979       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
9980                          "module variable '%s' at %L, needed due to "
9981                          "the default initialization", sym->name,
9982                          &sym->declared_at) == FAILURE)
9983     return FAILURE;
9984
9985   /* Assign default initializer.  */
9986   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
9987       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
9988     {
9989       sym->value = gfc_default_initializer (&sym->ts);
9990     }
9991
9992   return SUCCESS;
9993 }
9994
9995
9996 /* Resolve symbols with flavor variable.  */
9997
9998 static gfc_try
9999 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
10000 {
10001   int no_init_flag, automatic_flag;
10002   gfc_expr *e;
10003   const char *auto_save_msg;
10004
10005   auto_save_msg = "Automatic object '%s' at %L cannot have the "
10006                   "SAVE attribute";
10007
10008   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10009     return FAILURE;
10010
10011   /* Set this flag to check that variables are parameters of all entries.
10012      This check is effected by the call to gfc_resolve_expr through
10013      is_non_constant_shape_array.  */
10014   specification_expr = 1;
10015
10016   if (sym->ns->proc_name
10017       && (sym->ns->proc_name->attr.flavor == FL_MODULE
10018           || sym->ns->proc_name->attr.is_main_program)
10019       && !sym->attr.use_assoc
10020       && !sym->attr.allocatable
10021       && !sym->attr.pointer
10022       && is_non_constant_shape_array (sym))
10023     {
10024       /* The shape of a main program or module array needs to be
10025          constant.  */
10026       gfc_error ("The module or main program array '%s' at %L must "
10027                  "have constant shape", sym->name, &sym->declared_at);
10028       specification_expr = 0;
10029       return FAILURE;
10030     }
10031
10032   /* Constraints on deferred type parameter.  */
10033   if (sym->ts.deferred && !(sym->attr.pointer || sym->attr.allocatable))
10034     {
10035       gfc_error ("Entity '%s' at %L has a deferred type parameter and "
10036                  "requires either the pointer or allocatable attribute",
10037                      sym->name, &sym->declared_at);
10038       return FAILURE;
10039     }
10040
10041   if (sym->ts.type == BT_CHARACTER)
10042     {
10043       /* Make sure that character string variables with assumed length are
10044          dummy arguments.  */
10045       e = sym->ts.u.cl->length;
10046       if (e == NULL && !sym->attr.dummy && !sym->attr.result
10047           && !sym->ts.deferred)
10048         {
10049           gfc_error ("Entity with assumed character length at %L must be a "
10050                      "dummy argument or a PARAMETER", &sym->declared_at);
10051           return FAILURE;
10052         }
10053
10054       if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
10055         {
10056           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10057           return FAILURE;
10058         }
10059
10060       if (!gfc_is_constant_expr (e)
10061           && !(e->expr_type == EXPR_VARIABLE
10062                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
10063           && sym->ns->proc_name
10064           && (sym->ns->proc_name->attr.flavor == FL_MODULE
10065               || sym->ns->proc_name->attr.is_main_program)
10066           && !sym->attr.use_assoc)
10067         {
10068           gfc_error ("'%s' at %L must have constant character length "
10069                      "in this context", sym->name, &sym->declared_at);
10070           return FAILURE;
10071         }
10072     }
10073
10074   if (sym->value == NULL && sym->attr.referenced)
10075     apply_default_init_local (sym); /* Try to apply a default initialization.  */
10076
10077   /* Determine if the symbol may not have an initializer.  */
10078   no_init_flag = automatic_flag = 0;
10079   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
10080       || sym->attr.intrinsic || sym->attr.result)
10081     no_init_flag = 1;
10082   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
10083            && is_non_constant_shape_array (sym))
10084     {
10085       no_init_flag = automatic_flag = 1;
10086
10087       /* Also, they must not have the SAVE attribute.
10088          SAVE_IMPLICIT is checked below.  */
10089       if (sym->attr.save == SAVE_EXPLICIT)
10090         {
10091           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10092           return FAILURE;
10093         }
10094     }
10095
10096   /* Ensure that any initializer is simplified.  */
10097   if (sym->value)
10098     gfc_simplify_expr (sym->value, 1);
10099
10100   /* Reject illegal initializers.  */
10101   if (!sym->mark && sym->value)
10102     {
10103       if (sym->attr.allocatable || (sym->ts.type == BT_CLASS
10104                                     && CLASS_DATA (sym)->attr.allocatable))
10105         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
10106                    sym->name, &sym->declared_at);
10107       else if (sym->attr.external)
10108         gfc_error ("External '%s' at %L cannot have an initializer",
10109                    sym->name, &sym->declared_at);
10110       else if (sym->attr.dummy
10111         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
10112         gfc_error ("Dummy '%s' at %L cannot have an initializer",
10113                    sym->name, &sym->declared_at);
10114       else if (sym->attr.intrinsic)
10115         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
10116                    sym->name, &sym->declared_at);
10117       else if (sym->attr.result)
10118         gfc_error ("Function result '%s' at %L cannot have an initializer",
10119                    sym->name, &sym->declared_at);
10120       else if (automatic_flag)
10121         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
10122                    sym->name, &sym->declared_at);
10123       else
10124         goto no_init_error;
10125       return FAILURE;
10126     }
10127
10128 no_init_error:
10129   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
10130     return resolve_fl_variable_derived (sym, no_init_flag);
10131
10132   return SUCCESS;
10133 }
10134
10135
10136 /* Resolve a procedure.  */
10137
10138 static gfc_try
10139 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
10140 {
10141   gfc_formal_arglist *arg;
10142
10143   if (sym->attr.function
10144       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10145     return FAILURE;
10146
10147   if (sym->ts.type == BT_CHARACTER)
10148     {
10149       gfc_charlen *cl = sym->ts.u.cl;
10150
10151       if (cl && cl->length && gfc_is_constant_expr (cl->length)
10152              && resolve_charlen (cl) == FAILURE)
10153         return FAILURE;
10154
10155       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
10156           && sym->attr.proc == PROC_ST_FUNCTION)
10157         {
10158           gfc_error ("Character-valued statement function '%s' at %L must "
10159                      "have constant length", sym->name, &sym->declared_at);
10160           return FAILURE;
10161         }
10162     }
10163
10164   /* Ensure that derived type for are not of a private type.  Internal
10165      module procedures are excluded by 2.2.3.3 - i.e., they are not
10166      externally accessible and can access all the objects accessible in
10167      the host.  */
10168   if (!(sym->ns->parent
10169         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
10170       && gfc_check_symbol_access (sym))
10171     {
10172       gfc_interface *iface;
10173
10174       for (arg = sym->formal; arg; arg = arg->next)
10175         {
10176           if (arg->sym
10177               && arg->sym->ts.type == BT_DERIVED
10178               && !arg->sym->ts.u.derived->attr.use_assoc
10179               && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10180               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
10181                                  "PRIVATE type and cannot be a dummy argument"
10182                                  " of '%s', which is PUBLIC at %L",
10183                                  arg->sym->name, sym->name, &sym->declared_at)
10184                  == FAILURE)
10185             {
10186               /* Stop this message from recurring.  */
10187               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10188               return FAILURE;
10189             }
10190         }
10191
10192       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10193          PRIVATE to the containing module.  */
10194       for (iface = sym->generic; iface; iface = iface->next)
10195         {
10196           for (arg = iface->sym->formal; arg; arg = arg->next)
10197             {
10198               if (arg->sym
10199                   && arg->sym->ts.type == BT_DERIVED
10200                   && !arg->sym->ts.u.derived->attr.use_assoc
10201                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10202                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10203                                      "'%s' in PUBLIC interface '%s' at %L "
10204                                      "takes dummy arguments of '%s' which is "
10205                                      "PRIVATE", iface->sym->name, sym->name,
10206                                      &iface->sym->declared_at,
10207                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10208                 {
10209                   /* Stop this message from recurring.  */
10210                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10211                   return FAILURE;
10212                 }
10213              }
10214         }
10215
10216       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10217          PRIVATE to the containing module.  */
10218       for (iface = sym->generic; iface; iface = iface->next)
10219         {
10220           for (arg = iface->sym->formal; arg; arg = arg->next)
10221             {
10222               if (arg->sym
10223                   && arg->sym->ts.type == BT_DERIVED
10224                   && !arg->sym->ts.u.derived->attr.use_assoc
10225                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10226                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10227                                      "'%s' in PUBLIC interface '%s' at %L "
10228                                      "takes dummy arguments of '%s' which is "
10229                                      "PRIVATE", iface->sym->name, sym->name,
10230                                      &iface->sym->declared_at,
10231                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10232                 {
10233                   /* Stop this message from recurring.  */
10234                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10235                   return FAILURE;
10236                 }
10237              }
10238         }
10239     }
10240
10241   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
10242       && !sym->attr.proc_pointer)
10243     {
10244       gfc_error ("Function '%s' at %L cannot have an initializer",
10245                  sym->name, &sym->declared_at);
10246       return FAILURE;
10247     }
10248
10249   /* An external symbol may not have an initializer because it is taken to be
10250      a procedure. Exception: Procedure Pointers.  */
10251   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
10252     {
10253       gfc_error ("External object '%s' at %L may not have an initializer",
10254                  sym->name, &sym->declared_at);
10255       return FAILURE;
10256     }
10257
10258   /* An elemental function is required to return a scalar 12.7.1  */
10259   if (sym->attr.elemental && sym->attr.function && sym->as)
10260     {
10261       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
10262                  "result", sym->name, &sym->declared_at);
10263       /* Reset so that the error only occurs once.  */
10264       sym->attr.elemental = 0;
10265       return FAILURE;
10266     }
10267
10268   if (sym->attr.proc == PROC_ST_FUNCTION
10269       && (sym->attr.allocatable || sym->attr.pointer))
10270     {
10271       gfc_error ("Statement function '%s' at %L may not have pointer or "
10272                  "allocatable attribute", sym->name, &sym->declared_at);
10273       return FAILURE;
10274     }
10275
10276   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
10277      char-len-param shall not be array-valued, pointer-valued, recursive
10278      or pure.  ....snip... A character value of * may only be used in the
10279      following ways: (i) Dummy arg of procedure - dummy associates with
10280      actual length; (ii) To declare a named constant; or (iii) External
10281      function - but length must be declared in calling scoping unit.  */
10282   if (sym->attr.function
10283       && sym->ts.type == BT_CHARACTER
10284       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
10285     {
10286       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
10287           || (sym->attr.recursive) || (sym->attr.pure))
10288         {
10289           if (sym->as && sym->as->rank)
10290             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10291                        "array-valued", sym->name, &sym->declared_at);
10292
10293           if (sym->attr.pointer)
10294             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10295                        "pointer-valued", sym->name, &sym->declared_at);
10296
10297           if (sym->attr.pure)
10298             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10299                        "pure", sym->name, &sym->declared_at);
10300
10301           if (sym->attr.recursive)
10302             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10303                        "recursive", sym->name, &sym->declared_at);
10304
10305           return FAILURE;
10306         }
10307
10308       /* Appendix B.2 of the standard.  Contained functions give an
10309          error anyway.  Fixed-form is likely to be F77/legacy. Deferred
10310          character length is an F2003 feature.  */
10311       if (!sym->attr.contained
10312             && gfc_current_form != FORM_FIXED
10313             && !sym->ts.deferred)
10314         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
10315                         "CHARACTER(*) function '%s' at %L",
10316                         sym->name, &sym->declared_at);
10317     }
10318
10319   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
10320     {
10321       gfc_formal_arglist *curr_arg;
10322       int has_non_interop_arg = 0;
10323
10324       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10325                              sym->common_block) == FAILURE)
10326         {
10327           /* Clear these to prevent looking at them again if there was an
10328              error.  */
10329           sym->attr.is_bind_c = 0;
10330           sym->attr.is_c_interop = 0;
10331           sym->ts.is_c_interop = 0;
10332         }
10333       else
10334         {
10335           /* So far, no errors have been found.  */
10336           sym->attr.is_c_interop = 1;
10337           sym->ts.is_c_interop = 1;
10338         }
10339       
10340       curr_arg = sym->formal;
10341       while (curr_arg != NULL)
10342         {
10343           /* Skip implicitly typed dummy args here.  */
10344           if (curr_arg->sym->attr.implicit_type == 0)
10345             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
10346               /* If something is found to fail, record the fact so we
10347                  can mark the symbol for the procedure as not being
10348                  BIND(C) to try and prevent multiple errors being
10349                  reported.  */
10350               has_non_interop_arg = 1;
10351           
10352           curr_arg = curr_arg->next;
10353         }
10354
10355       /* See if any of the arguments were not interoperable and if so, clear
10356          the procedure symbol to prevent duplicate error messages.  */
10357       if (has_non_interop_arg != 0)
10358         {
10359           sym->attr.is_c_interop = 0;
10360           sym->ts.is_c_interop = 0;
10361           sym->attr.is_bind_c = 0;
10362         }
10363     }
10364   
10365   if (!sym->attr.proc_pointer)
10366     {
10367       if (sym->attr.save == SAVE_EXPLICIT)
10368         {
10369           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
10370                      "in '%s' at %L", sym->name, &sym->declared_at);
10371           return FAILURE;
10372         }
10373       if (sym->attr.intent)
10374         {
10375           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
10376                      "in '%s' at %L", sym->name, &sym->declared_at);
10377           return FAILURE;
10378         }
10379       if (sym->attr.subroutine && sym->attr.result)
10380         {
10381           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
10382                      "in '%s' at %L", sym->name, &sym->declared_at);
10383           return FAILURE;
10384         }
10385       if (sym->attr.external && sym->attr.function
10386           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
10387               || sym->attr.contained))
10388         {
10389           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
10390                      "in '%s' at %L", sym->name, &sym->declared_at);
10391           return FAILURE;
10392         }
10393       if (strcmp ("ppr@", sym->name) == 0)
10394         {
10395           gfc_error ("Procedure pointer result '%s' at %L "
10396                      "is missing the pointer attribute",
10397                      sym->ns->proc_name->name, &sym->declared_at);
10398           return FAILURE;
10399         }
10400     }
10401
10402   return SUCCESS;
10403 }
10404
10405
10406 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
10407    been defined and we now know their defined arguments, check that they fulfill
10408    the requirements of the standard for procedures used as finalizers.  */
10409
10410 static gfc_try
10411 gfc_resolve_finalizers (gfc_symbol* derived)
10412 {
10413   gfc_finalizer* list;
10414   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
10415   gfc_try result = SUCCESS;
10416   bool seen_scalar = false;
10417
10418   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
10419     return SUCCESS;
10420
10421   /* Walk over the list of finalizer-procedures, check them, and if any one
10422      does not fit in with the standard's definition, print an error and remove
10423      it from the list.  */
10424   prev_link = &derived->f2k_derived->finalizers;
10425   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
10426     {
10427       gfc_symbol* arg;
10428       gfc_finalizer* i;
10429       int my_rank;
10430
10431       /* Skip this finalizer if we already resolved it.  */
10432       if (list->proc_tree)
10433         {
10434           prev_link = &(list->next);
10435           continue;
10436         }
10437
10438       /* Check this exists and is a SUBROUTINE.  */
10439       if (!list->proc_sym->attr.subroutine)
10440         {
10441           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
10442                      list->proc_sym->name, &list->where);
10443           goto error;
10444         }
10445
10446       /* We should have exactly one argument.  */
10447       if (!list->proc_sym->formal || list->proc_sym->formal->next)
10448         {
10449           gfc_error ("FINAL procedure at %L must have exactly one argument",
10450                      &list->where);
10451           goto error;
10452         }
10453       arg = list->proc_sym->formal->sym;
10454
10455       /* This argument must be of our type.  */
10456       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
10457         {
10458           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
10459                      &arg->declared_at, derived->name);
10460           goto error;
10461         }
10462
10463       /* It must neither be a pointer nor allocatable nor optional.  */
10464       if (arg->attr.pointer)
10465         {
10466           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
10467                      &arg->declared_at);
10468           goto error;
10469         }
10470       if (arg->attr.allocatable)
10471         {
10472           gfc_error ("Argument of FINAL procedure at %L must not be"
10473                      " ALLOCATABLE", &arg->declared_at);
10474           goto error;
10475         }
10476       if (arg->attr.optional)
10477         {
10478           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
10479                      &arg->declared_at);
10480           goto error;
10481         }
10482
10483       /* It must not be INTENT(OUT).  */
10484       if (arg->attr.intent == INTENT_OUT)
10485         {
10486           gfc_error ("Argument of FINAL procedure at %L must not be"
10487                      " INTENT(OUT)", &arg->declared_at);
10488           goto error;
10489         }
10490
10491       /* Warn if the procedure is non-scalar and not assumed shape.  */
10492       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
10493           && arg->as->type != AS_ASSUMED_SHAPE)
10494         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
10495                      " shape argument", &arg->declared_at);
10496
10497       /* Check that it does not match in kind and rank with a FINAL procedure
10498          defined earlier.  To really loop over the *earlier* declarations,
10499          we need to walk the tail of the list as new ones were pushed at the
10500          front.  */
10501       /* TODO: Handle kind parameters once they are implemented.  */
10502       my_rank = (arg->as ? arg->as->rank : 0);
10503       for (i = list->next; i; i = i->next)
10504         {
10505           /* Argument list might be empty; that is an error signalled earlier,
10506              but we nevertheless continued resolving.  */
10507           if (i->proc_sym->formal)
10508             {
10509               gfc_symbol* i_arg = i->proc_sym->formal->sym;
10510               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
10511               if (i_rank == my_rank)
10512                 {
10513                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
10514                              " rank (%d) as '%s'",
10515                              list->proc_sym->name, &list->where, my_rank, 
10516                              i->proc_sym->name);
10517                   goto error;
10518                 }
10519             }
10520         }
10521
10522         /* Is this the/a scalar finalizer procedure?  */
10523         if (!arg->as || arg->as->rank == 0)
10524           seen_scalar = true;
10525
10526         /* Find the symtree for this procedure.  */
10527         gcc_assert (!list->proc_tree);
10528         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
10529
10530         prev_link = &list->next;
10531         continue;
10532
10533         /* Remove wrong nodes immediately from the list so we don't risk any
10534            troubles in the future when they might fail later expectations.  */
10535 error:
10536         result = FAILURE;
10537         i = list;
10538         *prev_link = list->next;
10539         gfc_free_finalizer (i);
10540     }
10541
10542   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
10543      were nodes in the list, must have been for arrays.  It is surely a good
10544      idea to have a scalar version there if there's something to finalize.  */
10545   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
10546     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
10547                  " defined at %L, suggest also scalar one",
10548                  derived->name, &derived->declared_at);
10549
10550   /* TODO:  Remove this error when finalization is finished.  */
10551   gfc_error ("Finalization at %L is not yet implemented",
10552              &derived->declared_at);
10553
10554   return result;
10555 }
10556
10557
10558 /* Check that it is ok for the typebound procedure proc to override the
10559    procedure old.  */
10560
10561 static gfc_try
10562 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
10563 {
10564   locus where;
10565   const gfc_symbol* proc_target;
10566   const gfc_symbol* old_target;
10567   unsigned proc_pass_arg, old_pass_arg, argpos;
10568   gfc_formal_arglist* proc_formal;
10569   gfc_formal_arglist* old_formal;
10570
10571   /* This procedure should only be called for non-GENERIC proc.  */
10572   gcc_assert (!proc->n.tb->is_generic);
10573
10574   /* If the overwritten procedure is GENERIC, this is an error.  */
10575   if (old->n.tb->is_generic)
10576     {
10577       gfc_error ("Can't overwrite GENERIC '%s' at %L",
10578                  old->name, &proc->n.tb->where);
10579       return FAILURE;
10580     }
10581
10582   where = proc->n.tb->where;
10583   proc_target = proc->n.tb->u.specific->n.sym;
10584   old_target = old->n.tb->u.specific->n.sym;
10585
10586   /* Check that overridden binding is not NON_OVERRIDABLE.  */
10587   if (old->n.tb->non_overridable)
10588     {
10589       gfc_error ("'%s' at %L overrides a procedure binding declared"
10590                  " NON_OVERRIDABLE", proc->name, &where);
10591       return FAILURE;
10592     }
10593
10594   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
10595   if (!old->n.tb->deferred && proc->n.tb->deferred)
10596     {
10597       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
10598                  " non-DEFERRED binding", proc->name, &where);
10599       return FAILURE;
10600     }
10601
10602   /* If the overridden binding is PURE, the overriding must be, too.  */
10603   if (old_target->attr.pure && !proc_target->attr.pure)
10604     {
10605       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
10606                  proc->name, &where);
10607       return FAILURE;
10608     }
10609
10610   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
10611      is not, the overriding must not be either.  */
10612   if (old_target->attr.elemental && !proc_target->attr.elemental)
10613     {
10614       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
10615                  " ELEMENTAL", proc->name, &where);
10616       return FAILURE;
10617     }
10618   if (!old_target->attr.elemental && proc_target->attr.elemental)
10619     {
10620       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
10621                  " be ELEMENTAL, either", proc->name, &where);
10622       return FAILURE;
10623     }
10624
10625   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
10626      SUBROUTINE.  */
10627   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
10628     {
10629       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
10630                  " SUBROUTINE", proc->name, &where);
10631       return FAILURE;
10632     }
10633
10634   /* If the overridden binding is a FUNCTION, the overriding must also be a
10635      FUNCTION and have the same characteristics.  */
10636   if (old_target->attr.function)
10637     {
10638       if (!proc_target->attr.function)
10639         {
10640           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
10641                      " FUNCTION", proc->name, &where);
10642           return FAILURE;
10643         }
10644
10645       /* FIXME:  Do more comprehensive checking (including, for instance, the
10646          rank and array-shape).  */
10647       gcc_assert (proc_target->result && old_target->result);
10648       if (!gfc_compare_types (&proc_target->result->ts,
10649                               &old_target->result->ts))
10650         {
10651           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
10652                      " matching result types", proc->name, &where);
10653           return FAILURE;
10654         }
10655     }
10656
10657   /* If the overridden binding is PUBLIC, the overriding one must not be
10658      PRIVATE.  */
10659   if (old->n.tb->access == ACCESS_PUBLIC
10660       && proc->n.tb->access == ACCESS_PRIVATE)
10661     {
10662       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
10663                  " PRIVATE", proc->name, &where);
10664       return FAILURE;
10665     }
10666
10667   /* Compare the formal argument lists of both procedures.  This is also abused
10668      to find the position of the passed-object dummy arguments of both
10669      bindings as at least the overridden one might not yet be resolved and we
10670      need those positions in the check below.  */
10671   proc_pass_arg = old_pass_arg = 0;
10672   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
10673     proc_pass_arg = 1;
10674   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
10675     old_pass_arg = 1;
10676   argpos = 1;
10677   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
10678        proc_formal && old_formal;
10679        proc_formal = proc_formal->next, old_formal = old_formal->next)
10680     {
10681       if (proc->n.tb->pass_arg
10682           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
10683         proc_pass_arg = argpos;
10684       if (old->n.tb->pass_arg
10685           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
10686         old_pass_arg = argpos;
10687
10688       /* Check that the names correspond.  */
10689       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
10690         {
10691           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
10692                      " to match the corresponding argument of the overridden"
10693                      " procedure", proc_formal->sym->name, proc->name, &where,
10694                      old_formal->sym->name);
10695           return FAILURE;
10696         }
10697
10698       /* Check that the types correspond if neither is the passed-object
10699          argument.  */
10700       /* FIXME:  Do more comprehensive testing here.  */
10701       if (proc_pass_arg != argpos && old_pass_arg != argpos
10702           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
10703         {
10704           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L "
10705                      "in respect to the overridden procedure",
10706                      proc_formal->sym->name, proc->name, &where);
10707           return FAILURE;
10708         }
10709
10710       ++argpos;
10711     }
10712   if (proc_formal || old_formal)
10713     {
10714       gfc_error ("'%s' at %L must have the same number of formal arguments as"
10715                  " the overridden procedure", proc->name, &where);
10716       return FAILURE;
10717     }
10718
10719   /* If the overridden binding is NOPASS, the overriding one must also be
10720      NOPASS.  */
10721   if (old->n.tb->nopass && !proc->n.tb->nopass)
10722     {
10723       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
10724                  " NOPASS", proc->name, &where);
10725       return FAILURE;
10726     }
10727
10728   /* If the overridden binding is PASS(x), the overriding one must also be
10729      PASS and the passed-object dummy arguments must correspond.  */
10730   if (!old->n.tb->nopass)
10731     {
10732       if (proc->n.tb->nopass)
10733         {
10734           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
10735                      " PASS", proc->name, &where);
10736           return FAILURE;
10737         }
10738
10739       if (proc_pass_arg != old_pass_arg)
10740         {
10741           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
10742                      " the same position as the passed-object dummy argument of"
10743                      " the overridden procedure", proc->name, &where);
10744           return FAILURE;
10745         }
10746     }
10747
10748   return SUCCESS;
10749 }
10750
10751
10752 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10753
10754 static gfc_try
10755 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10756                              const char* generic_name, locus where)
10757 {
10758   gfc_symbol* sym1;
10759   gfc_symbol* sym2;
10760
10761   gcc_assert (t1->specific && t2->specific);
10762   gcc_assert (!t1->specific->is_generic);
10763   gcc_assert (!t2->specific->is_generic);
10764
10765   sym1 = t1->specific->u.specific->n.sym;
10766   sym2 = t2->specific->u.specific->n.sym;
10767
10768   if (sym1 == sym2)
10769     return SUCCESS;
10770
10771   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10772   if (sym1->attr.subroutine != sym2->attr.subroutine
10773       || sym1->attr.function != sym2->attr.function)
10774     {
10775       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10776                  " GENERIC '%s' at %L",
10777                  sym1->name, sym2->name, generic_name, &where);
10778       return FAILURE;
10779     }
10780
10781   /* Compare the interfaces.  */
10782   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10783     {
10784       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10785                  sym1->name, sym2->name, generic_name, &where);
10786       return FAILURE;
10787     }
10788
10789   return SUCCESS;
10790 }
10791
10792
10793 /* Worker function for resolving a generic procedure binding; this is used to
10794    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10795
10796    The difference between those cases is finding possible inherited bindings
10797    that are overridden, as one has to look for them in tb_sym_root,
10798    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10799    the super-type and set p->overridden correctly.  */
10800
10801 static gfc_try
10802 resolve_tb_generic_targets (gfc_symbol* super_type,
10803                             gfc_typebound_proc* p, const char* name)
10804 {
10805   gfc_tbp_generic* target;
10806   gfc_symtree* first_target;
10807   gfc_symtree* inherited;
10808
10809   gcc_assert (p && p->is_generic);
10810
10811   /* Try to find the specific bindings for the symtrees in our target-list.  */
10812   gcc_assert (p->u.generic);
10813   for (target = p->u.generic; target; target = target->next)
10814     if (!target->specific)
10815       {
10816         gfc_typebound_proc* overridden_tbp;
10817         gfc_tbp_generic* g;
10818         const char* target_name;
10819
10820         target_name = target->specific_st->name;
10821
10822         /* Defined for this type directly.  */
10823         if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
10824           {
10825             target->specific = target->specific_st->n.tb;
10826             goto specific_found;
10827           }
10828
10829         /* Look for an inherited specific binding.  */
10830         if (super_type)
10831           {
10832             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10833                                                  true, NULL);
10834
10835             if (inherited)
10836               {
10837                 gcc_assert (inherited->n.tb);
10838                 target->specific = inherited->n.tb;
10839                 goto specific_found;
10840               }
10841           }
10842
10843         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10844                    " at %L", target_name, name, &p->where);
10845         return FAILURE;
10846
10847         /* Once we've found the specific binding, check it is not ambiguous with
10848            other specifics already found or inherited for the same GENERIC.  */
10849 specific_found:
10850         gcc_assert (target->specific);
10851
10852         /* This must really be a specific binding!  */
10853         if (target->specific->is_generic)
10854           {
10855             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
10856                        " '%s' is GENERIC, too", name, &p->where, target_name);
10857             return FAILURE;
10858           }
10859
10860         /* Check those already resolved on this type directly.  */
10861         for (g = p->u.generic; g; g = g->next)
10862           if (g != target && g->specific
10863               && check_generic_tbp_ambiguity (target, g, name, p->where)
10864                   == FAILURE)
10865             return FAILURE;
10866
10867         /* Check for ambiguity with inherited specific targets.  */
10868         for (overridden_tbp = p->overridden; overridden_tbp;
10869              overridden_tbp = overridden_tbp->overridden)
10870           if (overridden_tbp->is_generic)
10871             {
10872               for (g = overridden_tbp->u.generic; g; g = g->next)
10873                 {
10874                   gcc_assert (g->specific);
10875                   if (check_generic_tbp_ambiguity (target, g,
10876                                                    name, p->where) == FAILURE)
10877                     return FAILURE;
10878                 }
10879             }
10880       }
10881
10882   /* If we attempt to "overwrite" a specific binding, this is an error.  */
10883   if (p->overridden && !p->overridden->is_generic)
10884     {
10885       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
10886                  " the same name", name, &p->where);
10887       return FAILURE;
10888     }
10889
10890   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
10891      all must have the same attributes here.  */
10892   first_target = p->u.generic->specific->u.specific;
10893   gcc_assert (first_target);
10894   p->subroutine = first_target->n.sym->attr.subroutine;
10895   p->function = first_target->n.sym->attr.function;
10896
10897   return SUCCESS;
10898 }
10899
10900
10901 /* Resolve a GENERIC procedure binding for a derived type.  */
10902
10903 static gfc_try
10904 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
10905 {
10906   gfc_symbol* super_type;
10907
10908   /* Find the overridden binding if any.  */
10909   st->n.tb->overridden = NULL;
10910   super_type = gfc_get_derived_super_type (derived);
10911   if (super_type)
10912     {
10913       gfc_symtree* overridden;
10914       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
10915                                             true, NULL);
10916
10917       if (overridden && overridden->n.tb)
10918         st->n.tb->overridden = overridden->n.tb;
10919     }
10920
10921   /* Resolve using worker function.  */
10922   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
10923 }
10924
10925
10926 /* Retrieve the target-procedure of an operator binding and do some checks in
10927    common for intrinsic and user-defined type-bound operators.  */
10928
10929 static gfc_symbol*
10930 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
10931 {
10932   gfc_symbol* target_proc;
10933
10934   gcc_assert (target->specific && !target->specific->is_generic);
10935   target_proc = target->specific->u.specific->n.sym;
10936   gcc_assert (target_proc);
10937
10938   /* All operator bindings must have a passed-object dummy argument.  */
10939   if (target->specific->nopass)
10940     {
10941       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
10942       return NULL;
10943     }
10944
10945   return target_proc;
10946 }
10947
10948
10949 /* Resolve a type-bound intrinsic operator.  */
10950
10951 static gfc_try
10952 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
10953                                 gfc_typebound_proc* p)
10954 {
10955   gfc_symbol* super_type;
10956   gfc_tbp_generic* target;
10957   
10958   /* If there's already an error here, do nothing (but don't fail again).  */
10959   if (p->error)
10960     return SUCCESS;
10961
10962   /* Operators should always be GENERIC bindings.  */
10963   gcc_assert (p->is_generic);
10964
10965   /* Look for an overridden binding.  */
10966   super_type = gfc_get_derived_super_type (derived);
10967   if (super_type && super_type->f2k_derived)
10968     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
10969                                                      op, true, NULL);
10970   else
10971     p->overridden = NULL;
10972
10973   /* Resolve general GENERIC properties using worker function.  */
10974   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
10975     goto error;
10976
10977   /* Check the targets to be procedures of correct interface.  */
10978   for (target = p->u.generic; target; target = target->next)
10979     {
10980       gfc_symbol* target_proc;
10981
10982       target_proc = get_checked_tb_operator_target (target, p->where);
10983       if (!target_proc)
10984         goto error;
10985
10986       if (!gfc_check_operator_interface (target_proc, op, p->where))
10987         goto error;
10988     }
10989
10990   return SUCCESS;
10991
10992 error:
10993   p->error = 1;
10994   return FAILURE;
10995 }
10996
10997
10998 /* Resolve a type-bound user operator (tree-walker callback).  */
10999
11000 static gfc_symbol* resolve_bindings_derived;
11001 static gfc_try resolve_bindings_result;
11002
11003 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
11004
11005 static void
11006 resolve_typebound_user_op (gfc_symtree* stree)
11007 {
11008   gfc_symbol* super_type;
11009   gfc_tbp_generic* target;
11010
11011   gcc_assert (stree && stree->n.tb);
11012
11013   if (stree->n.tb->error)
11014     return;
11015
11016   /* Operators should always be GENERIC bindings.  */
11017   gcc_assert (stree->n.tb->is_generic);
11018
11019   /* Find overridden procedure, if any.  */
11020   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11021   if (super_type && super_type->f2k_derived)
11022     {
11023       gfc_symtree* overridden;
11024       overridden = gfc_find_typebound_user_op (super_type, NULL,
11025                                                stree->name, true, NULL);
11026
11027       if (overridden && overridden->n.tb)
11028         stree->n.tb->overridden = overridden->n.tb;
11029     }
11030   else
11031     stree->n.tb->overridden = NULL;
11032
11033   /* Resolve basically using worker function.  */
11034   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
11035         == FAILURE)
11036     goto error;
11037
11038   /* Check the targets to be functions of correct interface.  */
11039   for (target = stree->n.tb->u.generic; target; target = target->next)
11040     {
11041       gfc_symbol* target_proc;
11042
11043       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
11044       if (!target_proc)
11045         goto error;
11046
11047       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
11048         goto error;
11049     }
11050
11051   return;
11052
11053 error:
11054   resolve_bindings_result = FAILURE;
11055   stree->n.tb->error = 1;
11056 }
11057
11058
11059 /* Resolve the type-bound procedures for a derived type.  */
11060
11061 static void
11062 resolve_typebound_procedure (gfc_symtree* stree)
11063 {
11064   gfc_symbol* proc;
11065   locus where;
11066   gfc_symbol* me_arg;
11067   gfc_symbol* super_type;
11068   gfc_component* comp;
11069
11070   gcc_assert (stree);
11071
11072   /* Undefined specific symbol from GENERIC target definition.  */
11073   if (!stree->n.tb)
11074     return;
11075
11076   if (stree->n.tb->error)
11077     return;
11078
11079   /* If this is a GENERIC binding, use that routine.  */
11080   if (stree->n.tb->is_generic)
11081     {
11082       if (resolve_typebound_generic (resolve_bindings_derived, stree)
11083             == FAILURE)
11084         goto error;
11085       return;
11086     }
11087
11088   /* Get the target-procedure to check it.  */
11089   gcc_assert (!stree->n.tb->is_generic);
11090   gcc_assert (stree->n.tb->u.specific);
11091   proc = stree->n.tb->u.specific->n.sym;
11092   where = stree->n.tb->where;
11093
11094   /* Default access should already be resolved from the parser.  */
11095   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
11096
11097   /* It should be a module procedure or an external procedure with explicit
11098      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
11099   if ((!proc->attr.subroutine && !proc->attr.function)
11100       || (proc->attr.proc != PROC_MODULE
11101           && proc->attr.if_source != IFSRC_IFBODY)
11102       || (proc->attr.abstract && !stree->n.tb->deferred))
11103     {
11104       gfc_error ("'%s' must be a module procedure or an external procedure with"
11105                  " an explicit interface at %L", proc->name, &where);
11106       goto error;
11107     }
11108   stree->n.tb->subroutine = proc->attr.subroutine;
11109   stree->n.tb->function = proc->attr.function;
11110
11111   /* Find the super-type of the current derived type.  We could do this once and
11112      store in a global if speed is needed, but as long as not I believe this is
11113      more readable and clearer.  */
11114   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11115
11116   /* If PASS, resolve and check arguments if not already resolved / loaded
11117      from a .mod file.  */
11118   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
11119     {
11120       if (stree->n.tb->pass_arg)
11121         {
11122           gfc_formal_arglist* i;
11123
11124           /* If an explicit passing argument name is given, walk the arg-list
11125              and look for it.  */
11126
11127           me_arg = NULL;
11128           stree->n.tb->pass_arg_num = 1;
11129           for (i = proc->formal; i; i = i->next)
11130             {
11131               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
11132                 {
11133                   me_arg = i->sym;
11134                   break;
11135                 }
11136               ++stree->n.tb->pass_arg_num;
11137             }
11138
11139           if (!me_arg)
11140             {
11141               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
11142                          " argument '%s'",
11143                          proc->name, stree->n.tb->pass_arg, &where,
11144                          stree->n.tb->pass_arg);
11145               goto error;
11146             }
11147         }
11148       else
11149         {
11150           /* Otherwise, take the first one; there should in fact be at least
11151              one.  */
11152           stree->n.tb->pass_arg_num = 1;
11153           if (!proc->formal)
11154             {
11155               gfc_error ("Procedure '%s' with PASS at %L must have at"
11156                          " least one argument", proc->name, &where);
11157               goto error;
11158             }
11159           me_arg = proc->formal->sym;
11160         }
11161
11162       /* Now check that the argument-type matches and the passed-object
11163          dummy argument is generally fine.  */
11164
11165       gcc_assert (me_arg);
11166
11167       if (me_arg->ts.type != BT_CLASS)
11168         {
11169           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11170                      " at %L", proc->name, &where);
11171           goto error;
11172         }
11173
11174       if (CLASS_DATA (me_arg)->ts.u.derived
11175           != resolve_bindings_derived)
11176         {
11177           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11178                      " the derived-type '%s'", me_arg->name, proc->name,
11179                      me_arg->name, &where, resolve_bindings_derived->name);
11180           goto error;
11181         }
11182   
11183       gcc_assert (me_arg->ts.type == BT_CLASS);
11184       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
11185         {
11186           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
11187                      " scalar", proc->name, &where);
11188           goto error;
11189         }
11190       if (CLASS_DATA (me_arg)->attr.allocatable)
11191         {
11192           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11193                      " be ALLOCATABLE", proc->name, &where);
11194           goto error;
11195         }
11196       if (CLASS_DATA (me_arg)->attr.class_pointer)
11197         {
11198           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11199                      " be POINTER", proc->name, &where);
11200           goto error;
11201         }
11202     }
11203
11204   /* If we are extending some type, check that we don't override a procedure
11205      flagged NON_OVERRIDABLE.  */
11206   stree->n.tb->overridden = NULL;
11207   if (super_type)
11208     {
11209       gfc_symtree* overridden;
11210       overridden = gfc_find_typebound_proc (super_type, NULL,
11211                                             stree->name, true, NULL);
11212
11213       if (overridden && overridden->n.tb)
11214         stree->n.tb->overridden = overridden->n.tb;
11215
11216       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
11217         goto error;
11218     }
11219
11220   /* See if there's a name collision with a component directly in this type.  */
11221   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
11222     if (!strcmp (comp->name, stree->name))
11223       {
11224         gfc_error ("Procedure '%s' at %L has the same name as a component of"
11225                    " '%s'",
11226                    stree->name, &where, resolve_bindings_derived->name);
11227         goto error;
11228       }
11229
11230   /* Try to find a name collision with an inherited component.  */
11231   if (super_type && gfc_find_component (super_type, stree->name, true, true))
11232     {
11233       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
11234                  " component of '%s'",
11235                  stree->name, &where, resolve_bindings_derived->name);
11236       goto error;
11237     }
11238
11239   stree->n.tb->error = 0;
11240   return;
11241
11242 error:
11243   resolve_bindings_result = FAILURE;
11244   stree->n.tb->error = 1;
11245 }
11246
11247
11248 static gfc_try
11249 resolve_typebound_procedures (gfc_symbol* derived)
11250 {
11251   int op;
11252
11253   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
11254     return SUCCESS;
11255
11256   resolve_bindings_derived = derived;
11257   resolve_bindings_result = SUCCESS;
11258
11259   /* Make sure the vtab has been generated.  */
11260   gfc_find_derived_vtab (derived);
11261
11262   if (derived->f2k_derived->tb_sym_root)
11263     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
11264                           &resolve_typebound_procedure);
11265
11266   if (derived->f2k_derived->tb_uop_root)
11267     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
11268                           &resolve_typebound_user_op);
11269
11270   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
11271     {
11272       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
11273       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
11274                                                p) == FAILURE)
11275         resolve_bindings_result = FAILURE;
11276     }
11277
11278   return resolve_bindings_result;
11279 }
11280
11281
11282 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
11283    to give all identical derived types the same backend_decl.  */
11284 static void
11285 add_dt_to_dt_list (gfc_symbol *derived)
11286 {
11287   gfc_dt_list *dt_list;
11288
11289   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
11290     if (derived == dt_list->derived)
11291       return;
11292
11293   dt_list = gfc_get_dt_list ();
11294   dt_list->next = gfc_derived_types;
11295   dt_list->derived = derived;
11296   gfc_derived_types = dt_list;
11297 }
11298
11299
11300 /* Ensure that a derived-type is really not abstract, meaning that every
11301    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
11302
11303 static gfc_try
11304 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
11305 {
11306   if (!st)
11307     return SUCCESS;
11308
11309   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
11310     return FAILURE;
11311   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
11312     return FAILURE;
11313
11314   if (st->n.tb && st->n.tb->deferred)
11315     {
11316       gfc_symtree* overriding;
11317       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
11318       if (!overriding)
11319         return FAILURE;
11320       gcc_assert (overriding->n.tb);
11321       if (overriding->n.tb->deferred)
11322         {
11323           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
11324                      " '%s' is DEFERRED and not overridden",
11325                      sub->name, &sub->declared_at, st->name);
11326           return FAILURE;
11327         }
11328     }
11329
11330   return SUCCESS;
11331 }
11332
11333 static gfc_try
11334 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
11335 {
11336   /* The algorithm used here is to recursively travel up the ancestry of sub
11337      and for each ancestor-type, check all bindings.  If any of them is
11338      DEFERRED, look it up starting from sub and see if the found (overriding)
11339      binding is not DEFERRED.
11340      This is not the most efficient way to do this, but it should be ok and is
11341      clearer than something sophisticated.  */
11342
11343   gcc_assert (ancestor && !sub->attr.abstract);
11344   
11345   if (!ancestor->attr.abstract)
11346     return SUCCESS;
11347
11348   /* Walk bindings of this ancestor.  */
11349   if (ancestor->f2k_derived)
11350     {
11351       gfc_try t;
11352       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
11353       if (t == FAILURE)
11354         return FAILURE;
11355     }
11356
11357   /* Find next ancestor type and recurse on it.  */
11358   ancestor = gfc_get_derived_super_type (ancestor);
11359   if (ancestor)
11360     return ensure_not_abstract (sub, ancestor);
11361
11362   return SUCCESS;
11363 }
11364
11365
11366 /* Resolve the components of a derived type.  */
11367
11368 static gfc_try
11369 resolve_fl_derived (gfc_symbol *sym)
11370 {
11371   gfc_symbol* super_type;
11372   gfc_component *c;
11373
11374   super_type = gfc_get_derived_super_type (sym);
11375   
11376   if (sym->attr.is_class && sym->ts.u.derived == NULL)
11377     {
11378       /* Fix up incomplete CLASS symbols.  */
11379       gfc_component *data = gfc_find_component (sym, "_data", true, true);
11380       gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true);
11381       if (vptr->ts.u.derived == NULL)
11382         {
11383           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
11384           gcc_assert (vtab);
11385           vptr->ts.u.derived = vtab->ts.u.derived;
11386         }
11387     }
11388
11389   /* F2008, C432. */
11390   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
11391     {
11392       gfc_error ("As extending type '%s' at %L has a coarray component, "
11393                  "parent type '%s' shall also have one", sym->name,
11394                  &sym->declared_at, super_type->name);
11395       return FAILURE;
11396     }
11397
11398   /* Ensure the extended type gets resolved before we do.  */
11399   if (super_type && resolve_fl_derived (super_type) == FAILURE)
11400     return FAILURE;
11401
11402   /* An ABSTRACT type must be extensible.  */
11403   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
11404     {
11405       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
11406                  sym->name, &sym->declared_at);
11407       return FAILURE;
11408     }
11409
11410   for (c = sym->components; c != NULL; c = c->next)
11411     {
11412       /* F2008, C442.  */
11413       if (c->attr.codimension /* FIXME: c->as check due to PR 43412.  */
11414           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
11415         {
11416           gfc_error ("Coarray component '%s' at %L must be allocatable with "
11417                      "deferred shape", c->name, &c->loc);
11418           return FAILURE;
11419         }
11420
11421       /* F2008, C443.  */
11422       if (c->attr.codimension && c->ts.type == BT_DERIVED
11423           && c->ts.u.derived->ts.is_iso_c)
11424         {
11425           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11426                      "shall not be a coarray", c->name, &c->loc);
11427           return FAILURE;
11428         }
11429
11430       /* F2008, C444.  */
11431       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
11432           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
11433               || c->attr.allocatable))
11434         {
11435           gfc_error ("Component '%s' at %L with coarray component "
11436                      "shall be a nonpointer, nonallocatable scalar",
11437                      c->name, &c->loc);
11438           return FAILURE;
11439         }
11440
11441       /* F2008, C448.  */
11442       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
11443         {
11444           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
11445                      "is not an array pointer", c->name, &c->loc);
11446           return FAILURE;
11447         }
11448
11449       if (c->attr.proc_pointer && c->ts.interface)
11450         {
11451           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
11452             gfc_error ("Interface '%s', used by procedure pointer component "
11453                        "'%s' at %L, is declared in a later PROCEDURE statement",
11454                        c->ts.interface->name, c->name, &c->loc);
11455
11456           /* Get the attributes from the interface (now resolved).  */
11457           if (c->ts.interface->attr.if_source
11458               || c->ts.interface->attr.intrinsic)
11459             {
11460               gfc_symbol *ifc = c->ts.interface;
11461
11462               if (ifc->formal && !ifc->formal_ns)
11463                 resolve_symbol (ifc);
11464
11465               if (ifc->attr.intrinsic)
11466                 resolve_intrinsic (ifc, &ifc->declared_at);
11467
11468               if (ifc->result)
11469                 {
11470                   c->ts = ifc->result->ts;
11471                   c->attr.allocatable = ifc->result->attr.allocatable;
11472                   c->attr.pointer = ifc->result->attr.pointer;
11473                   c->attr.dimension = ifc->result->attr.dimension;
11474                   c->as = gfc_copy_array_spec (ifc->result->as);
11475                 }
11476               else
11477                 {   
11478                   c->ts = ifc->ts;
11479                   c->attr.allocatable = ifc->attr.allocatable;
11480                   c->attr.pointer = ifc->attr.pointer;
11481                   c->attr.dimension = ifc->attr.dimension;
11482                   c->as = gfc_copy_array_spec (ifc->as);
11483                 }
11484               c->ts.interface = ifc;
11485               c->attr.function = ifc->attr.function;
11486               c->attr.subroutine = ifc->attr.subroutine;
11487               gfc_copy_formal_args_ppc (c, ifc);
11488
11489               c->attr.pure = ifc->attr.pure;
11490               c->attr.elemental = ifc->attr.elemental;
11491               c->attr.recursive = ifc->attr.recursive;
11492               c->attr.always_explicit = ifc->attr.always_explicit;
11493               c->attr.ext_attr |= ifc->attr.ext_attr;
11494               /* Replace symbols in array spec.  */
11495               if (c->as)
11496                 {
11497                   int i;
11498                   for (i = 0; i < c->as->rank; i++)
11499                     {
11500                       gfc_expr_replace_comp (c->as->lower[i], c);
11501                       gfc_expr_replace_comp (c->as->upper[i], c);
11502                     }
11503                 }
11504               /* Copy char length.  */
11505               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11506                 {
11507                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11508                   gfc_expr_replace_comp (cl->length, c);
11509                   if (cl->length && !cl->resolved
11510                         && gfc_resolve_expr (cl->length) == FAILURE)
11511                     return FAILURE;
11512                   c->ts.u.cl = cl;
11513                 }
11514             }
11515           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
11516             {
11517               gfc_error ("Interface '%s' of procedure pointer component "
11518                          "'%s' at %L must be explicit", c->ts.interface->name,
11519                          c->name, &c->loc);
11520               return FAILURE;
11521             }
11522         }
11523       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
11524         {
11525           /* Since PPCs are not implicitly typed, a PPC without an explicit
11526              interface must be a subroutine.  */
11527           gfc_add_subroutine (&c->attr, c->name, &c->loc);
11528         }
11529
11530       /* Procedure pointer components: Check PASS arg.  */
11531       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
11532           && !sym->attr.vtype)
11533         {
11534           gfc_symbol* me_arg;
11535
11536           if (c->tb->pass_arg)
11537             {
11538               gfc_formal_arglist* i;
11539
11540               /* If an explicit passing argument name is given, walk the arg-list
11541                 and look for it.  */
11542
11543               me_arg = NULL;
11544               c->tb->pass_arg_num = 1;
11545               for (i = c->formal; i; i = i->next)
11546                 {
11547                   if (!strcmp (i->sym->name, c->tb->pass_arg))
11548                     {
11549                       me_arg = i->sym;
11550                       break;
11551                     }
11552                   c->tb->pass_arg_num++;
11553                 }
11554
11555               if (!me_arg)
11556                 {
11557                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
11558                              "at %L has no argument '%s'", c->name,
11559                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
11560                   c->tb->error = 1;
11561                   return FAILURE;
11562                 }
11563             }
11564           else
11565             {
11566               /* Otherwise, take the first one; there should in fact be at least
11567                 one.  */
11568               c->tb->pass_arg_num = 1;
11569               if (!c->formal)
11570                 {
11571                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
11572                              "must have at least one argument",
11573                              c->name, &c->loc);
11574                   c->tb->error = 1;
11575                   return FAILURE;
11576                 }
11577               me_arg = c->formal->sym;
11578             }
11579
11580           /* Now check that the argument-type matches.  */
11581           gcc_assert (me_arg);
11582           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
11583               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
11584               || (me_arg->ts.type == BT_CLASS
11585                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
11586             {
11587               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11588                          " the derived type '%s'", me_arg->name, c->name,
11589                          me_arg->name, &c->loc, sym->name);
11590               c->tb->error = 1;
11591               return FAILURE;
11592             }
11593
11594           /* Check for C453.  */
11595           if (me_arg->attr.dimension)
11596             {
11597               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11598                          "must be scalar", me_arg->name, c->name, me_arg->name,
11599                          &c->loc);
11600               c->tb->error = 1;
11601               return FAILURE;
11602             }
11603
11604           if (me_arg->attr.pointer)
11605             {
11606               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11607                          "may not have the POINTER attribute", me_arg->name,
11608                          c->name, me_arg->name, &c->loc);
11609               c->tb->error = 1;
11610               return FAILURE;
11611             }
11612
11613           if (me_arg->attr.allocatable)
11614             {
11615               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11616                          "may not be ALLOCATABLE", me_arg->name, c->name,
11617                          me_arg->name, &c->loc);
11618               c->tb->error = 1;
11619               return FAILURE;
11620             }
11621
11622           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11623             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11624                        " at %L", c->name, &c->loc);
11625
11626         }
11627
11628       /* Check type-spec if this is not the parent-type component.  */
11629       if ((!sym->attr.extension || c != sym->components) && !sym->attr.vtype
11630           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11631         return FAILURE;
11632
11633       /* If this type is an extension, set the accessibility of the parent
11634          component.  */
11635       if (super_type && c == sym->components
11636           && strcmp (super_type->name, c->name) == 0)
11637         c->attr.access = super_type->attr.access;
11638       
11639       /* If this type is an extension, see if this component has the same name
11640          as an inherited type-bound procedure.  */
11641       if (super_type && !sym->attr.is_class
11642           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11643         {
11644           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11645                      " inherited type-bound procedure",
11646                      c->name, sym->name, &c->loc);
11647           return FAILURE;
11648         }
11649
11650       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer
11651             && !c->ts.deferred)
11652         {
11653          if (c->ts.u.cl->length == NULL
11654              || (resolve_charlen (c->ts.u.cl) == FAILURE)
11655              || !gfc_is_constant_expr (c->ts.u.cl->length))
11656            {
11657              gfc_error ("Character length of component '%s' needs to "
11658                         "be a constant specification expression at %L",
11659                         c->name,
11660                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
11661              return FAILURE;
11662            }
11663         }
11664
11665       if (c->ts.type == BT_CHARACTER && c->ts.deferred
11666           && !c->attr.pointer && !c->attr.allocatable)
11667         {
11668           gfc_error ("Character component '%s' of '%s' at %L with deferred "
11669                      "length must be a POINTER or ALLOCATABLE",
11670                      c->name, sym->name, &c->loc);
11671           return FAILURE;
11672         }
11673
11674       if (c->ts.type == BT_DERIVED
11675           && sym->component_access != ACCESS_PRIVATE
11676           && gfc_check_symbol_access (sym)
11677           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11678           && !c->ts.u.derived->attr.use_assoc
11679           && !gfc_check_symbol_access (c->ts.u.derived)
11680           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11681                              "is a PRIVATE type and cannot be a component of "
11682                              "'%s', which is PUBLIC at %L", c->name,
11683                              sym->name, &sym->declared_at) == FAILURE)
11684         return FAILURE;
11685
11686       if ((sym->attr.sequence || sym->attr.is_bind_c) && c->ts.type == BT_CLASS)
11687         {
11688           gfc_error ("Polymorphic component %s at %L in SEQUENCE or BIND(C) "
11689                      "type %s", c->name, &c->loc, sym->name);
11690           return FAILURE;
11691         }
11692
11693       if (sym->attr.sequence)
11694         {
11695           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
11696             {
11697               gfc_error ("Component %s of SEQUENCE type declared at %L does "
11698                          "not have the SEQUENCE attribute",
11699                          c->ts.u.derived->name, &sym->declared_at);
11700               return FAILURE;
11701             }
11702         }
11703
11704       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && !sym->attr.vtype
11705           && c->attr.pointer && c->ts.u.derived->components == NULL
11706           && !c->ts.u.derived->attr.zero_comp)
11707         {
11708           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11709                      "that has not been declared", c->name, sym->name,
11710                      &c->loc);
11711           return FAILURE;
11712         }
11713
11714       if (c->ts.type == BT_CLASS && CLASS_DATA (c)->attr.class_pointer
11715           && CLASS_DATA (c)->ts.u.derived->components == NULL
11716           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
11717         {
11718           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11719                      "that has not been declared", c->name, sym->name,
11720                      &c->loc);
11721           return FAILURE;
11722         }
11723
11724       /* C437.  */
11725       if (c->ts.type == BT_CLASS
11726           && !(CLASS_DATA (c)->attr.class_pointer
11727                || CLASS_DATA (c)->attr.allocatable))
11728         {
11729           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
11730                      "or pointer", c->name, &c->loc);
11731           return FAILURE;
11732         }
11733
11734       /* Ensure that all the derived type components are put on the
11735          derived type list; even in formal namespaces, where derived type
11736          pointer components might not have been declared.  */
11737       if (c->ts.type == BT_DERIVED
11738             && c->ts.u.derived
11739             && c->ts.u.derived->components
11740             && c->attr.pointer
11741             && sym != c->ts.u.derived)
11742         add_dt_to_dt_list (c->ts.u.derived);
11743
11744       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
11745                                            || c->attr.proc_pointer
11746                                            || c->attr.allocatable)) == FAILURE)
11747         return FAILURE;
11748     }
11749
11750   /* Resolve the type-bound procedures.  */
11751   if (resolve_typebound_procedures (sym) == FAILURE)
11752     return FAILURE;
11753
11754   /* Resolve the finalizer procedures.  */
11755   if (gfc_resolve_finalizers (sym) == FAILURE)
11756     return FAILURE;
11757
11758   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11759      all DEFERRED bindings are overridden.  */
11760   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11761       && !sym->attr.is_class
11762       && ensure_not_abstract (sym, super_type) == FAILURE)
11763     return FAILURE;
11764
11765   /* Add derived type to the derived type list.  */
11766   add_dt_to_dt_list (sym);
11767
11768   return SUCCESS;
11769 }
11770
11771
11772 static gfc_try
11773 resolve_fl_namelist (gfc_symbol *sym)
11774 {
11775   gfc_namelist *nl;
11776   gfc_symbol *nlsym;
11777
11778   for (nl = sym->namelist; nl; nl = nl->next)
11779     {
11780       /* Check again, the check in match only works if NAMELIST comes
11781          after the decl.  */
11782       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SIZE)
11783         {
11784           gfc_error ("Assumed size array '%s' in namelist '%s' at %L is not "
11785                      "allowed", nl->sym->name, sym->name, &sym->declared_at);
11786           return FAILURE;
11787         }
11788
11789       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
11790           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: NAMELIST array "
11791                              "object '%s' with assumed shape in namelist "
11792                              "'%s' at %L", nl->sym->name, sym->name,
11793                              &sym->declared_at) == FAILURE)
11794         return FAILURE;
11795
11796       if (is_non_constant_shape_array (nl->sym)
11797           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST array "
11798                              "object '%s' with nonconstant shape in namelist "
11799                              "'%s' at %L", nl->sym->name, sym->name,
11800                              &sym->declared_at) == FAILURE)
11801         return FAILURE;
11802
11803       if (nl->sym->ts.type == BT_CHARACTER
11804           && (nl->sym->ts.u.cl->length == NULL
11805               || !gfc_is_constant_expr (nl->sym->ts.u.cl->length))
11806           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
11807                              "'%s' with nonconstant character length in "
11808                              "namelist '%s' at %L", nl->sym->name, sym->name,
11809                              &sym->declared_at) == FAILURE)
11810         return FAILURE;
11811
11812       /* FIXME: Once UDDTIO is implemented, the following can be
11813          removed.  */
11814       if (nl->sym->ts.type == BT_CLASS)
11815         {
11816           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L is "
11817                      "polymorphic and requires a defined input/output "
11818                      "procedure", nl->sym->name, sym->name, &sym->declared_at);
11819           return FAILURE;
11820         }
11821
11822       if (nl->sym->ts.type == BT_DERIVED
11823           && (nl->sym->ts.u.derived->attr.alloc_comp
11824               || nl->sym->ts.u.derived->attr.pointer_comp))
11825         {
11826           if (gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
11827                               "'%s' in namelist '%s' at %L with ALLOCATABLE "
11828                               "or POINTER components", nl->sym->name,
11829                               sym->name, &sym->declared_at) == FAILURE)
11830             return FAILURE;
11831
11832          /* FIXME: Once UDDTIO is implemented, the following can be
11833             removed.  */
11834           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L has "
11835                      "ALLOCATABLE or POINTER components and thus requires "
11836                      "a defined input/output procedure", nl->sym->name,
11837                      sym->name, &sym->declared_at);
11838           return FAILURE;
11839         }
11840     }
11841
11842   /* Reject PRIVATE objects in a PUBLIC namelist.  */
11843   if (gfc_check_symbol_access (sym))
11844     {
11845       for (nl = sym->namelist; nl; nl = nl->next)
11846         {
11847           if (!nl->sym->attr.use_assoc
11848               && !is_sym_host_assoc (nl->sym, sym->ns)
11849               && !gfc_check_symbol_access (nl->sym))
11850             {
11851               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
11852                          "cannot be member of PUBLIC namelist '%s' at %L",
11853                          nl->sym->name, sym->name, &sym->declared_at);
11854               return FAILURE;
11855             }
11856
11857           /* Types with private components that came here by USE-association.  */
11858           if (nl->sym->ts.type == BT_DERIVED
11859               && derived_inaccessible (nl->sym->ts.u.derived))
11860             {
11861               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
11862                          "components and cannot be member of namelist '%s' at %L",
11863                          nl->sym->name, sym->name, &sym->declared_at);
11864               return FAILURE;
11865             }
11866
11867           /* Types with private components that are defined in the same module.  */
11868           if (nl->sym->ts.type == BT_DERIVED
11869               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
11870               && nl->sym->ts.u.derived->attr.private_comp)
11871             {
11872               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
11873                          "cannot be a member of PUBLIC namelist '%s' at %L",
11874                          nl->sym->name, sym->name, &sym->declared_at);
11875               return FAILURE;
11876             }
11877         }
11878     }
11879
11880
11881   /* 14.1.2 A module or internal procedure represent local entities
11882      of the same type as a namelist member and so are not allowed.  */
11883   for (nl = sym->namelist; nl; nl = nl->next)
11884     {
11885       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
11886         continue;
11887
11888       if (nl->sym->attr.function && nl->sym == nl->sym->result)
11889         if ((nl->sym == sym->ns->proc_name)
11890                ||
11891             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
11892           continue;
11893
11894       nlsym = NULL;
11895       if (nl->sym && nl->sym->name)
11896         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
11897       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
11898         {
11899           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
11900                      "attribute in '%s' at %L", nlsym->name,
11901                      &sym->declared_at);
11902           return FAILURE;
11903         }
11904     }
11905
11906   return SUCCESS;
11907 }
11908
11909
11910 static gfc_try
11911 resolve_fl_parameter (gfc_symbol *sym)
11912 {
11913   /* A parameter array's shape needs to be constant.  */
11914   if (sym->as != NULL 
11915       && (sym->as->type == AS_DEFERRED
11916           || is_non_constant_shape_array (sym)))
11917     {
11918       gfc_error ("Parameter array '%s' at %L cannot be automatic "
11919                  "or of deferred shape", sym->name, &sym->declared_at);
11920       return FAILURE;
11921     }
11922
11923   /* Make sure a parameter that has been implicitly typed still
11924      matches the implicit type, since PARAMETER statements can precede
11925      IMPLICIT statements.  */
11926   if (sym->attr.implicit_type
11927       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
11928                                                              sym->ns)))
11929     {
11930       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
11931                  "later IMPLICIT type", sym->name, &sym->declared_at);
11932       return FAILURE;
11933     }
11934
11935   /* Make sure the types of derived parameters are consistent.  This
11936      type checking is deferred until resolution because the type may
11937      refer to a derived type from the host.  */
11938   if (sym->ts.type == BT_DERIVED
11939       && !gfc_compare_types (&sym->ts, &sym->value->ts))
11940     {
11941       gfc_error ("Incompatible derived type in PARAMETER at %L",
11942                  &sym->value->where);
11943       return FAILURE;
11944     }
11945   return SUCCESS;
11946 }
11947
11948
11949 /* Do anything necessary to resolve a symbol.  Right now, we just
11950    assume that an otherwise unknown symbol is a variable.  This sort
11951    of thing commonly happens for symbols in module.  */
11952
11953 static void
11954 resolve_symbol (gfc_symbol *sym)
11955 {
11956   int check_constant, mp_flag;
11957   gfc_symtree *symtree;
11958   gfc_symtree *this_symtree;
11959   gfc_namespace *ns;
11960   gfc_component *c;
11961
11962   /* Avoid double resolution of function result symbols.  */
11963   if ((sym->result || sym->attr.result) && !sym->attr.dummy
11964       && (sym->ns != gfc_current_ns))
11965     return;
11966   
11967   if (sym->attr.flavor == FL_UNKNOWN)
11968     {
11969
11970     /* If we find that a flavorless symbol is an interface in one of the
11971        parent namespaces, find its symtree in this namespace, free the
11972        symbol and set the symtree to point to the interface symbol.  */
11973       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
11974         {
11975           symtree = gfc_find_symtree (ns->sym_root, sym->name);
11976           if (symtree && (symtree->n.sym->generic ||
11977                           (symtree->n.sym->attr.flavor == FL_PROCEDURE
11978                            && sym->ns->construct_entities)))
11979             {
11980               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
11981                                                sym->name);
11982               gfc_release_symbol (sym);
11983               symtree->n.sym->refs++;
11984               this_symtree->n.sym = symtree->n.sym;
11985               return;
11986             }
11987         }
11988
11989       /* Otherwise give it a flavor according to such attributes as
11990          it has.  */
11991       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
11992         sym->attr.flavor = FL_VARIABLE;
11993       else
11994         {
11995           sym->attr.flavor = FL_PROCEDURE;
11996           if (sym->attr.dimension)
11997             sym->attr.function = 1;
11998         }
11999     }
12000
12001   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
12002     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
12003
12004   if (sym->attr.procedure && sym->ts.interface
12005       && sym->attr.if_source != IFSRC_DECL
12006       && resolve_procedure_interface (sym) == FAILURE)
12007     return;
12008
12009   if (sym->attr.is_protected && !sym->attr.proc_pointer
12010       && (sym->attr.procedure || sym->attr.external))
12011     {
12012       if (sym->attr.external)
12013         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
12014                    "at %L", &sym->declared_at);
12015       else
12016         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
12017                    "at %L", &sym->declared_at);
12018
12019       return;
12020     }
12021
12022
12023   /* F2008, C530. */
12024   if (sym->attr.contiguous
12025       && (!sym->attr.dimension || (sym->as->type != AS_ASSUMED_SHAPE
12026                                    && !sym->attr.pointer)))
12027     {
12028       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
12029                   "array pointer or an assumed-shape array", sym->name,
12030                   &sym->declared_at);
12031       return;
12032     }
12033
12034   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
12035     return;
12036
12037   /* Symbols that are module procedures with results (functions) have
12038      the types and array specification copied for type checking in
12039      procedures that call them, as well as for saving to a module
12040      file.  These symbols can't stand the scrutiny that their results
12041      can.  */
12042   mp_flag = (sym->result != NULL && sym->result != sym);
12043
12044   /* Make sure that the intrinsic is consistent with its internal 
12045      representation. This needs to be done before assigning a default 
12046      type to avoid spurious warnings.  */
12047   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
12048       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
12049     return;
12050
12051   /* Resolve associate names.  */
12052   if (sym->assoc)
12053     resolve_assoc_var (sym, true);
12054
12055   /* Assign default type to symbols that need one and don't have one.  */
12056   if (sym->ts.type == BT_UNKNOWN)
12057     {
12058       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
12059         gfc_set_default_type (sym, 1, NULL);
12060
12061       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
12062           && !sym->attr.function && !sym->attr.subroutine
12063           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
12064         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
12065
12066       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12067         {
12068           /* The specific case of an external procedure should emit an error
12069              in the case that there is no implicit type.  */
12070           if (!mp_flag)
12071             gfc_set_default_type (sym, sym->attr.external, NULL);
12072           else
12073             {
12074               /* Result may be in another namespace.  */
12075               resolve_symbol (sym->result);
12076
12077               if (!sym->result->attr.proc_pointer)
12078                 {
12079                   sym->ts = sym->result->ts;
12080                   sym->as = gfc_copy_array_spec (sym->result->as);
12081                   sym->attr.dimension = sym->result->attr.dimension;
12082                   sym->attr.pointer = sym->result->attr.pointer;
12083                   sym->attr.allocatable = sym->result->attr.allocatable;
12084                   sym->attr.contiguous = sym->result->attr.contiguous;
12085                 }
12086             }
12087         }
12088     }
12089
12090   /* Assumed size arrays and assumed shape arrays must be dummy
12091      arguments.  Array-spec's of implied-shape should have been resolved to
12092      AS_EXPLICIT already.  */
12093
12094   if (sym->as)
12095     {
12096       gcc_assert (sym->as->type != AS_IMPLIED_SHAPE);
12097       if (((sym->as->type == AS_ASSUMED_SIZE && !sym->as->cp_was_assumed)
12098            || sym->as->type == AS_ASSUMED_SHAPE)
12099           && sym->attr.dummy == 0)
12100         {
12101           if (sym->as->type == AS_ASSUMED_SIZE)
12102             gfc_error ("Assumed size array at %L must be a dummy argument",
12103                        &sym->declared_at);
12104           else
12105             gfc_error ("Assumed shape array at %L must be a dummy argument",
12106                        &sym->declared_at);
12107           return;
12108         }
12109     }
12110
12111   /* Make sure symbols with known intent or optional are really dummy
12112      variable.  Because of ENTRY statement, this has to be deferred
12113      until resolution time.  */
12114
12115   if (!sym->attr.dummy
12116       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
12117     {
12118       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
12119       return;
12120     }
12121
12122   if (sym->attr.value && !sym->attr.dummy)
12123     {
12124       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
12125                  "it is not a dummy argument", sym->name, &sym->declared_at);
12126       return;
12127     }
12128
12129   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
12130     {
12131       gfc_charlen *cl = sym->ts.u.cl;
12132       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
12133         {
12134           gfc_error ("Character dummy variable '%s' at %L with VALUE "
12135                      "attribute must have constant length",
12136                      sym->name, &sym->declared_at);
12137           return;
12138         }
12139
12140       if (sym->ts.is_c_interop
12141           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
12142         {
12143           gfc_error ("C interoperable character dummy variable '%s' at %L "
12144                      "with VALUE attribute must have length one",
12145                      sym->name, &sym->declared_at);
12146           return;
12147         }
12148     }
12149
12150   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
12151      do this for something that was implicitly typed because that is handled
12152      in gfc_set_default_type.  Handle dummy arguments and procedure
12153      definitions separately.  Also, anything that is use associated is not
12154      handled here but instead is handled in the module it is declared in.
12155      Finally, derived type definitions are allowed to be BIND(C) since that
12156      only implies that they're interoperable, and they are checked fully for
12157      interoperability when a variable is declared of that type.  */
12158   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
12159       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
12160       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
12161     {
12162       gfc_try t = SUCCESS;
12163       
12164       /* First, make sure the variable is declared at the
12165          module-level scope (J3/04-007, Section 15.3).  */
12166       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
12167           sym->attr.in_common == 0)
12168         {
12169           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
12170                      "is neither a COMMON block nor declared at the "
12171                      "module level scope", sym->name, &(sym->declared_at));
12172           t = FAILURE;
12173         }
12174       else if (sym->common_head != NULL)
12175         {
12176           t = verify_com_block_vars_c_interop (sym->common_head);
12177         }
12178       else
12179         {
12180           /* If type() declaration, we need to verify that the components
12181              of the given type are all C interoperable, etc.  */
12182           if (sym->ts.type == BT_DERIVED &&
12183               sym->ts.u.derived->attr.is_c_interop != 1)
12184             {
12185               /* Make sure the user marked the derived type as BIND(C).  If
12186                  not, call the verify routine.  This could print an error
12187                  for the derived type more than once if multiple variables
12188                  of that type are declared.  */
12189               if (sym->ts.u.derived->attr.is_bind_c != 1)
12190                 verify_bind_c_derived_type (sym->ts.u.derived);
12191               t = FAILURE;
12192             }
12193           
12194           /* Verify the variable itself as C interoperable if it
12195              is BIND(C).  It is not possible for this to succeed if
12196              the verify_bind_c_derived_type failed, so don't have to handle
12197              any error returned by verify_bind_c_derived_type.  */
12198           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
12199                                  sym->common_block);
12200         }
12201
12202       if (t == FAILURE)
12203         {
12204           /* clear the is_bind_c flag to prevent reporting errors more than
12205              once if something failed.  */
12206           sym->attr.is_bind_c = 0;
12207           return;
12208         }
12209     }
12210
12211   /* If a derived type symbol has reached this point, without its
12212      type being declared, we have an error.  Notice that most
12213      conditions that produce undefined derived types have already
12214      been dealt with.  However, the likes of:
12215      implicit type(t) (t) ..... call foo (t) will get us here if
12216      the type is not declared in the scope of the implicit
12217      statement. Change the type to BT_UNKNOWN, both because it is so
12218      and to prevent an ICE.  */
12219   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
12220       && !sym->ts.u.derived->attr.zero_comp)
12221     {
12222       gfc_error ("The derived type '%s' at %L is of type '%s', "
12223                  "which has not been defined", sym->name,
12224                   &sym->declared_at, sym->ts.u.derived->name);
12225       sym->ts.type = BT_UNKNOWN;
12226       return;
12227     }
12228
12229   /* Make sure that the derived type has been resolved and that the
12230      derived type is visible in the symbol's namespace, if it is a
12231      module function and is not PRIVATE.  */
12232   if (sym->ts.type == BT_DERIVED
12233         && sym->ts.u.derived->attr.use_assoc
12234         && sym->ns->proc_name
12235         && sym->ns->proc_name->attr.flavor == FL_MODULE)
12236     {
12237       gfc_symbol *ds;
12238
12239       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
12240         return;
12241
12242       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
12243       if (!ds && sym->attr.function && gfc_check_symbol_access (sym))
12244         {
12245           symtree = gfc_new_symtree (&sym->ns->sym_root,
12246                                      sym->ts.u.derived->name);
12247           symtree->n.sym = sym->ts.u.derived;
12248           sym->ts.u.derived->refs++;
12249         }
12250     }
12251
12252   /* Unless the derived-type declaration is use associated, Fortran 95
12253      does not allow public entries of private derived types.
12254      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
12255      161 in 95-006r3.  */
12256   if (sym->ts.type == BT_DERIVED
12257       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
12258       && !sym->ts.u.derived->attr.use_assoc
12259       && gfc_check_symbol_access (sym)
12260       && !gfc_check_symbol_access (sym->ts.u.derived)
12261       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
12262                          "of PRIVATE derived type '%s'",
12263                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
12264                          : "variable", sym->name, &sym->declared_at,
12265                          sym->ts.u.derived->name) == FAILURE)
12266     return;
12267
12268   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
12269      default initialization is defined (5.1.2.4.4).  */
12270   if (sym->ts.type == BT_DERIVED
12271       && sym->attr.dummy
12272       && sym->attr.intent == INTENT_OUT
12273       && sym->as
12274       && sym->as->type == AS_ASSUMED_SIZE)
12275     {
12276       for (c = sym->ts.u.derived->components; c; c = c->next)
12277         {
12278           if (c->initializer)
12279             {
12280               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
12281                          "ASSUMED SIZE and so cannot have a default initializer",
12282                          sym->name, &sym->declared_at);
12283               return;
12284             }
12285         }
12286     }
12287
12288   /* F2008, C526.  */
12289   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12290        || sym->attr.codimension)
12291       && sym->attr.result)
12292     gfc_error ("Function result '%s' at %L shall not be a coarray or have "
12293                "a coarray component", sym->name, &sym->declared_at);
12294
12295   /* F2008, C524.  */
12296   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
12297       && sym->ts.u.derived->ts.is_iso_c)
12298     gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12299                "shall not be a coarray", sym->name, &sym->declared_at);
12300
12301   /* F2008, C525.  */
12302   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp
12303       && (sym->attr.codimension || sym->attr.pointer || sym->attr.dimension
12304           || sym->attr.allocatable))
12305     gfc_error ("Variable '%s' at %L with coarray component "
12306                "shall be a nonpointer, nonallocatable scalar",
12307                sym->name, &sym->declared_at);
12308
12309   /* F2008, C526.  The function-result case was handled above.  */
12310   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12311        || sym->attr.codimension)
12312       && !(sym->attr.allocatable || sym->attr.dummy || sym->attr.save
12313            || sym->ns->proc_name->attr.flavor == FL_MODULE
12314            || sym->ns->proc_name->attr.is_main_program
12315            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
12316     gfc_error ("Variable '%s' at %L is a coarray or has a coarray "
12317                "component and is not ALLOCATABLE, SAVE nor a "
12318                "dummy argument", sym->name, &sym->declared_at);
12319   /* F2008, C528.  */  /* FIXME: sym->as check due to PR 43412.  */
12320   else if (sym->attr.codimension && !sym->attr.allocatable
12321       && sym->as && sym->as->cotype == AS_DEFERRED)
12322     gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
12323                 "deferred shape", sym->name, &sym->declared_at);
12324   else if (sym->attr.codimension && sym->attr.allocatable
12325       && (sym->as->type != AS_DEFERRED || sym->as->cotype != AS_DEFERRED))
12326     gfc_error ("Allocatable coarray variable '%s' at %L must have "
12327                "deferred shape", sym->name, &sym->declared_at);
12328
12329
12330   /* F2008, C541.  */
12331   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12332        || (sym->attr.codimension && sym->attr.allocatable))
12333       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
12334     gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
12335                "allocatable coarray or have coarray components",
12336                sym->name, &sym->declared_at);
12337
12338   if (sym->attr.codimension && sym->attr.dummy
12339       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
12340     gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
12341                "procedure '%s'", sym->name, &sym->declared_at,
12342                sym->ns->proc_name->name);
12343
12344   switch (sym->attr.flavor)
12345     {
12346     case FL_VARIABLE:
12347       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
12348         return;
12349       break;
12350
12351     case FL_PROCEDURE:
12352       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
12353         return;
12354       break;
12355
12356     case FL_NAMELIST:
12357       if (resolve_fl_namelist (sym) == FAILURE)
12358         return;
12359       break;
12360
12361     case FL_PARAMETER:
12362       if (resolve_fl_parameter (sym) == FAILURE)
12363         return;
12364       break;
12365
12366     default:
12367       break;
12368     }
12369
12370   /* Resolve array specifier. Check as well some constraints
12371      on COMMON blocks.  */
12372
12373   check_constant = sym->attr.in_common && !sym->attr.pointer;
12374
12375   /* Set the formal_arg_flag so that check_conflict will not throw
12376      an error for host associated variables in the specification
12377      expression for an array_valued function.  */
12378   if (sym->attr.function && sym->as)
12379     formal_arg_flag = 1;
12380
12381   gfc_resolve_array_spec (sym->as, check_constant);
12382
12383   formal_arg_flag = 0;
12384
12385   /* Resolve formal namespaces.  */
12386   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
12387       && !sym->attr.contained && !sym->attr.intrinsic)
12388     gfc_resolve (sym->formal_ns);
12389
12390   /* Make sure the formal namespace is present.  */
12391   if (sym->formal && !sym->formal_ns)
12392     {
12393       gfc_formal_arglist *formal = sym->formal;
12394       while (formal && !formal->sym)
12395         formal = formal->next;
12396
12397       if (formal)
12398         {
12399           sym->formal_ns = formal->sym->ns;
12400           sym->formal_ns->refs++;
12401         }
12402     }
12403
12404   /* Check threadprivate restrictions.  */
12405   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
12406       && (!sym->attr.in_common
12407           && sym->module == NULL
12408           && (sym->ns->proc_name == NULL
12409               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
12410     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
12411
12412   /* If we have come this far we can apply default-initializers, as
12413      described in 14.7.5, to those variables that have not already
12414      been assigned one.  */
12415   if (sym->ts.type == BT_DERIVED
12416       && sym->ns == gfc_current_ns
12417       && !sym->value
12418       && !sym->attr.allocatable
12419       && !sym->attr.alloc_comp)
12420     {
12421       symbol_attribute *a = &sym->attr;
12422
12423       if ((!a->save && !a->dummy && !a->pointer
12424            && !a->in_common && !a->use_assoc
12425            && (a->referenced || a->result)
12426            && !(a->function && sym != sym->result))
12427           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
12428         apply_default_init (sym);
12429     }
12430
12431   if (sym->ts.type == BT_CLASS && sym->ns == gfc_current_ns
12432       && sym->attr.dummy && sym->attr.intent == INTENT_OUT
12433       && !CLASS_DATA (sym)->attr.class_pointer
12434       && !CLASS_DATA (sym)->attr.allocatable)
12435     apply_default_init (sym);
12436
12437   /* If this symbol has a type-spec, check it.  */
12438   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
12439       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
12440     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
12441           == FAILURE)
12442       return;
12443 }
12444
12445
12446 /************* Resolve DATA statements *************/
12447
12448 static struct
12449 {
12450   gfc_data_value *vnode;
12451   mpz_t left;
12452 }
12453 values;
12454
12455
12456 /* Advance the values structure to point to the next value in the data list.  */
12457
12458 static gfc_try
12459 next_data_value (void)
12460 {
12461   while (mpz_cmp_ui (values.left, 0) == 0)
12462     {
12463
12464       if (values.vnode->next == NULL)
12465         return FAILURE;
12466
12467       values.vnode = values.vnode->next;
12468       mpz_set (values.left, values.vnode->repeat);
12469     }
12470
12471   return SUCCESS;
12472 }
12473
12474
12475 static gfc_try
12476 check_data_variable (gfc_data_variable *var, locus *where)
12477 {
12478   gfc_expr *e;
12479   mpz_t size;
12480   mpz_t offset;
12481   gfc_try t;
12482   ar_type mark = AR_UNKNOWN;
12483   int i;
12484   mpz_t section_index[GFC_MAX_DIMENSIONS];
12485   gfc_ref *ref;
12486   gfc_array_ref *ar;
12487   gfc_symbol *sym;
12488   int has_pointer;
12489
12490   if (gfc_resolve_expr (var->expr) == FAILURE)
12491     return FAILURE;
12492
12493   ar = NULL;
12494   mpz_init_set_si (offset, 0);
12495   e = var->expr;
12496
12497   if (e->expr_type != EXPR_VARIABLE)
12498     gfc_internal_error ("check_data_variable(): Bad expression");
12499
12500   sym = e->symtree->n.sym;
12501
12502   if (sym->ns->is_block_data && !sym->attr.in_common)
12503     {
12504       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
12505                  sym->name, &sym->declared_at);
12506     }
12507
12508   if (e->ref == NULL && sym->as)
12509     {
12510       gfc_error ("DATA array '%s' at %L must be specified in a previous"
12511                  " declaration", sym->name, where);
12512       return FAILURE;
12513     }
12514
12515   has_pointer = sym->attr.pointer;
12516
12517   if (gfc_is_coindexed (e))
12518     {
12519       gfc_error ("DATA element '%s' at %L cannot have a coindex", sym->name,
12520                  where);
12521       return FAILURE;
12522     }
12523
12524   for (ref = e->ref; ref; ref = ref->next)
12525     {
12526       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
12527         has_pointer = 1;
12528
12529       if (has_pointer
12530             && ref->type == REF_ARRAY
12531             && ref->u.ar.type != AR_FULL)
12532           {
12533             gfc_error ("DATA element '%s' at %L is a pointer and so must "
12534                         "be a full array", sym->name, where);
12535             return FAILURE;
12536           }
12537     }
12538
12539   if (e->rank == 0 || has_pointer)
12540     {
12541       mpz_init_set_ui (size, 1);
12542       ref = NULL;
12543     }
12544   else
12545     {
12546       ref = e->ref;
12547
12548       /* Find the array section reference.  */
12549       for (ref = e->ref; ref; ref = ref->next)
12550         {
12551           if (ref->type != REF_ARRAY)
12552             continue;
12553           if (ref->u.ar.type == AR_ELEMENT)
12554             continue;
12555           break;
12556         }
12557       gcc_assert (ref);
12558
12559       /* Set marks according to the reference pattern.  */
12560       switch (ref->u.ar.type)
12561         {
12562         case AR_FULL:
12563           mark = AR_FULL;
12564           break;
12565
12566         case AR_SECTION:
12567           ar = &ref->u.ar;
12568           /* Get the start position of array section.  */
12569           gfc_get_section_index (ar, section_index, &offset);
12570           mark = AR_SECTION;
12571           break;
12572
12573         default:
12574           gcc_unreachable ();
12575         }
12576
12577       if (gfc_array_size (e, &size) == FAILURE)
12578         {
12579           gfc_error ("Nonconstant array section at %L in DATA statement",
12580                      &e->where);
12581           mpz_clear (offset);
12582           return FAILURE;
12583         }
12584     }
12585
12586   t = SUCCESS;
12587
12588   while (mpz_cmp_ui (size, 0) > 0)
12589     {
12590       if (next_data_value () == FAILURE)
12591         {
12592           gfc_error ("DATA statement at %L has more variables than values",
12593                      where);
12594           t = FAILURE;
12595           break;
12596         }
12597
12598       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
12599       if (t == FAILURE)
12600         break;
12601
12602       /* If we have more than one element left in the repeat count,
12603          and we have more than one element left in the target variable,
12604          then create a range assignment.  */
12605       /* FIXME: Only done for full arrays for now, since array sections
12606          seem tricky.  */
12607       if (mark == AR_FULL && ref && ref->next == NULL
12608           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
12609         {
12610           mpz_t range;
12611
12612           if (mpz_cmp (size, values.left) >= 0)
12613             {
12614               mpz_init_set (range, values.left);
12615               mpz_sub (size, size, values.left);
12616               mpz_set_ui (values.left, 0);
12617             }
12618           else
12619             {
12620               mpz_init_set (range, size);
12621               mpz_sub (values.left, values.left, size);
12622               mpz_set_ui (size, 0);
12623             }
12624
12625           t = gfc_assign_data_value_range (var->expr, values.vnode->expr,
12626                                            offset, range);
12627
12628           mpz_add (offset, offset, range);
12629           mpz_clear (range);
12630
12631           if (t == FAILURE)
12632             break;
12633         }
12634
12635       /* Assign initial value to symbol.  */
12636       else
12637         {
12638           mpz_sub_ui (values.left, values.left, 1);
12639           mpz_sub_ui (size, size, 1);
12640
12641           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
12642           if (t == FAILURE)
12643             break;
12644
12645           if (mark == AR_FULL)
12646             mpz_add_ui (offset, offset, 1);
12647
12648           /* Modify the array section indexes and recalculate the offset
12649              for next element.  */
12650           else if (mark == AR_SECTION)
12651             gfc_advance_section (section_index, ar, &offset);
12652         }
12653     }
12654
12655   if (mark == AR_SECTION)
12656     {
12657       for (i = 0; i < ar->dimen; i++)
12658         mpz_clear (section_index[i]);
12659     }
12660
12661   mpz_clear (size);
12662   mpz_clear (offset);
12663
12664   return t;
12665 }
12666
12667
12668 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
12669
12670 /* Iterate over a list of elements in a DATA statement.  */
12671
12672 static gfc_try
12673 traverse_data_list (gfc_data_variable *var, locus *where)
12674 {
12675   mpz_t trip;
12676   iterator_stack frame;
12677   gfc_expr *e, *start, *end, *step;
12678   gfc_try retval = SUCCESS;
12679
12680   mpz_init (frame.value);
12681   mpz_init (trip);
12682
12683   start = gfc_copy_expr (var->iter.start);
12684   end = gfc_copy_expr (var->iter.end);
12685   step = gfc_copy_expr (var->iter.step);
12686
12687   if (gfc_simplify_expr (start, 1) == FAILURE
12688       || start->expr_type != EXPR_CONSTANT)
12689     {
12690       gfc_error ("start of implied-do loop at %L could not be "
12691                  "simplified to a constant value", &start->where);
12692       retval = FAILURE;
12693       goto cleanup;
12694     }
12695   if (gfc_simplify_expr (end, 1) == FAILURE
12696       || end->expr_type != EXPR_CONSTANT)
12697     {
12698       gfc_error ("end of implied-do loop at %L could not be "
12699                  "simplified to a constant value", &start->where);
12700       retval = FAILURE;
12701       goto cleanup;
12702     }
12703   if (gfc_simplify_expr (step, 1) == FAILURE
12704       || step->expr_type != EXPR_CONSTANT)
12705     {
12706       gfc_error ("step of implied-do loop at %L could not be "
12707                  "simplified to a constant value", &start->where);
12708       retval = FAILURE;
12709       goto cleanup;
12710     }
12711
12712   mpz_set (trip, end->value.integer);
12713   mpz_sub (trip, trip, start->value.integer);
12714   mpz_add (trip, trip, step->value.integer);
12715
12716   mpz_div (trip, trip, step->value.integer);
12717
12718   mpz_set (frame.value, start->value.integer);
12719
12720   frame.prev = iter_stack;
12721   frame.variable = var->iter.var->symtree;
12722   iter_stack = &frame;
12723
12724   while (mpz_cmp_ui (trip, 0) > 0)
12725     {
12726       if (traverse_data_var (var->list, where) == FAILURE)
12727         {
12728           retval = FAILURE;
12729           goto cleanup;
12730         }
12731
12732       e = gfc_copy_expr (var->expr);
12733       if (gfc_simplify_expr (e, 1) == FAILURE)
12734         {
12735           gfc_free_expr (e);
12736           retval = FAILURE;
12737           goto cleanup;
12738         }
12739
12740       mpz_add (frame.value, frame.value, step->value.integer);
12741
12742       mpz_sub_ui (trip, trip, 1);
12743     }
12744
12745 cleanup:
12746   mpz_clear (frame.value);
12747   mpz_clear (trip);
12748
12749   gfc_free_expr (start);
12750   gfc_free_expr (end);
12751   gfc_free_expr (step);
12752
12753   iter_stack = frame.prev;
12754   return retval;
12755 }
12756
12757
12758 /* Type resolve variables in the variable list of a DATA statement.  */
12759
12760 static gfc_try
12761 traverse_data_var (gfc_data_variable *var, locus *where)
12762 {
12763   gfc_try t;
12764
12765   for (; var; var = var->next)
12766     {
12767       if (var->expr == NULL)
12768         t = traverse_data_list (var, where);
12769       else
12770         t = check_data_variable (var, where);
12771
12772       if (t == FAILURE)
12773         return FAILURE;
12774     }
12775
12776   return SUCCESS;
12777 }
12778
12779
12780 /* Resolve the expressions and iterators associated with a data statement.
12781    This is separate from the assignment checking because data lists should
12782    only be resolved once.  */
12783
12784 static gfc_try
12785 resolve_data_variables (gfc_data_variable *d)
12786 {
12787   for (; d; d = d->next)
12788     {
12789       if (d->list == NULL)
12790         {
12791           if (gfc_resolve_expr (d->expr) == FAILURE)
12792             return FAILURE;
12793         }
12794       else
12795         {
12796           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
12797             return FAILURE;
12798
12799           if (resolve_data_variables (d->list) == FAILURE)
12800             return FAILURE;
12801         }
12802     }
12803
12804   return SUCCESS;
12805 }
12806
12807
12808 /* Resolve a single DATA statement.  We implement this by storing a pointer to
12809    the value list into static variables, and then recursively traversing the
12810    variables list, expanding iterators and such.  */
12811
12812 static void
12813 resolve_data (gfc_data *d)
12814 {
12815
12816   if (resolve_data_variables (d->var) == FAILURE)
12817     return;
12818
12819   values.vnode = d->value;
12820   if (d->value == NULL)
12821     mpz_set_ui (values.left, 0);
12822   else
12823     mpz_set (values.left, d->value->repeat);
12824
12825   if (traverse_data_var (d->var, &d->where) == FAILURE)
12826     return;
12827
12828   /* At this point, we better not have any values left.  */
12829
12830   if (next_data_value () == SUCCESS)
12831     gfc_error ("DATA statement at %L has more values than variables",
12832                &d->where);
12833 }
12834
12835
12836 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
12837    accessed by host or use association, is a dummy argument to a pure function,
12838    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
12839    is storage associated with any such variable, shall not be used in the
12840    following contexts: (clients of this function).  */
12841
12842 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
12843    procedure.  Returns zero if assignment is OK, nonzero if there is a
12844    problem.  */
12845 int
12846 gfc_impure_variable (gfc_symbol *sym)
12847 {
12848   gfc_symbol *proc;
12849   gfc_namespace *ns;
12850
12851   if (sym->attr.use_assoc || sym->attr.in_common)
12852     return 1;
12853
12854   /* Check if the symbol's ns is inside the pure procedure.  */
12855   for (ns = gfc_current_ns; ns; ns = ns->parent)
12856     {
12857       if (ns == sym->ns)
12858         break;
12859       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
12860         return 1;
12861     }
12862
12863   proc = sym->ns->proc_name;
12864   if (sym->attr.dummy && gfc_pure (proc)
12865         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
12866                 ||
12867              proc->attr.function))
12868     return 1;
12869
12870   /* TODO: Sort out what can be storage associated, if anything, and include
12871      it here.  In principle equivalences should be scanned but it does not
12872      seem to be possible to storage associate an impure variable this way.  */
12873   return 0;
12874 }
12875
12876
12877 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
12878    current namespace is inside a pure procedure.  */
12879
12880 int
12881 gfc_pure (gfc_symbol *sym)
12882 {
12883   symbol_attribute attr;
12884   gfc_namespace *ns;
12885
12886   if (sym == NULL)
12887     {
12888       /* Check if the current namespace or one of its parents
12889         belongs to a pure procedure.  */
12890       for (ns = gfc_current_ns; ns; ns = ns->parent)
12891         {
12892           sym = ns->proc_name;
12893           if (sym == NULL)
12894             return 0;
12895           attr = sym->attr;
12896           if (attr.flavor == FL_PROCEDURE && attr.pure)
12897             return 1;
12898         }
12899       return 0;
12900     }
12901
12902   attr = sym->attr;
12903
12904   return attr.flavor == FL_PROCEDURE && attr.pure;
12905 }
12906
12907
12908 /* Test whether a symbol is implicitly pure or not.  For a NULL pointer,
12909    checks if the current namespace is implicitly pure.  Note that this
12910    function returns false for a PURE procedure.  */
12911
12912 int
12913 gfc_implicit_pure (gfc_symbol *sym)
12914 {
12915   symbol_attribute attr;
12916
12917   if (sym == NULL)
12918     {
12919       /* Check if the current namespace is implicit_pure.  */
12920       sym = gfc_current_ns->proc_name;
12921       if (sym == NULL)
12922         return 0;
12923       attr = sym->attr;
12924       if (attr.flavor == FL_PROCEDURE
12925             && attr.implicit_pure && !attr.pure)
12926         return 1;
12927       return 0;
12928     }
12929
12930   attr = sym->attr;
12931
12932   return attr.flavor == FL_PROCEDURE && attr.implicit_pure && !attr.pure;
12933 }
12934
12935
12936 /* Test whether the current procedure is elemental or not.  */
12937
12938 int
12939 gfc_elemental (gfc_symbol *sym)
12940 {
12941   symbol_attribute attr;
12942
12943   if (sym == NULL)
12944     sym = gfc_current_ns->proc_name;
12945   if (sym == NULL)
12946     return 0;
12947   attr = sym->attr;
12948
12949   return attr.flavor == FL_PROCEDURE && attr.elemental;
12950 }
12951
12952
12953 /* Warn about unused labels.  */
12954
12955 static void
12956 warn_unused_fortran_label (gfc_st_label *label)
12957 {
12958   if (label == NULL)
12959     return;
12960
12961   warn_unused_fortran_label (label->left);
12962
12963   if (label->defined == ST_LABEL_UNKNOWN)
12964     return;
12965
12966   switch (label->referenced)
12967     {
12968     case ST_LABEL_UNKNOWN:
12969       gfc_warning ("Label %d at %L defined but not used", label->value,
12970                    &label->where);
12971       break;
12972
12973     case ST_LABEL_BAD_TARGET:
12974       gfc_warning ("Label %d at %L defined but cannot be used",
12975                    label->value, &label->where);
12976       break;
12977
12978     default:
12979       break;
12980     }
12981
12982   warn_unused_fortran_label (label->right);
12983 }
12984
12985
12986 /* Returns the sequence type of a symbol or sequence.  */
12987
12988 static seq_type
12989 sequence_type (gfc_typespec ts)
12990 {
12991   seq_type result;
12992   gfc_component *c;
12993
12994   switch (ts.type)
12995   {
12996     case BT_DERIVED:
12997
12998       if (ts.u.derived->components == NULL)
12999         return SEQ_NONDEFAULT;
13000
13001       result = sequence_type (ts.u.derived->components->ts);
13002       for (c = ts.u.derived->components->next; c; c = c->next)
13003         if (sequence_type (c->ts) != result)
13004           return SEQ_MIXED;
13005
13006       return result;
13007
13008     case BT_CHARACTER:
13009       if (ts.kind != gfc_default_character_kind)
13010           return SEQ_NONDEFAULT;
13011
13012       return SEQ_CHARACTER;
13013
13014     case BT_INTEGER:
13015       if (ts.kind != gfc_default_integer_kind)
13016           return SEQ_NONDEFAULT;
13017
13018       return SEQ_NUMERIC;
13019
13020     case BT_REAL:
13021       if (!(ts.kind == gfc_default_real_kind
13022             || ts.kind == gfc_default_double_kind))
13023           return SEQ_NONDEFAULT;
13024
13025       return SEQ_NUMERIC;
13026
13027     case BT_COMPLEX:
13028       if (ts.kind != gfc_default_complex_kind)
13029           return SEQ_NONDEFAULT;
13030
13031       return SEQ_NUMERIC;
13032
13033     case BT_LOGICAL:
13034       if (ts.kind != gfc_default_logical_kind)
13035           return SEQ_NONDEFAULT;
13036
13037       return SEQ_NUMERIC;
13038
13039     default:
13040       return SEQ_NONDEFAULT;
13041   }
13042 }
13043
13044
13045 /* Resolve derived type EQUIVALENCE object.  */
13046
13047 static gfc_try
13048 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
13049 {
13050   gfc_component *c = derived->components;
13051
13052   if (!derived)
13053     return SUCCESS;
13054
13055   /* Shall not be an object of nonsequence derived type.  */
13056   if (!derived->attr.sequence)
13057     {
13058       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
13059                  "attribute to be an EQUIVALENCE object", sym->name,
13060                  &e->where);
13061       return FAILURE;
13062     }
13063
13064   /* Shall not have allocatable components.  */
13065   if (derived->attr.alloc_comp)
13066     {
13067       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
13068                  "components to be an EQUIVALENCE object",sym->name,
13069                  &e->where);
13070       return FAILURE;
13071     }
13072
13073   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
13074     {
13075       gfc_error ("Derived type variable '%s' at %L with default "
13076                  "initialization cannot be in EQUIVALENCE with a variable "
13077                  "in COMMON", sym->name, &e->where);
13078       return FAILURE;
13079     }
13080
13081   for (; c ; c = c->next)
13082     {
13083       if (c->ts.type == BT_DERIVED
13084           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
13085         return FAILURE;
13086
13087       /* Shall not be an object of sequence derived type containing a pointer
13088          in the structure.  */
13089       if (c->attr.pointer)
13090         {
13091           gfc_error ("Derived type variable '%s' at %L with pointer "
13092                      "component(s) cannot be an EQUIVALENCE object",
13093                      sym->name, &e->where);
13094           return FAILURE;
13095         }
13096     }
13097   return SUCCESS;
13098 }
13099
13100
13101 /* Resolve equivalence object. 
13102    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
13103    an allocatable array, an object of nonsequence derived type, an object of
13104    sequence derived type containing a pointer at any level of component
13105    selection, an automatic object, a function name, an entry name, a result
13106    name, a named constant, a structure component, or a subobject of any of
13107    the preceding objects.  A substring shall not have length zero.  A
13108    derived type shall not have components with default initialization nor
13109    shall two objects of an equivalence group be initialized.
13110    Either all or none of the objects shall have an protected attribute.
13111    The simple constraints are done in symbol.c(check_conflict) and the rest
13112    are implemented here.  */
13113
13114 static void
13115 resolve_equivalence (gfc_equiv *eq)
13116 {
13117   gfc_symbol *sym;
13118   gfc_symbol *first_sym;
13119   gfc_expr *e;
13120   gfc_ref *r;
13121   locus *last_where = NULL;
13122   seq_type eq_type, last_eq_type;
13123   gfc_typespec *last_ts;
13124   int object, cnt_protected;
13125   const char *msg;
13126
13127   last_ts = &eq->expr->symtree->n.sym->ts;
13128
13129   first_sym = eq->expr->symtree->n.sym;
13130
13131   cnt_protected = 0;
13132
13133   for (object = 1; eq; eq = eq->eq, object++)
13134     {
13135       e = eq->expr;
13136
13137       e->ts = e->symtree->n.sym->ts;
13138       /* match_varspec might not know yet if it is seeing
13139          array reference or substring reference, as it doesn't
13140          know the types.  */
13141       if (e->ref && e->ref->type == REF_ARRAY)
13142         {
13143           gfc_ref *ref = e->ref;
13144           sym = e->symtree->n.sym;
13145
13146           if (sym->attr.dimension)
13147             {
13148               ref->u.ar.as = sym->as;
13149               ref = ref->next;
13150             }
13151
13152           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
13153           if (e->ts.type == BT_CHARACTER
13154               && ref
13155               && ref->type == REF_ARRAY
13156               && ref->u.ar.dimen == 1
13157               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
13158               && ref->u.ar.stride[0] == NULL)
13159             {
13160               gfc_expr *start = ref->u.ar.start[0];
13161               gfc_expr *end = ref->u.ar.end[0];
13162               void *mem = NULL;
13163
13164               /* Optimize away the (:) reference.  */
13165               if (start == NULL && end == NULL)
13166                 {
13167                   if (e->ref == ref)
13168                     e->ref = ref->next;
13169                   else
13170                     e->ref->next = ref->next;
13171                   mem = ref;
13172                 }
13173               else
13174                 {
13175                   ref->type = REF_SUBSTRING;
13176                   if (start == NULL)
13177                     start = gfc_get_int_expr (gfc_default_integer_kind,
13178                                               NULL, 1);
13179                   ref->u.ss.start = start;
13180                   if (end == NULL && e->ts.u.cl)
13181                     end = gfc_copy_expr (e->ts.u.cl->length);
13182                   ref->u.ss.end = end;
13183                   ref->u.ss.length = e->ts.u.cl;
13184                   e->ts.u.cl = NULL;
13185                 }
13186               ref = ref->next;
13187               gfc_free (mem);
13188             }
13189
13190           /* Any further ref is an error.  */
13191           if (ref)
13192             {
13193               gcc_assert (ref->type == REF_ARRAY);
13194               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
13195                          &ref->u.ar.where);
13196               continue;
13197             }
13198         }
13199
13200       if (gfc_resolve_expr (e) == FAILURE)
13201         continue;
13202
13203       sym = e->symtree->n.sym;
13204
13205       if (sym->attr.is_protected)
13206         cnt_protected++;
13207       if (cnt_protected > 0 && cnt_protected != object)
13208         {
13209               gfc_error ("Either all or none of the objects in the "
13210                          "EQUIVALENCE set at %L shall have the "
13211                          "PROTECTED attribute",
13212                          &e->where);
13213               break;
13214         }
13215
13216       /* Shall not equivalence common block variables in a PURE procedure.  */
13217       if (sym->ns->proc_name
13218           && sym->ns->proc_name->attr.pure
13219           && sym->attr.in_common)
13220         {
13221           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
13222                      "object in the pure procedure '%s'",
13223                      sym->name, &e->where, sym->ns->proc_name->name);
13224           break;
13225         }
13226
13227       /* Shall not be a named constant.  */
13228       if (e->expr_type == EXPR_CONSTANT)
13229         {
13230           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
13231                      "object", sym->name, &e->where);
13232           continue;
13233         }
13234
13235       if (e->ts.type == BT_DERIVED
13236           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
13237         continue;
13238
13239       /* Check that the types correspond correctly:
13240          Note 5.28:
13241          A numeric sequence structure may be equivalenced to another sequence
13242          structure, an object of default integer type, default real type, double
13243          precision real type, default logical type such that components of the
13244          structure ultimately only become associated to objects of the same
13245          kind. A character sequence structure may be equivalenced to an object
13246          of default character kind or another character sequence structure.
13247          Other objects may be equivalenced only to objects of the same type and
13248          kind parameters.  */
13249
13250       /* Identical types are unconditionally OK.  */
13251       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
13252         goto identical_types;
13253
13254       last_eq_type = sequence_type (*last_ts);
13255       eq_type = sequence_type (sym->ts);
13256
13257       /* Since the pair of objects is not of the same type, mixed or
13258          non-default sequences can be rejected.  */
13259
13260       msg = "Sequence %s with mixed components in EQUIVALENCE "
13261             "statement at %L with different type objects";
13262       if ((object ==2
13263            && last_eq_type == SEQ_MIXED
13264            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
13265               == FAILURE)
13266           || (eq_type == SEQ_MIXED
13267               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13268                                  &e->where) == FAILURE))
13269         continue;
13270
13271       msg = "Non-default type object or sequence %s in EQUIVALENCE "
13272             "statement at %L with objects of different type";
13273       if ((object ==2
13274            && last_eq_type == SEQ_NONDEFAULT
13275            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
13276                               last_where) == FAILURE)
13277           || (eq_type == SEQ_NONDEFAULT
13278               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13279                                  &e->where) == FAILURE))
13280         continue;
13281
13282       msg ="Non-CHARACTER object '%s' in default CHARACTER "
13283            "EQUIVALENCE statement at %L";
13284       if (last_eq_type == SEQ_CHARACTER
13285           && eq_type != SEQ_CHARACTER
13286           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13287                              &e->where) == FAILURE)
13288                 continue;
13289
13290       msg ="Non-NUMERIC object '%s' in default NUMERIC "
13291            "EQUIVALENCE statement at %L";
13292       if (last_eq_type == SEQ_NUMERIC
13293           && eq_type != SEQ_NUMERIC
13294           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13295                              &e->where) == FAILURE)
13296                 continue;
13297
13298   identical_types:
13299       last_ts =&sym->ts;
13300       last_where = &e->where;
13301
13302       if (!e->ref)
13303         continue;
13304
13305       /* Shall not be an automatic array.  */
13306       if (e->ref->type == REF_ARRAY
13307           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
13308         {
13309           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
13310                      "an EQUIVALENCE object", sym->name, &e->where);
13311           continue;
13312         }
13313
13314       r = e->ref;
13315       while (r)
13316         {
13317           /* Shall not be a structure component.  */
13318           if (r->type == REF_COMPONENT)
13319             {
13320               gfc_error ("Structure component '%s' at %L cannot be an "
13321                          "EQUIVALENCE object",
13322                          r->u.c.component->name, &e->where);
13323               break;
13324             }
13325
13326           /* A substring shall not have length zero.  */
13327           if (r->type == REF_SUBSTRING)
13328             {
13329               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
13330                 {
13331                   gfc_error ("Substring at %L has length zero",
13332                              &r->u.ss.start->where);
13333                   break;
13334                 }
13335             }
13336           r = r->next;
13337         }
13338     }
13339 }
13340
13341
13342 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
13343
13344 static void
13345 resolve_fntype (gfc_namespace *ns)
13346 {
13347   gfc_entry_list *el;
13348   gfc_symbol *sym;
13349
13350   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
13351     return;
13352
13353   /* If there are any entries, ns->proc_name is the entry master
13354      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
13355   if (ns->entries)
13356     sym = ns->entries->sym;
13357   else
13358     sym = ns->proc_name;
13359   if (sym->result == sym
13360       && sym->ts.type == BT_UNKNOWN
13361       && gfc_set_default_type (sym, 0, NULL) == FAILURE
13362       && !sym->attr.untyped)
13363     {
13364       gfc_error ("Function '%s' at %L has no IMPLICIT type",
13365                  sym->name, &sym->declared_at);
13366       sym->attr.untyped = 1;
13367     }
13368
13369   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
13370       && !sym->attr.contained
13371       && !gfc_check_symbol_access (sym->ts.u.derived)
13372       && gfc_check_symbol_access (sym))
13373     {
13374       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
13375                       "%L of PRIVATE type '%s'", sym->name,
13376                       &sym->declared_at, sym->ts.u.derived->name);
13377     }
13378
13379     if (ns->entries)
13380     for (el = ns->entries->next; el; el = el->next)
13381       {
13382         if (el->sym->result == el->sym
13383             && el->sym->ts.type == BT_UNKNOWN
13384             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
13385             && !el->sym->attr.untyped)
13386           {
13387             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
13388                        el->sym->name, &el->sym->declared_at);
13389             el->sym->attr.untyped = 1;
13390           }
13391       }
13392 }
13393
13394
13395 /* 12.3.2.1.1 Defined operators.  */
13396
13397 static gfc_try
13398 check_uop_procedure (gfc_symbol *sym, locus where)
13399 {
13400   gfc_formal_arglist *formal;
13401
13402   if (!sym->attr.function)
13403     {
13404       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
13405                  sym->name, &where);
13406       return FAILURE;
13407     }
13408
13409   if (sym->ts.type == BT_CHARACTER
13410       && !(sym->ts.u.cl && sym->ts.u.cl->length)
13411       && !(sym->result && sym->result->ts.u.cl
13412            && sym->result->ts.u.cl->length))
13413     {
13414       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
13415                  "character length", sym->name, &where);
13416       return FAILURE;
13417     }
13418
13419   formal = sym->formal;
13420   if (!formal || !formal->sym)
13421     {
13422       gfc_error ("User operator procedure '%s' at %L must have at least "
13423                  "one argument", sym->name, &where);
13424       return FAILURE;
13425     }
13426
13427   if (formal->sym->attr.intent != INTENT_IN)
13428     {
13429       gfc_error ("First argument of operator interface at %L must be "
13430                  "INTENT(IN)", &where);
13431       return FAILURE;
13432     }
13433
13434   if (formal->sym->attr.optional)
13435     {
13436       gfc_error ("First argument of operator interface at %L cannot be "
13437                  "optional", &where);
13438       return FAILURE;
13439     }
13440
13441   formal = formal->next;
13442   if (!formal || !formal->sym)
13443     return SUCCESS;
13444
13445   if (formal->sym->attr.intent != INTENT_IN)
13446     {
13447       gfc_error ("Second argument of operator interface at %L must be "
13448                  "INTENT(IN)", &where);
13449       return FAILURE;
13450     }
13451
13452   if (formal->sym->attr.optional)
13453     {
13454       gfc_error ("Second argument of operator interface at %L cannot be "
13455                  "optional", &where);
13456       return FAILURE;
13457     }
13458
13459   if (formal->next)
13460     {
13461       gfc_error ("Operator interface at %L must have, at most, two "
13462                  "arguments", &where);
13463       return FAILURE;
13464     }
13465
13466   return SUCCESS;
13467 }
13468
13469 static void
13470 gfc_resolve_uops (gfc_symtree *symtree)
13471 {
13472   gfc_interface *itr;
13473
13474   if (symtree == NULL)
13475     return;
13476
13477   gfc_resolve_uops (symtree->left);
13478   gfc_resolve_uops (symtree->right);
13479
13480   for (itr = symtree->n.uop->op; itr; itr = itr->next)
13481     check_uop_procedure (itr->sym, itr->sym->declared_at);
13482 }
13483
13484
13485 /* Examine all of the expressions associated with a program unit,
13486    assign types to all intermediate expressions, make sure that all
13487    assignments are to compatible types and figure out which names
13488    refer to which functions or subroutines.  It doesn't check code
13489    block, which is handled by resolve_code.  */
13490
13491 static void
13492 resolve_types (gfc_namespace *ns)
13493 {
13494   gfc_namespace *n;
13495   gfc_charlen *cl;
13496   gfc_data *d;
13497   gfc_equiv *eq;
13498   gfc_namespace* old_ns = gfc_current_ns;
13499
13500   /* Check that all IMPLICIT types are ok.  */
13501   if (!ns->seen_implicit_none)
13502     {
13503       unsigned letter;
13504       for (letter = 0; letter != GFC_LETTERS; ++letter)
13505         if (ns->set_flag[letter]
13506             && resolve_typespec_used (&ns->default_type[letter],
13507                                       &ns->implicit_loc[letter],
13508                                       NULL) == FAILURE)
13509           return;
13510     }
13511
13512   gfc_current_ns = ns;
13513
13514   resolve_entries (ns);
13515
13516   resolve_common_vars (ns->blank_common.head, false);
13517   resolve_common_blocks (ns->common_root);
13518
13519   resolve_contained_functions (ns);
13520
13521   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
13522
13523   for (cl = ns->cl_list; cl; cl = cl->next)
13524     resolve_charlen (cl);
13525
13526   gfc_traverse_ns (ns, resolve_symbol);
13527
13528   resolve_fntype (ns);
13529
13530   for (n = ns->contained; n; n = n->sibling)
13531     {
13532       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
13533         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
13534                    "also be PURE", n->proc_name->name,
13535                    &n->proc_name->declared_at);
13536
13537       resolve_types (n);
13538     }
13539
13540   forall_flag = 0;
13541   gfc_check_interfaces (ns);
13542
13543   gfc_traverse_ns (ns, resolve_values);
13544
13545   if (ns->save_all)
13546     gfc_save_all (ns);
13547
13548   iter_stack = NULL;
13549   for (d = ns->data; d; d = d->next)
13550     resolve_data (d);
13551
13552   iter_stack = NULL;
13553   gfc_traverse_ns (ns, gfc_formalize_init_value);
13554
13555   gfc_traverse_ns (ns, gfc_verify_binding_labels);
13556
13557   if (ns->common_root != NULL)
13558     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
13559
13560   for (eq = ns->equiv; eq; eq = eq->next)
13561     resolve_equivalence (eq);
13562
13563   /* Warn about unused labels.  */
13564   if (warn_unused_label)
13565     warn_unused_fortran_label (ns->st_labels);
13566
13567   gfc_resolve_uops (ns->uop_root);
13568
13569   gfc_current_ns = old_ns;
13570 }
13571
13572
13573 /* Call resolve_code recursively.  */
13574
13575 static void
13576 resolve_codes (gfc_namespace *ns)
13577 {
13578   gfc_namespace *n;
13579   bitmap_obstack old_obstack;
13580
13581   if (ns->resolved == 1)
13582     return;
13583
13584   for (n = ns->contained; n; n = n->sibling)
13585     resolve_codes (n);
13586
13587   gfc_current_ns = ns;
13588
13589   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
13590   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
13591     cs_base = NULL;
13592
13593   /* Set to an out of range value.  */
13594   current_entry_id = -1;
13595
13596   old_obstack = labels_obstack;
13597   bitmap_obstack_initialize (&labels_obstack);
13598
13599   resolve_code (ns->code, ns);
13600
13601   bitmap_obstack_release (&labels_obstack);
13602   labels_obstack = old_obstack;
13603 }
13604
13605
13606 /* This function is called after a complete program unit has been compiled.
13607    Its purpose is to examine all of the expressions associated with a program
13608    unit, assign types to all intermediate expressions, make sure that all
13609    assignments are to compatible types and figure out which names refer to
13610    which functions or subroutines.  */
13611
13612 void
13613 gfc_resolve (gfc_namespace *ns)
13614 {
13615   gfc_namespace *old_ns;
13616   code_stack *old_cs_base;
13617
13618   if (ns->resolved)
13619     return;
13620
13621   ns->resolved = -1;
13622   old_ns = gfc_current_ns;
13623   old_cs_base = cs_base;
13624
13625   resolve_types (ns);
13626   resolve_codes (ns);
13627
13628   gfc_current_ns = old_ns;
13629   cs_base = old_cs_base;
13630   ns->resolved = 1;
13631
13632   gfc_run_passes (ns);
13633 }