OSDN Git Service

2011-04-29 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           && sym->attr.flavor != FL_PROCEDURE)
320         {
321           sym->as->type = AS_ASSUMED_SHAPE;
322           for (i = 0; i < sym->as->rank; i++)
323             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
324                                                   NULL, 1);
325         }
326
327       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
328           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
329           || sym->attr.optional)
330         {
331           proc->attr.always_explicit = 1;
332           if (proc->result)
333             proc->result->attr.always_explicit = 1;
334         }
335
336       /* If the flavor is unknown at this point, it has to be a variable.
337          A procedure specification would have already set the type.  */
338
339       if (sym->attr.flavor == FL_UNKNOWN)
340         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
341
342       if (gfc_pure (proc) && !sym->attr.pointer
343           && sym->attr.flavor != FL_PROCEDURE)
344         {
345           if (proc->attr.function && sym->attr.intent != INTENT_IN)
346             {
347               if (sym->attr.value)
348                 gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s' "
349                                 "of pure function '%s' at %L with VALUE "
350                                 "attribute but without INTENT(IN)", sym->name,
351                                 proc->name, &sym->declared_at);
352               else
353                 gfc_error ("Argument '%s' of pure function '%s' at %L must be "
354                            "INTENT(IN) or VALUE", sym->name, proc->name,
355                            &sym->declared_at);
356             }
357
358           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
359             {
360               if (sym->attr.value)
361                 gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s' "
362                                 "of pure subroutine '%s' at %L with VALUE "
363                                 "attribute but without INTENT", sym->name,
364                                 proc->name, &sym->declared_at);
365               else
366                 gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
367                        "have its INTENT specified or have the VALUE "
368                        "attribute", sym->name, proc->name, &sym->declared_at);
369             }
370         }
371
372       if (proc->attr.implicit_pure && !sym->attr.pointer
373           && sym->attr.flavor != FL_PROCEDURE)
374         {
375           if (proc->attr.function && sym->attr.intent != INTENT_IN)
376             proc->attr.implicit_pure = 0;
377
378           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
379             proc->attr.implicit_pure = 0;
380         }
381
382       if (gfc_elemental (proc))
383         {
384           /* F2008, C1289.  */
385           if (sym->attr.codimension)
386             {
387               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
388                          "procedure", sym->name, &sym->declared_at);
389               continue;
390             }
391
392           if (sym->as != NULL)
393             {
394               gfc_error ("Argument '%s' of elemental procedure at %L must "
395                          "be scalar", sym->name, &sym->declared_at);
396               continue;
397             }
398
399           if (sym->attr.allocatable)
400             {
401               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
402                          "have the ALLOCATABLE attribute", sym->name,
403                          &sym->declared_at);
404               continue;
405             }
406
407           if (sym->attr.pointer)
408             {
409               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
410                          "have the POINTER attribute", sym->name,
411                          &sym->declared_at);
412               continue;
413             }
414
415           if (sym->attr.flavor == FL_PROCEDURE)
416             {
417               gfc_error ("Dummy procedure '%s' not allowed in elemental "
418                          "procedure '%s' at %L", sym->name, proc->name,
419                          &sym->declared_at);
420               continue;
421             }
422
423           if (sym->attr.intent == INTENT_UNKNOWN)
424             {
425               gfc_error ("Argument '%s' of elemental procedure '%s' at %L must "
426                          "have its INTENT specified", sym->name, proc->name,
427                          &sym->declared_at);
428               continue;
429             }
430         }
431
432       /* Each dummy shall be specified to be scalar.  */
433       if (proc->attr.proc == PROC_ST_FUNCTION)
434         {
435           if (sym->as != NULL)
436             {
437               gfc_error ("Argument '%s' of statement function at %L must "
438                          "be scalar", sym->name, &sym->declared_at);
439               continue;
440             }
441
442           if (sym->ts.type == BT_CHARACTER)
443             {
444               gfc_charlen *cl = sym->ts.u.cl;
445               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
446                 {
447                   gfc_error ("Character-valued argument '%s' of statement "
448                              "function at %L must have constant length",
449                              sym->name, &sym->declared_at);
450                   continue;
451                 }
452             }
453         }
454     }
455   formal_arg_flag = 0;
456 }
457
458
459 /* Work function called when searching for symbols that have argument lists
460    associated with them.  */
461
462 static void
463 find_arglists (gfc_symbol *sym)
464 {
465   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
466     return;
467
468   resolve_formal_arglist (sym);
469 }
470
471
472 /* Given a namespace, resolve all formal argument lists within the namespace.
473  */
474
475 static void
476 resolve_formal_arglists (gfc_namespace *ns)
477 {
478   if (ns == NULL)
479     return;
480
481   gfc_traverse_ns (ns, find_arglists);
482 }
483
484
485 static void
486 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
487 {
488   gfc_try t;
489
490   /* If this namespace is not a function or an entry master function,
491      ignore it.  */
492   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
493       || sym->attr.entry_master)
494     return;
495
496   /* Try to find out of what the return type is.  */
497   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
498     {
499       t = gfc_set_default_type (sym->result, 0, ns);
500
501       if (t == FAILURE && !sym->result->attr.untyped)
502         {
503           if (sym->result == sym)
504             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
505                        sym->name, &sym->declared_at);
506           else if (!sym->result->attr.proc_pointer)
507             gfc_error ("Result '%s' of contained function '%s' at %L has "
508                        "no IMPLICIT type", sym->result->name, sym->name,
509                        &sym->result->declared_at);
510           sym->result->attr.untyped = 1;
511         }
512     }
513
514   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
515      type, lists the only ways a character length value of * can be used:
516      dummy arguments of procedures, named constants, and function results
517      in external functions.  Internal function results and results of module
518      procedures are not on this list, ergo, not permitted.  */
519
520   if (sym->result->ts.type == BT_CHARACTER)
521     {
522       gfc_charlen *cl = sym->result->ts.u.cl;
523       if ((!cl || !cl->length) && !sym->result->ts.deferred)
524         {
525           /* See if this is a module-procedure and adapt error message
526              accordingly.  */
527           bool module_proc;
528           gcc_assert (ns->parent && ns->parent->proc_name);
529           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
530
531           gfc_error ("Character-valued %s '%s' at %L must not be"
532                      " assumed length",
533                      module_proc ? _("module procedure")
534                                  : _("internal function"),
535                      sym->name, &sym->declared_at);
536         }
537     }
538 }
539
540
541 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
542    introduce duplicates.  */
543
544 static void
545 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
546 {
547   gfc_formal_arglist *f, *new_arglist;
548   gfc_symbol *new_sym;
549
550   for (; new_args != NULL; new_args = new_args->next)
551     {
552       new_sym = new_args->sym;
553       /* See if this arg is already in the formal argument list.  */
554       for (f = proc->formal; f; f = f->next)
555         {
556           if (new_sym == f->sym)
557             break;
558         }
559
560       if (f)
561         continue;
562
563       /* Add a new argument.  Argument order is not important.  */
564       new_arglist = gfc_get_formal_arglist ();
565       new_arglist->sym = new_sym;
566       new_arglist->next = proc->formal;
567       proc->formal  = new_arglist;
568     }
569 }
570
571
572 /* Flag the arguments that are not present in all entries.  */
573
574 static void
575 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
576 {
577   gfc_formal_arglist *f, *head;
578   head = new_args;
579
580   for (f = proc->formal; f; f = f->next)
581     {
582       if (f->sym == NULL)
583         continue;
584
585       for (new_args = head; new_args; new_args = new_args->next)
586         {
587           if (new_args->sym == f->sym)
588             break;
589         }
590
591       if (new_args)
592         continue;
593
594       f->sym->attr.not_always_present = 1;
595     }
596 }
597
598
599 /* Resolve alternate entry points.  If a symbol has multiple entry points we
600    create a new master symbol for the main routine, and turn the existing
601    symbol into an entry point.  */
602
603 static void
604 resolve_entries (gfc_namespace *ns)
605 {
606   gfc_namespace *old_ns;
607   gfc_code *c;
608   gfc_symbol *proc;
609   gfc_entry_list *el;
610   char name[GFC_MAX_SYMBOL_LEN + 1];
611   static int master_count = 0;
612
613   if (ns->proc_name == NULL)
614     return;
615
616   /* No need to do anything if this procedure doesn't have alternate entry
617      points.  */
618   if (!ns->entries)
619     return;
620
621   /* We may already have resolved alternate entry points.  */
622   if (ns->proc_name->attr.entry_master)
623     return;
624
625   /* If this isn't a procedure something has gone horribly wrong.  */
626   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
627
628   /* Remember the current namespace.  */
629   old_ns = gfc_current_ns;
630
631   gfc_current_ns = ns;
632
633   /* Add the main entry point to the list of entry points.  */
634   el = gfc_get_entry_list ();
635   el->sym = ns->proc_name;
636   el->id = 0;
637   el->next = ns->entries;
638   ns->entries = el;
639   ns->proc_name->attr.entry = 1;
640
641   /* If it is a module function, it needs to be in the right namespace
642      so that gfc_get_fake_result_decl can gather up the results. The
643      need for this arose in get_proc_name, where these beasts were
644      left in their own namespace, to keep prior references linked to
645      the entry declaration.*/
646   if (ns->proc_name->attr.function
647       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
648     el->sym->ns = ns;
649
650   /* Do the same for entries where the master is not a module
651      procedure.  These are retained in the module namespace because
652      of the module procedure declaration.  */
653   for (el = el->next; el; el = el->next)
654     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
655           && el->sym->attr.mod_proc)
656       el->sym->ns = ns;
657   el = ns->entries;
658
659   /* Add an entry statement for it.  */
660   c = gfc_get_code ();
661   c->op = EXEC_ENTRY;
662   c->ext.entry = el;
663   c->next = ns->code;
664   ns->code = c;
665
666   /* Create a new symbol for the master function.  */
667   /* Give the internal function a unique name (within this file).
668      Also include the function name so the user has some hope of figuring
669      out what is going on.  */
670   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
671             master_count++, ns->proc_name->name);
672   gfc_get_ha_symbol (name, &proc);
673   gcc_assert (proc != NULL);
674
675   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
676   if (ns->proc_name->attr.subroutine)
677     gfc_add_subroutine (&proc->attr, proc->name, NULL);
678   else
679     {
680       gfc_symbol *sym;
681       gfc_typespec *ts, *fts;
682       gfc_array_spec *as, *fas;
683       gfc_add_function (&proc->attr, proc->name, NULL);
684       proc->result = proc;
685       fas = ns->entries->sym->as;
686       fas = fas ? fas : ns->entries->sym->result->as;
687       fts = &ns->entries->sym->result->ts;
688       if (fts->type == BT_UNKNOWN)
689         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
690       for (el = ns->entries->next; el; el = el->next)
691         {
692           ts = &el->sym->result->ts;
693           as = el->sym->as;
694           as = as ? as : el->sym->result->as;
695           if (ts->type == BT_UNKNOWN)
696             ts = gfc_get_default_type (el->sym->result->name, NULL);
697
698           if (! gfc_compare_types (ts, fts)
699               || (el->sym->result->attr.dimension
700                   != ns->entries->sym->result->attr.dimension)
701               || (el->sym->result->attr.pointer
702                   != ns->entries->sym->result->attr.pointer))
703             break;
704           else if (as && fas && ns->entries->sym->result != el->sym->result
705                       && gfc_compare_array_spec (as, fas) == 0)
706             gfc_error ("Function %s at %L has entries with mismatched "
707                        "array specifications", ns->entries->sym->name,
708                        &ns->entries->sym->declared_at);
709           /* The characteristics need to match and thus both need to have
710              the same string length, i.e. both len=*, or both len=4.
711              Having both len=<variable> is also possible, but difficult to
712              check at compile time.  */
713           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
714                    && (((ts->u.cl->length && !fts->u.cl->length)
715                         ||(!ts->u.cl->length && fts->u.cl->length))
716                        || (ts->u.cl->length
717                            && ts->u.cl->length->expr_type
718                               != fts->u.cl->length->expr_type)
719                        || (ts->u.cl->length
720                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
721                            && mpz_cmp (ts->u.cl->length->value.integer,
722                                        fts->u.cl->length->value.integer) != 0)))
723             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
724                             "entries returning variables of different "
725                             "string lengths", ns->entries->sym->name,
726                             &ns->entries->sym->declared_at);
727         }
728
729       if (el == NULL)
730         {
731           sym = ns->entries->sym->result;
732           /* All result types the same.  */
733           proc->ts = *fts;
734           if (sym->attr.dimension)
735             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
736           if (sym->attr.pointer)
737             gfc_add_pointer (&proc->attr, NULL);
738         }
739       else
740         {
741           /* Otherwise the result will be passed through a union by
742              reference.  */
743           proc->attr.mixed_entry_master = 1;
744           for (el = ns->entries; el; el = el->next)
745             {
746               sym = el->sym->result;
747               if (sym->attr.dimension)
748                 {
749                   if (el == ns->entries)
750                     gfc_error ("FUNCTION result %s can't be an array in "
751                                "FUNCTION %s at %L", sym->name,
752                                ns->entries->sym->name, &sym->declared_at);
753                   else
754                     gfc_error ("ENTRY result %s can't be an array in "
755                                "FUNCTION %s at %L", sym->name,
756                                ns->entries->sym->name, &sym->declared_at);
757                 }
758               else if (sym->attr.pointer)
759                 {
760                   if (el == ns->entries)
761                     gfc_error ("FUNCTION result %s can't be a POINTER in "
762                                "FUNCTION %s at %L", sym->name,
763                                ns->entries->sym->name, &sym->declared_at);
764                   else
765                     gfc_error ("ENTRY result %s can't be a POINTER in "
766                                "FUNCTION %s at %L", sym->name,
767                                ns->entries->sym->name, &sym->declared_at);
768                 }
769               else
770                 {
771                   ts = &sym->ts;
772                   if (ts->type == BT_UNKNOWN)
773                     ts = gfc_get_default_type (sym->name, NULL);
774                   switch (ts->type)
775                     {
776                     case BT_INTEGER:
777                       if (ts->kind == gfc_default_integer_kind)
778                         sym = NULL;
779                       break;
780                     case BT_REAL:
781                       if (ts->kind == gfc_default_real_kind
782                           || ts->kind == gfc_default_double_kind)
783                         sym = NULL;
784                       break;
785                     case BT_COMPLEX:
786                       if (ts->kind == gfc_default_complex_kind)
787                         sym = NULL;
788                       break;
789                     case BT_LOGICAL:
790                       if (ts->kind == gfc_default_logical_kind)
791                         sym = NULL;
792                       break;
793                     case BT_UNKNOWN:
794                       /* We will issue error elsewhere.  */
795                       sym = NULL;
796                       break;
797                     default:
798                       break;
799                     }
800                   if (sym)
801                     {
802                       if (el == ns->entries)
803                         gfc_error ("FUNCTION result %s can't be of type %s "
804                                    "in FUNCTION %s at %L", sym->name,
805                                    gfc_typename (ts), ns->entries->sym->name,
806                                    &sym->declared_at);
807                       else
808                         gfc_error ("ENTRY result %s can't be of type %s "
809                                    "in FUNCTION %s at %L", sym->name,
810                                    gfc_typename (ts), ns->entries->sym->name,
811                                    &sym->declared_at);
812                     }
813                 }
814             }
815         }
816     }
817   proc->attr.access = ACCESS_PRIVATE;
818   proc->attr.entry_master = 1;
819
820   /* Merge all the entry point arguments.  */
821   for (el = ns->entries; el; el = el->next)
822     merge_argument_lists (proc, el->sym->formal);
823
824   /* Check the master formal arguments for any that are not
825      present in all entry points.  */
826   for (el = ns->entries; el; el = el->next)
827     check_argument_lists (proc, el->sym->formal);
828
829   /* Use the master function for the function body.  */
830   ns->proc_name = proc;
831
832   /* Finalize the new symbols.  */
833   gfc_commit_symbols ();
834
835   /* Restore the original namespace.  */
836   gfc_current_ns = old_ns;
837 }
838
839
840 /* Resolve common variables.  */
841 static void
842 resolve_common_vars (gfc_symbol *sym, bool named_common)
843 {
844   gfc_symbol *csym = sym;
845
846   for (; csym; csym = csym->common_next)
847     {
848       if (csym->value || csym->attr.data)
849         {
850           if (!csym->ns->is_block_data)
851             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
852                             "but only in BLOCK DATA initialization is "
853                             "allowed", csym->name, &csym->declared_at);
854           else if (!named_common)
855             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
856                             "in a blank COMMON but initialization is only "
857                             "allowed in named common blocks", csym->name,
858                             &csym->declared_at);
859         }
860
861       if (csym->ts.type != BT_DERIVED)
862         continue;
863
864       if (!(csym->ts.u.derived->attr.sequence
865             || csym->ts.u.derived->attr.is_bind_c))
866         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
867                        "has neither the SEQUENCE nor the BIND(C) "
868                        "attribute", csym->name, &csym->declared_at);
869       if (csym->ts.u.derived->attr.alloc_comp)
870         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
871                        "has an ultimate component that is "
872                        "allocatable", csym->name, &csym->declared_at);
873       if (gfc_has_default_initializer (csym->ts.u.derived))
874         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
875                        "may not have default initializer", csym->name,
876                        &csym->declared_at);
877
878       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
879         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
880     }
881 }
882
883 /* Resolve common blocks.  */
884 static void
885 resolve_common_blocks (gfc_symtree *common_root)
886 {
887   gfc_symbol *sym;
888
889   if (common_root == NULL)
890     return;
891
892   if (common_root->left)
893     resolve_common_blocks (common_root->left);
894   if (common_root->right)
895     resolve_common_blocks (common_root->right);
896
897   resolve_common_vars (common_root->n.common->head, true);
898
899   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
900   if (sym == NULL)
901     return;
902
903   if (sym->attr.flavor == FL_PARAMETER)
904     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
905                sym->name, &common_root->n.common->where, &sym->declared_at);
906
907   if (sym->attr.intrinsic)
908     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
909                sym->name, &common_root->n.common->where);
910   else if (sym->attr.result
911            || gfc_is_function_return_value (sym, gfc_current_ns))
912     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
913                     "that is also a function result", sym->name,
914                     &common_root->n.common->where);
915   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
916            && sym->attr.proc != PROC_ST_FUNCTION)
917     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
918                     "that is also a global procedure", sym->name,
919                     &common_root->n.common->where);
920 }
921
922
923 /* Resolve contained function types.  Because contained functions can call one
924    another, they have to be worked out before any of the contained procedures
925    can be resolved.
926
927    The good news is that if a function doesn't already have a type, the only
928    way it can get one is through an IMPLICIT type or a RESULT variable, because
929    by definition contained functions are contained namespace they're contained
930    in, not in a sibling or parent namespace.  */
931
932 static void
933 resolve_contained_functions (gfc_namespace *ns)
934 {
935   gfc_namespace *child;
936   gfc_entry_list *el;
937
938   resolve_formal_arglists (ns);
939
940   for (child = ns->contained; child; child = child->sibling)
941     {
942       /* Resolve alternate entry points first.  */
943       resolve_entries (child);
944
945       /* Then check function return types.  */
946       resolve_contained_fntype (child->proc_name, child);
947       for (el = child->entries; el; el = el->next)
948         resolve_contained_fntype (el->sym, child);
949     }
950 }
951
952
953 /* Resolve all of the elements of a structure constructor and make sure that
954    the types are correct. The 'init' flag indicates that the given
955    constructor is an initializer.  */
956
957 static gfc_try
958 resolve_structure_cons (gfc_expr *expr, int init)
959 {
960   gfc_constructor *cons;
961   gfc_component *comp;
962   gfc_try t;
963   symbol_attribute a;
964
965   t = SUCCESS;
966
967   if (expr->ts.type == BT_DERIVED)
968     resolve_symbol (expr->ts.u.derived);
969
970   cons = gfc_constructor_first (expr->value.constructor);
971   /* A constructor may have references if it is the result of substituting a
972      parameter variable.  In this case we just pull out the component we
973      want.  */
974   if (expr->ref)
975     comp = expr->ref->u.c.sym->components;
976   else
977     comp = expr->ts.u.derived->components;
978
979   /* See if the user is trying to invoke a structure constructor for one of
980      the iso_c_binding derived types.  */
981   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
982       && expr->ts.u.derived->ts.is_iso_c && cons
983       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
984     {
985       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
986                  expr->ts.u.derived->name, &(expr->where));
987       return FAILURE;
988     }
989
990   /* Return if structure constructor is c_null_(fun)prt.  */
991   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
992       && expr->ts.u.derived->ts.is_iso_c && cons
993       && cons->expr && cons->expr->expr_type == EXPR_NULL)
994     return SUCCESS;
995
996   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
997     {
998       int rank;
999
1000       if (!cons->expr)
1001         continue;
1002
1003       if (gfc_resolve_expr (cons->expr) == FAILURE)
1004         {
1005           t = FAILURE;
1006           continue;
1007         }
1008
1009       rank = comp->as ? comp->as->rank : 0;
1010       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
1011           && (comp->attr.allocatable || cons->expr->rank))
1012         {
1013           gfc_error ("The rank of the element in the derived type "
1014                      "constructor at %L does not match that of the "
1015                      "component (%d/%d)", &cons->expr->where,
1016                      cons->expr->rank, rank);
1017           t = FAILURE;
1018         }
1019
1020       /* If we don't have the right type, try to convert it.  */
1021
1022       if (!comp->attr.proc_pointer &&
1023           !gfc_compare_types (&cons->expr->ts, &comp->ts))
1024         {
1025           t = FAILURE;
1026           if (strcmp (comp->name, "_extends") == 0)
1027             {
1028               /* Can afford to be brutal with the _extends initializer.
1029                  The derived type can get lost because it is PRIVATE
1030                  but it is not usage constrained by the standard.  */
1031               cons->expr->ts = comp->ts;
1032               t = SUCCESS;
1033             }
1034           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
1035             gfc_error ("The element in the derived type constructor at %L, "
1036                        "for pointer component '%s', is %s but should be %s",
1037                        &cons->expr->where, comp->name,
1038                        gfc_basic_typename (cons->expr->ts.type),
1039                        gfc_basic_typename (comp->ts.type));
1040           else
1041             t = gfc_convert_type (cons->expr, &comp->ts, 1);
1042         }
1043
1044       /* For strings, the length of the constructor should be the same as
1045          the one of the structure, ensure this if the lengths are known at
1046          compile time and when we are dealing with PARAMETER or structure
1047          constructors.  */
1048       if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1049           && comp->ts.u.cl->length
1050           && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1051           && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1052           && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1053           && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1054                       comp->ts.u.cl->length->value.integer) != 0)
1055         {
1056           if (cons->expr->expr_type == EXPR_VARIABLE
1057               && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1058             {
1059               /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1060                  to make use of the gfc_resolve_character_array_constructor
1061                  machinery.  The expression is later simplified away to
1062                  an array of string literals.  */
1063               gfc_expr *para = cons->expr;
1064               cons->expr = gfc_get_expr ();
1065               cons->expr->ts = para->ts;
1066               cons->expr->where = para->where;
1067               cons->expr->expr_type = EXPR_ARRAY;
1068               cons->expr->rank = para->rank;
1069               cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1070               gfc_constructor_append_expr (&cons->expr->value.constructor,
1071                                            para, &cons->expr->where);
1072             }
1073           if (cons->expr->expr_type == EXPR_ARRAY)
1074             {
1075               gfc_constructor *p;
1076               p = gfc_constructor_first (cons->expr->value.constructor);
1077               if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1078                 {
1079                   gfc_charlen *cl, *cl2;
1080
1081                   cl2 = NULL;
1082                   for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1083                     {
1084                       if (cl == cons->expr->ts.u.cl)
1085                         break;
1086                       cl2 = cl;
1087                     }
1088
1089                   gcc_assert (cl);
1090
1091                   if (cl2)
1092                     cl2->next = cl->next;
1093
1094                   gfc_free_expr (cl->length);
1095                   free (cl);
1096                 }
1097
1098               cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1099               cons->expr->ts.u.cl->length_from_typespec = true;
1100               cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1101               gfc_resolve_character_array_constructor (cons->expr);
1102             }
1103         }
1104
1105       if (cons->expr->expr_type == EXPR_NULL
1106           && !(comp->attr.pointer || comp->attr.allocatable
1107                || comp->attr.proc_pointer
1108                || (comp->ts.type == BT_CLASS
1109                    && (CLASS_DATA (comp)->attr.class_pointer
1110                        || CLASS_DATA (comp)->attr.allocatable))))
1111         {
1112           t = FAILURE;
1113           gfc_error ("The NULL in the derived type constructor at %L is "
1114                      "being applied to component '%s', which is neither "
1115                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
1116                      comp->name);
1117         }
1118
1119       if (!comp->attr.pointer || comp->attr.proc_pointer
1120           || cons->expr->expr_type == EXPR_NULL)
1121         continue;
1122
1123       a = gfc_expr_attr (cons->expr);
1124
1125       if (!a.pointer && !a.target)
1126         {
1127           t = FAILURE;
1128           gfc_error ("The element in the derived type constructor at %L, "
1129                      "for pointer component '%s' should be a POINTER or "
1130                      "a TARGET", &cons->expr->where, comp->name);
1131         }
1132
1133       if (init)
1134         {
1135           /* F08:C461. Additional checks for pointer initialization.  */
1136           if (a.allocatable)
1137             {
1138               t = FAILURE;
1139               gfc_error ("Pointer initialization target at %L "
1140                          "must not be ALLOCATABLE ", &cons->expr->where);
1141             }
1142           if (!a.save)
1143             {
1144               t = FAILURE;
1145               gfc_error ("Pointer initialization target at %L "
1146                          "must have the SAVE attribute", &cons->expr->where);
1147             }
1148         }
1149
1150       /* F2003, C1272 (3).  */
1151       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
1152           && (gfc_impure_variable (cons->expr->symtree->n.sym)
1153               || gfc_is_coindexed (cons->expr)))
1154         {
1155           t = FAILURE;
1156           gfc_error ("Invalid expression in the derived type constructor for "
1157                      "pointer component '%s' at %L in PURE procedure",
1158                      comp->name, &cons->expr->where);
1159         }
1160
1161       if (gfc_implicit_pure (NULL)
1162             && cons->expr->expr_type == EXPR_VARIABLE
1163             && (gfc_impure_variable (cons->expr->symtree->n.sym)
1164                 || gfc_is_coindexed (cons->expr)))
1165         gfc_current_ns->proc_name->attr.implicit_pure = 0;
1166
1167     }
1168
1169   return t;
1170 }
1171
1172
1173 /****************** Expression name resolution ******************/
1174
1175 /* Returns 0 if a symbol was not declared with a type or
1176    attribute declaration statement, nonzero otherwise.  */
1177
1178 static int
1179 was_declared (gfc_symbol *sym)
1180 {
1181   symbol_attribute a;
1182
1183   a = sym->attr;
1184
1185   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1186     return 1;
1187
1188   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1189       || a.optional || a.pointer || a.save || a.target || a.volatile_
1190       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1191       || a.asynchronous || a.codimension)
1192     return 1;
1193
1194   return 0;
1195 }
1196
1197
1198 /* Determine if a symbol is generic or not.  */
1199
1200 static int
1201 generic_sym (gfc_symbol *sym)
1202 {
1203   gfc_symbol *s;
1204
1205   if (sym->attr.generic ||
1206       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1207     return 1;
1208
1209   if (was_declared (sym) || sym->ns->parent == NULL)
1210     return 0;
1211
1212   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1213   
1214   if (s != NULL)
1215     {
1216       if (s == sym)
1217         return 0;
1218       else
1219         return generic_sym (s);
1220     }
1221
1222   return 0;
1223 }
1224
1225
1226 /* Determine if a symbol is specific or not.  */
1227
1228 static int
1229 specific_sym (gfc_symbol *sym)
1230 {
1231   gfc_symbol *s;
1232
1233   if (sym->attr.if_source == IFSRC_IFBODY
1234       || sym->attr.proc == PROC_MODULE
1235       || sym->attr.proc == PROC_INTERNAL
1236       || sym->attr.proc == PROC_ST_FUNCTION
1237       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1238       || sym->attr.external)
1239     return 1;
1240
1241   if (was_declared (sym) || sym->ns->parent == NULL)
1242     return 0;
1243
1244   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1245
1246   return (s == NULL) ? 0 : specific_sym (s);
1247 }
1248
1249
1250 /* Figure out if the procedure is specific, generic or unknown.  */
1251
1252 typedef enum
1253 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1254 proc_type;
1255
1256 static proc_type
1257 procedure_kind (gfc_symbol *sym)
1258 {
1259   if (generic_sym (sym))
1260     return PTYPE_GENERIC;
1261
1262   if (specific_sym (sym))
1263     return PTYPE_SPECIFIC;
1264
1265   return PTYPE_UNKNOWN;
1266 }
1267
1268 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1269    is nonzero when matching actual arguments.  */
1270
1271 static int need_full_assumed_size = 0;
1272
1273 static bool
1274 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1275 {
1276   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1277       return false;
1278
1279   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1280      What should it be?  */
1281   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1282           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1283                && (e->ref->u.ar.type == AR_FULL))
1284     {
1285       gfc_error ("The upper bound in the last dimension must "
1286                  "appear in the reference to the assumed size "
1287                  "array '%s' at %L", sym->name, &e->where);
1288       return true;
1289     }
1290   return false;
1291 }
1292
1293
1294 /* Look for bad assumed size array references in argument expressions
1295   of elemental and array valued intrinsic procedures.  Since this is
1296   called from procedure resolution functions, it only recurses at
1297   operators.  */
1298
1299 static bool
1300 resolve_assumed_size_actual (gfc_expr *e)
1301 {
1302   if (e == NULL)
1303    return false;
1304
1305   switch (e->expr_type)
1306     {
1307     case EXPR_VARIABLE:
1308       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1309         return true;
1310       break;
1311
1312     case EXPR_OP:
1313       if (resolve_assumed_size_actual (e->value.op.op1)
1314           || resolve_assumed_size_actual (e->value.op.op2))
1315         return true;
1316       break;
1317
1318     default:
1319       break;
1320     }
1321   return false;
1322 }
1323
1324
1325 /* Check a generic procedure, passed as an actual argument, to see if
1326    there is a matching specific name.  If none, it is an error, and if
1327    more than one, the reference is ambiguous.  */
1328 static int
1329 count_specific_procs (gfc_expr *e)
1330 {
1331   int n;
1332   gfc_interface *p;
1333   gfc_symbol *sym;
1334         
1335   n = 0;
1336   sym = e->symtree->n.sym;
1337
1338   for (p = sym->generic; p; p = p->next)
1339     if (strcmp (sym->name, p->sym->name) == 0)
1340       {
1341         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1342                                        sym->name);
1343         n++;
1344       }
1345
1346   if (n > 1)
1347     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1348                &e->where);
1349
1350   if (n == 0)
1351     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1352                "argument at %L", sym->name, &e->where);
1353
1354   return n;
1355 }
1356
1357
1358 /* See if a call to sym could possibly be a not allowed RECURSION because of
1359    a missing RECURIVE declaration.  This means that either sym is the current
1360    context itself, or sym is the parent of a contained procedure calling its
1361    non-RECURSIVE containing procedure.
1362    This also works if sym is an ENTRY.  */
1363
1364 static bool
1365 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1366 {
1367   gfc_symbol* proc_sym;
1368   gfc_symbol* context_proc;
1369   gfc_namespace* real_context;
1370
1371   if (sym->attr.flavor == FL_PROGRAM)
1372     return false;
1373
1374   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1375
1376   /* If we've got an ENTRY, find real procedure.  */
1377   if (sym->attr.entry && sym->ns->entries)
1378     proc_sym = sym->ns->entries->sym;
1379   else
1380     proc_sym = sym;
1381
1382   /* If sym is RECURSIVE, all is well of course.  */
1383   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1384     return false;
1385
1386   /* Find the context procedure's "real" symbol if it has entries.
1387      We look for a procedure symbol, so recurse on the parents if we don't
1388      find one (like in case of a BLOCK construct).  */
1389   for (real_context = context; ; real_context = real_context->parent)
1390     {
1391       /* We should find something, eventually!  */
1392       gcc_assert (real_context);
1393
1394       context_proc = (real_context->entries ? real_context->entries->sym
1395                                             : real_context->proc_name);
1396
1397       /* In some special cases, there may not be a proc_name, like for this
1398          invalid code:
1399          real(bad_kind()) function foo () ...
1400          when checking the call to bad_kind ().
1401          In these cases, we simply return here and assume that the
1402          call is ok.  */
1403       if (!context_proc)
1404         return false;
1405
1406       if (context_proc->attr.flavor != FL_LABEL)
1407         break;
1408     }
1409
1410   /* A call from sym's body to itself is recursion, of course.  */
1411   if (context_proc == proc_sym)
1412     return true;
1413
1414   /* The same is true if context is a contained procedure and sym the
1415      containing one.  */
1416   if (context_proc->attr.contained)
1417     {
1418       gfc_symbol* parent_proc;
1419
1420       gcc_assert (context->parent);
1421       parent_proc = (context->parent->entries ? context->parent->entries->sym
1422                                               : context->parent->proc_name);
1423
1424       if (parent_proc == proc_sym)
1425         return true;
1426     }
1427
1428   return false;
1429 }
1430
1431
1432 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1433    its typespec and formal argument list.  */
1434
1435 static gfc_try
1436 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1437 {
1438   gfc_intrinsic_sym* isym = NULL;
1439   const char* symstd;
1440
1441   if (sym->formal)
1442     return SUCCESS;
1443
1444   /* We already know this one is an intrinsic, so we don't call
1445      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1446      gfc_find_subroutine directly to check whether it is a function or
1447      subroutine.  */
1448
1449   if (sym->intmod_sym_id)
1450     isym = gfc_intrinsic_function_by_id ((gfc_isym_id) sym->intmod_sym_id);
1451   else
1452     isym = gfc_find_function (sym->name);
1453
1454   if (isym)
1455     {
1456       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1457           && !sym->attr.implicit_type)
1458         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1459                       " ignored", sym->name, &sym->declared_at);
1460
1461       if (!sym->attr.function &&
1462           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1463         return FAILURE;
1464
1465       sym->ts = isym->ts;
1466     }
1467   else if ((isym = gfc_find_subroutine (sym->name)))
1468     {
1469       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1470         {
1471           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1472                       " specifier", sym->name, &sym->declared_at);
1473           return FAILURE;
1474         }
1475
1476       if (!sym->attr.subroutine &&
1477           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1478         return FAILURE;
1479     }
1480   else
1481     {
1482       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1483                  &sym->declared_at);
1484       return FAILURE;
1485     }
1486
1487   gfc_copy_formal_args_intr (sym, isym);
1488
1489   /* Check it is actually available in the standard settings.  */
1490   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1491       == FAILURE)
1492     {
1493       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1494                  " available in the current standard settings but %s.  Use"
1495                  " an appropriate -std=* option or enable -fall-intrinsics"
1496                  " in order to use it.",
1497                  sym->name, &sym->declared_at, symstd);
1498       return FAILURE;
1499     }
1500
1501   return SUCCESS;
1502 }
1503
1504
1505 /* Resolve a procedure expression, like passing it to a called procedure or as
1506    RHS for a procedure pointer assignment.  */
1507
1508 static gfc_try
1509 resolve_procedure_expression (gfc_expr* expr)
1510 {
1511   gfc_symbol* sym;
1512
1513   if (expr->expr_type != EXPR_VARIABLE)
1514     return SUCCESS;
1515   gcc_assert (expr->symtree);
1516
1517   sym = expr->symtree->n.sym;
1518
1519   if (sym->attr.intrinsic)
1520     resolve_intrinsic (sym, &expr->where);
1521
1522   if (sym->attr.flavor != FL_PROCEDURE
1523       || (sym->attr.function && sym->result == sym))
1524     return SUCCESS;
1525
1526   /* A non-RECURSIVE procedure that is used as procedure expression within its
1527      own body is in danger of being called recursively.  */
1528   if (is_illegal_recursion (sym, gfc_current_ns))
1529     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1530                  " itself recursively.  Declare it RECURSIVE or use"
1531                  " -frecursive", sym->name, &expr->where);
1532   
1533   return SUCCESS;
1534 }
1535
1536
1537 /* Resolve an actual argument list.  Most of the time, this is just
1538    resolving the expressions in the list.
1539    The exception is that we sometimes have to decide whether arguments
1540    that look like procedure arguments are really simple variable
1541    references.  */
1542
1543 static gfc_try
1544 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1545                         bool no_formal_args)
1546 {
1547   gfc_symbol *sym;
1548   gfc_symtree *parent_st;
1549   gfc_expr *e;
1550   int save_need_full_assumed_size;
1551
1552   for (; arg; arg = arg->next)
1553     {
1554       e = arg->expr;
1555       if (e == NULL)
1556         {
1557           /* Check the label is a valid branching target.  */
1558           if (arg->label)
1559             {
1560               if (arg->label->defined == ST_LABEL_UNKNOWN)
1561                 {
1562                   gfc_error ("Label %d referenced at %L is never defined",
1563                              arg->label->value, &arg->label->where);
1564                   return FAILURE;
1565                 }
1566             }
1567           continue;
1568         }
1569
1570       if (e->expr_type == EXPR_VARIABLE
1571             && e->symtree->n.sym->attr.generic
1572             && no_formal_args
1573             && count_specific_procs (e) != 1)
1574         return FAILURE;
1575
1576       if (e->ts.type != BT_PROCEDURE)
1577         {
1578           save_need_full_assumed_size = need_full_assumed_size;
1579           if (e->expr_type != EXPR_VARIABLE)
1580             need_full_assumed_size = 0;
1581           if (gfc_resolve_expr (e) != SUCCESS)
1582             return FAILURE;
1583           need_full_assumed_size = save_need_full_assumed_size;
1584           goto argument_list;
1585         }
1586
1587       /* See if the expression node should really be a variable reference.  */
1588
1589       sym = e->symtree->n.sym;
1590
1591       if (sym->attr.flavor == FL_PROCEDURE
1592           || sym->attr.intrinsic
1593           || sym->attr.external)
1594         {
1595           int actual_ok;
1596
1597           /* If a procedure is not already determined to be something else
1598              check if it is intrinsic.  */
1599           if (!sym->attr.intrinsic
1600               && !(sym->attr.external || sym->attr.use_assoc
1601                    || sym->attr.if_source == IFSRC_IFBODY)
1602               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1603             sym->attr.intrinsic = 1;
1604
1605           if (sym->attr.proc == PROC_ST_FUNCTION)
1606             {
1607               gfc_error ("Statement function '%s' at %L is not allowed as an "
1608                          "actual argument", sym->name, &e->where);
1609             }
1610
1611           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1612                                                sym->attr.subroutine);
1613           if (sym->attr.intrinsic && actual_ok == 0)
1614             {
1615               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1616                          "actual argument", sym->name, &e->where);
1617             }
1618
1619           if (sym->attr.contained && !sym->attr.use_assoc
1620               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1621             {
1622               if (gfc_notify_std (GFC_STD_F2008,
1623                                   "Fortran 2008: Internal procedure '%s' is"
1624                                   " used as actual argument at %L",
1625                                   sym->name, &e->where) == FAILURE)
1626                 return FAILURE;
1627             }
1628
1629           if (sym->attr.elemental && !sym->attr.intrinsic)
1630             {
1631               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1632                          "allowed as an actual argument at %L", sym->name,
1633                          &e->where);
1634             }
1635
1636           /* Check if a generic interface has a specific procedure
1637             with the same name before emitting an error.  */
1638           if (sym->attr.generic && count_specific_procs (e) != 1)
1639             return FAILURE;
1640           
1641           /* Just in case a specific was found for the expression.  */
1642           sym = e->symtree->n.sym;
1643
1644           /* If the symbol is the function that names the current (or
1645              parent) scope, then we really have a variable reference.  */
1646
1647           if (gfc_is_function_return_value (sym, sym->ns))
1648             goto got_variable;
1649
1650           /* If all else fails, see if we have a specific intrinsic.  */
1651           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1652             {
1653               gfc_intrinsic_sym *isym;
1654
1655               isym = gfc_find_function (sym->name);
1656               if (isym == NULL || !isym->specific)
1657                 {
1658                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1659                              "for the reference '%s' at %L", sym->name,
1660                              &e->where);
1661                   return FAILURE;
1662                 }
1663               sym->ts = isym->ts;
1664               sym->attr.intrinsic = 1;
1665               sym->attr.function = 1;
1666             }
1667
1668           if (gfc_resolve_expr (e) == FAILURE)
1669             return FAILURE;
1670           goto argument_list;
1671         }
1672
1673       /* See if the name is a module procedure in a parent unit.  */
1674
1675       if (was_declared (sym) || sym->ns->parent == NULL)
1676         goto got_variable;
1677
1678       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1679         {
1680           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1681           return FAILURE;
1682         }
1683
1684       if (parent_st == NULL)
1685         goto got_variable;
1686
1687       sym = parent_st->n.sym;
1688       e->symtree = parent_st;           /* Point to the right thing.  */
1689
1690       if (sym->attr.flavor == FL_PROCEDURE
1691           || sym->attr.intrinsic
1692           || sym->attr.external)
1693         {
1694           if (gfc_resolve_expr (e) == FAILURE)
1695             return FAILURE;
1696           goto argument_list;
1697         }
1698
1699     got_variable:
1700       e->expr_type = EXPR_VARIABLE;
1701       e->ts = sym->ts;
1702       if (sym->as != NULL)
1703         {
1704           e->rank = sym->as->rank;
1705           e->ref = gfc_get_ref ();
1706           e->ref->type = REF_ARRAY;
1707           e->ref->u.ar.type = AR_FULL;
1708           e->ref->u.ar.as = sym->as;
1709         }
1710
1711       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1712          primary.c (match_actual_arg). If above code determines that it
1713          is a  variable instead, it needs to be resolved as it was not
1714          done at the beginning of this function.  */
1715       save_need_full_assumed_size = need_full_assumed_size;
1716       if (e->expr_type != EXPR_VARIABLE)
1717         need_full_assumed_size = 0;
1718       if (gfc_resolve_expr (e) != SUCCESS)
1719         return FAILURE;
1720       need_full_assumed_size = save_need_full_assumed_size;
1721
1722     argument_list:
1723       /* Check argument list functions %VAL, %LOC and %REF.  There is
1724          nothing to do for %REF.  */
1725       if (arg->name && arg->name[0] == '%')
1726         {
1727           if (strncmp ("%VAL", arg->name, 4) == 0)
1728             {
1729               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1730                 {
1731                   gfc_error ("By-value argument at %L is not of numeric "
1732                              "type", &e->where);
1733                   return FAILURE;
1734                 }
1735
1736               if (e->rank)
1737                 {
1738                   gfc_error ("By-value argument at %L cannot be an array or "
1739                              "an array section", &e->where);
1740                 return FAILURE;
1741                 }
1742
1743               /* Intrinsics are still PROC_UNKNOWN here.  However,
1744                  since same file external procedures are not resolvable
1745                  in gfortran, it is a good deal easier to leave them to
1746                  intrinsic.c.  */
1747               if (ptype != PROC_UNKNOWN
1748                   && ptype != PROC_DUMMY
1749                   && ptype != PROC_EXTERNAL
1750                   && ptype != PROC_MODULE)
1751                 {
1752                   gfc_error ("By-value argument at %L is not allowed "
1753                              "in this context", &e->where);
1754                   return FAILURE;
1755                 }
1756             }
1757
1758           /* Statement functions have already been excluded above.  */
1759           else if (strncmp ("%LOC", arg->name, 4) == 0
1760                    && e->ts.type == BT_PROCEDURE)
1761             {
1762               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1763                 {
1764                   gfc_error ("Passing internal procedure at %L by location "
1765                              "not allowed", &e->where);
1766                   return FAILURE;
1767                 }
1768             }
1769         }
1770
1771       /* Fortran 2008, C1237.  */
1772       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1773           && gfc_has_ultimate_pointer (e))
1774         {
1775           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1776                      "component", &e->where);
1777           return FAILURE;
1778         }
1779     }
1780
1781   return SUCCESS;
1782 }
1783
1784
1785 /* Do the checks of the actual argument list that are specific to elemental
1786    procedures.  If called with c == NULL, we have a function, otherwise if
1787    expr == NULL, we have a subroutine.  */
1788
1789 static gfc_try
1790 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1791 {
1792   gfc_actual_arglist *arg0;
1793   gfc_actual_arglist *arg;
1794   gfc_symbol *esym = NULL;
1795   gfc_intrinsic_sym *isym = NULL;
1796   gfc_expr *e = NULL;
1797   gfc_intrinsic_arg *iformal = NULL;
1798   gfc_formal_arglist *eformal = NULL;
1799   bool formal_optional = false;
1800   bool set_by_optional = false;
1801   int i;
1802   int rank = 0;
1803
1804   /* Is this an elemental procedure?  */
1805   if (expr && expr->value.function.actual != NULL)
1806     {
1807       if (expr->value.function.esym != NULL
1808           && expr->value.function.esym->attr.elemental)
1809         {
1810           arg0 = expr->value.function.actual;
1811           esym = expr->value.function.esym;
1812         }
1813       else if (expr->value.function.isym != NULL
1814                && expr->value.function.isym->elemental)
1815         {
1816           arg0 = expr->value.function.actual;
1817           isym = expr->value.function.isym;
1818         }
1819       else
1820         return SUCCESS;
1821     }
1822   else if (c && c->ext.actual != NULL)
1823     {
1824       arg0 = c->ext.actual;
1825       
1826       if (c->resolved_sym)
1827         esym = c->resolved_sym;
1828       else
1829         esym = c->symtree->n.sym;
1830       gcc_assert (esym);
1831
1832       if (!esym->attr.elemental)
1833         return SUCCESS;
1834     }
1835   else
1836     return SUCCESS;
1837
1838   /* The rank of an elemental is the rank of its array argument(s).  */
1839   for (arg = arg0; arg; arg = arg->next)
1840     {
1841       if (arg->expr != NULL && arg->expr->rank > 0)
1842         {
1843           rank = arg->expr->rank;
1844           if (arg->expr->expr_type == EXPR_VARIABLE
1845               && arg->expr->symtree->n.sym->attr.optional)
1846             set_by_optional = true;
1847
1848           /* Function specific; set the result rank and shape.  */
1849           if (expr)
1850             {
1851               expr->rank = rank;
1852               if (!expr->shape && arg->expr->shape)
1853                 {
1854                   expr->shape = gfc_get_shape (rank);
1855                   for (i = 0; i < rank; i++)
1856                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1857                 }
1858             }
1859           break;
1860         }
1861     }
1862
1863   /* If it is an array, it shall not be supplied as an actual argument
1864      to an elemental procedure unless an array of the same rank is supplied
1865      as an actual argument corresponding to a nonoptional dummy argument of
1866      that elemental procedure(12.4.1.5).  */
1867   formal_optional = false;
1868   if (isym)
1869     iformal = isym->formal;
1870   else
1871     eformal = esym->formal;
1872
1873   for (arg = arg0; arg; arg = arg->next)
1874     {
1875       if (eformal)
1876         {
1877           if (eformal->sym && eformal->sym->attr.optional)
1878             formal_optional = true;
1879           eformal = eformal->next;
1880         }
1881       else if (isym && iformal)
1882         {
1883           if (iformal->optional)
1884             formal_optional = true;
1885           iformal = iformal->next;
1886         }
1887       else if (isym)
1888         formal_optional = true;
1889
1890       if (pedantic && arg->expr != NULL
1891           && arg->expr->expr_type == EXPR_VARIABLE
1892           && arg->expr->symtree->n.sym->attr.optional
1893           && formal_optional
1894           && arg->expr->rank
1895           && (set_by_optional || arg->expr->rank != rank)
1896           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1897         {
1898           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1899                        "MISSING, it cannot be the actual argument of an "
1900                        "ELEMENTAL procedure unless there is a non-optional "
1901                        "argument with the same rank (12.4.1.5)",
1902                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1903           return FAILURE;
1904         }
1905     }
1906
1907   for (arg = arg0; arg; arg = arg->next)
1908     {
1909       if (arg->expr == NULL || arg->expr->rank == 0)
1910         continue;
1911
1912       /* Being elemental, the last upper bound of an assumed size array
1913          argument must be present.  */
1914       if (resolve_assumed_size_actual (arg->expr))
1915         return FAILURE;
1916
1917       /* Elemental procedure's array actual arguments must conform.  */
1918       if (e != NULL)
1919         {
1920           if (gfc_check_conformance (arg->expr, e,
1921                                      "elemental procedure") == FAILURE)
1922             return FAILURE;
1923         }
1924       else
1925         e = arg->expr;
1926     }
1927
1928   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1929      is an array, the intent inout/out variable needs to be also an array.  */
1930   if (rank > 0 && esym && expr == NULL)
1931     for (eformal = esym->formal, arg = arg0; arg && eformal;
1932          arg = arg->next, eformal = eformal->next)
1933       if ((eformal->sym->attr.intent == INTENT_OUT
1934            || eformal->sym->attr.intent == INTENT_INOUT)
1935           && arg->expr && arg->expr->rank == 0)
1936         {
1937           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1938                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1939                      "actual argument is an array", &arg->expr->where,
1940                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1941                      : "INOUT", eformal->sym->name, esym->name);
1942           return FAILURE;
1943         }
1944   return SUCCESS;
1945 }
1946
1947
1948 /* This function does the checking of references to global procedures
1949    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1950    77 and 95 standards.  It checks for a gsymbol for the name, making
1951    one if it does not already exist.  If it already exists, then the
1952    reference being resolved must correspond to the type of gsymbol.
1953    Otherwise, the new symbol is equipped with the attributes of the
1954    reference.  The corresponding code that is called in creating
1955    global entities is parse.c.
1956
1957    In addition, for all but -std=legacy, the gsymbols are used to
1958    check the interfaces of external procedures from the same file.
1959    The namespace of the gsymbol is resolved and then, once this is
1960    done the interface is checked.  */
1961
1962
1963 static bool
1964 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1965 {
1966   if (!gsym_ns->proc_name->attr.recursive)
1967     return true;
1968
1969   if (sym->ns == gsym_ns)
1970     return false;
1971
1972   if (sym->ns->parent && sym->ns->parent == gsym_ns)
1973     return false;
1974
1975   return true;
1976 }
1977
1978 static bool
1979 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
1980 {
1981   if (gsym_ns->entries)
1982     {
1983       gfc_entry_list *entry = gsym_ns->entries;
1984
1985       for (; entry; entry = entry->next)
1986         {
1987           if (strcmp (sym->name, entry->sym->name) == 0)
1988             {
1989               if (strcmp (gsym_ns->proc_name->name,
1990                           sym->ns->proc_name->name) == 0)
1991                 return false;
1992
1993               if (sym->ns->parent
1994                   && strcmp (gsym_ns->proc_name->name,
1995                              sym->ns->parent->proc_name->name) == 0)
1996                 return false;
1997             }
1998         }
1999     }
2000   return true;
2001 }
2002
2003 static void
2004 resolve_global_procedure (gfc_symbol *sym, locus *where,
2005                           gfc_actual_arglist **actual, int sub)
2006 {
2007   gfc_gsymbol * gsym;
2008   gfc_namespace *ns;
2009   enum gfc_symbol_type type;
2010
2011   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
2012
2013   gsym = gfc_get_gsymbol (sym->name);
2014
2015   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
2016     gfc_global_used (gsym, where);
2017
2018   if (gfc_option.flag_whole_file
2019         && (sym->attr.if_source == IFSRC_UNKNOWN
2020             || sym->attr.if_source == IFSRC_IFBODY)
2021         && gsym->type != GSYM_UNKNOWN
2022         && gsym->ns
2023         && gsym->ns->resolved != -1
2024         && gsym->ns->proc_name
2025         && not_in_recursive (sym, gsym->ns)
2026         && not_entry_self_reference (sym, gsym->ns))
2027     {
2028       gfc_symbol *def_sym;
2029
2030       /* Resolve the gsymbol namespace if needed.  */
2031       if (!gsym->ns->resolved)
2032         {
2033           gfc_dt_list *old_dt_list;
2034           struct gfc_omp_saved_state old_omp_state;
2035
2036           /* Stash away derived types so that the backend_decls do not
2037              get mixed up.  */
2038           old_dt_list = gfc_derived_types;
2039           gfc_derived_types = NULL;
2040           /* And stash away openmp state.  */
2041           gfc_omp_save_and_clear_state (&old_omp_state);
2042
2043           gfc_resolve (gsym->ns);
2044
2045           /* Store the new derived types with the global namespace.  */
2046           if (gfc_derived_types)
2047             gsym->ns->derived_types = gfc_derived_types;
2048
2049           /* Restore the derived types of this namespace.  */
2050           gfc_derived_types = old_dt_list;
2051           /* And openmp state.  */
2052           gfc_omp_restore_state (&old_omp_state);
2053         }
2054
2055       /* Make sure that translation for the gsymbol occurs before
2056          the procedure currently being resolved.  */
2057       ns = gfc_global_ns_list;
2058       for (; ns && ns != gsym->ns; ns = ns->sibling)
2059         {
2060           if (ns->sibling == gsym->ns)
2061             {
2062               ns->sibling = gsym->ns->sibling;
2063               gsym->ns->sibling = gfc_global_ns_list;
2064               gfc_global_ns_list = gsym->ns;
2065               break;
2066             }
2067         }
2068
2069       def_sym = gsym->ns->proc_name;
2070       if (def_sym->attr.entry_master)
2071         {
2072           gfc_entry_list *entry;
2073           for (entry = gsym->ns->entries; entry; entry = entry->next)
2074             if (strcmp (entry->sym->name, sym->name) == 0)
2075               {
2076                 def_sym = entry->sym;
2077                 break;
2078               }
2079         }
2080
2081       /* Differences in constant character lengths.  */
2082       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
2083         {
2084           long int l1 = 0, l2 = 0;
2085           gfc_charlen *cl1 = sym->ts.u.cl;
2086           gfc_charlen *cl2 = def_sym->ts.u.cl;
2087
2088           if (cl1 != NULL
2089               && cl1->length != NULL
2090               && cl1->length->expr_type == EXPR_CONSTANT)
2091             l1 = mpz_get_si (cl1->length->value.integer);
2092
2093           if (cl2 != NULL
2094               && cl2->length != NULL
2095               && cl2->length->expr_type == EXPR_CONSTANT)
2096             l2 = mpz_get_si (cl2->length->value.integer);
2097
2098           if (l1 && l2 && l1 != l2)
2099             gfc_error ("Character length mismatch in return type of "
2100                        "function '%s' at %L (%ld/%ld)", sym->name,
2101                        &sym->declared_at, l1, l2);
2102         }
2103
2104      /* Type mismatch of function return type and expected type.  */
2105      if (sym->attr.function
2106          && !gfc_compare_types (&sym->ts, &def_sym->ts))
2107         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
2108                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2109                    gfc_typename (&def_sym->ts));
2110
2111       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
2112         {
2113           gfc_formal_arglist *arg = def_sym->formal;
2114           for ( ; arg; arg = arg->next)
2115             if (!arg->sym)
2116               continue;
2117             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
2118             else if (arg->sym->attr.allocatable
2119                      || arg->sym->attr.asynchronous
2120                      || arg->sym->attr.optional
2121                      || arg->sym->attr.pointer
2122                      || arg->sym->attr.target
2123                      || arg->sym->attr.value
2124                      || arg->sym->attr.volatile_)
2125               {
2126                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
2127                            "has an attribute that requires an explicit "
2128                            "interface for this procedure", arg->sym->name,
2129                            sym->name, &sym->declared_at);
2130                 break;
2131               }
2132             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
2133             else if (arg->sym && arg->sym->as
2134                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
2135               {
2136                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
2137                            "argument '%s' must have an explicit interface",
2138                            sym->name, &sym->declared_at, arg->sym->name);
2139                 break;
2140               }
2141             /* F2008, 12.4.2.2 (2c)  */
2142             else if (arg->sym->attr.codimension)
2143               {
2144                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
2145                            "'%s' must have an explicit interface",
2146                            sym->name, &sym->declared_at, arg->sym->name);
2147                 break;
2148               }
2149             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
2150             else if (false) /* TODO: is a parametrized derived type  */
2151               {
2152                 gfc_error ("Procedure '%s' at %L with parametrized derived "
2153                            "type argument '%s' must have an explicit "
2154                            "interface", sym->name, &sym->declared_at,
2155                            arg->sym->name);
2156                 break;
2157               }
2158             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
2159             else if (arg->sym->ts.type == BT_CLASS)
2160               {
2161                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
2162                            "argument '%s' must have an explicit interface",
2163                            sym->name, &sym->declared_at, arg->sym->name);
2164                 break;
2165               }
2166         }
2167
2168       if (def_sym->attr.function)
2169         {
2170           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
2171           if (def_sym->as && def_sym->as->rank
2172               && (!sym->as || sym->as->rank != def_sym->as->rank))
2173             gfc_error ("The reference to function '%s' at %L either needs an "
2174                        "explicit INTERFACE or the rank is incorrect", sym->name,
2175                        where);
2176
2177           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
2178           if ((def_sym->result->attr.pointer
2179                || def_sym->result->attr.allocatable)
2180                && (sym->attr.if_source != IFSRC_IFBODY
2181                    || def_sym->result->attr.pointer
2182                         != sym->result->attr.pointer
2183                    || def_sym->result->attr.allocatable
2184                         != sym->result->attr.allocatable))
2185             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
2186                        "result must have an explicit interface", sym->name,
2187                        where);
2188
2189           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
2190           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
2191               && def_sym->ts.type == BT_CHARACTER && def_sym->ts.u.cl->length != NULL)
2192             {
2193               gfc_charlen *cl = sym->ts.u.cl;
2194
2195               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
2196                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
2197                 {
2198                   gfc_error ("Nonconstant character-length function '%s' at %L "
2199                              "must have an explicit interface", sym->name,
2200                              &sym->declared_at);
2201                 }
2202             }
2203         }
2204
2205       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2206       if (def_sym->attr.elemental && !sym->attr.elemental)
2207         {
2208           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2209                      "interface", sym->name, &sym->declared_at);
2210         }
2211
2212       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2213       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2214         {
2215           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2216                      "an explicit interface", sym->name, &sym->declared_at);
2217         }
2218
2219       if (gfc_option.flag_whole_file == 1
2220           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2221               && !(gfc_option.warn_std & GFC_STD_GNU)))
2222         gfc_errors_to_warnings (1);
2223
2224       if (sym->attr.if_source != IFSRC_IFBODY)  
2225         gfc_procedure_use (def_sym, actual, where);
2226
2227       gfc_errors_to_warnings (0);
2228     }
2229
2230   if (gsym->type == GSYM_UNKNOWN)
2231     {
2232       gsym->type = type;
2233       gsym->where = *where;
2234     }
2235
2236   gsym->used = 1;
2237 }
2238
2239
2240 /************* Function resolution *************/
2241
2242 /* Resolve a function call known to be generic.
2243    Section 14.1.2.4.1.  */
2244
2245 static match
2246 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2247 {
2248   gfc_symbol *s;
2249
2250   if (sym->attr.generic)
2251     {
2252       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2253       if (s != NULL)
2254         {
2255           expr->value.function.name = s->name;
2256           expr->value.function.esym = s;
2257
2258           if (s->ts.type != BT_UNKNOWN)
2259             expr->ts = s->ts;
2260           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2261             expr->ts = s->result->ts;
2262
2263           if (s->as != NULL)
2264             expr->rank = s->as->rank;
2265           else if (s->result != NULL && s->result->as != NULL)
2266             expr->rank = s->result->as->rank;
2267
2268           gfc_set_sym_referenced (expr->value.function.esym);
2269
2270           return MATCH_YES;
2271         }
2272
2273       /* TODO: Need to search for elemental references in generic
2274          interface.  */
2275     }
2276
2277   if (sym->attr.intrinsic)
2278     return gfc_intrinsic_func_interface (expr, 0);
2279
2280   return MATCH_NO;
2281 }
2282
2283
2284 static gfc_try
2285 resolve_generic_f (gfc_expr *expr)
2286 {
2287   gfc_symbol *sym;
2288   match m;
2289
2290   sym = expr->symtree->n.sym;
2291
2292   for (;;)
2293     {
2294       m = resolve_generic_f0 (expr, sym);
2295       if (m == MATCH_YES)
2296         return SUCCESS;
2297       else if (m == MATCH_ERROR)
2298         return FAILURE;
2299
2300 generic:
2301       if (sym->ns->parent == NULL)
2302         break;
2303       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2304
2305       if (sym == NULL)
2306         break;
2307       if (!generic_sym (sym))
2308         goto generic;
2309     }
2310
2311   /* Last ditch attempt.  See if the reference is to an intrinsic
2312      that possesses a matching interface.  14.1.2.4  */
2313   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
2314     {
2315       gfc_error ("There is no specific function for the generic '%s' at %L",
2316                  expr->symtree->n.sym->name, &expr->where);
2317       return FAILURE;
2318     }
2319
2320   m = gfc_intrinsic_func_interface (expr, 0);
2321   if (m == MATCH_YES)
2322     return SUCCESS;
2323   if (m == MATCH_NO)
2324     gfc_error ("Generic function '%s' at %L is not consistent with a "
2325                "specific intrinsic interface", expr->symtree->n.sym->name,
2326                &expr->where);
2327
2328   return FAILURE;
2329 }
2330
2331
2332 /* Resolve a function call known to be specific.  */
2333
2334 static match
2335 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2336 {
2337   match m;
2338
2339   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2340     {
2341       if (sym->attr.dummy)
2342         {
2343           sym->attr.proc = PROC_DUMMY;
2344           goto found;
2345         }
2346
2347       sym->attr.proc = PROC_EXTERNAL;
2348       goto found;
2349     }
2350
2351   if (sym->attr.proc == PROC_MODULE
2352       || sym->attr.proc == PROC_ST_FUNCTION
2353       || sym->attr.proc == PROC_INTERNAL)
2354     goto found;
2355
2356   if (sym->attr.intrinsic)
2357     {
2358       m = gfc_intrinsic_func_interface (expr, 1);
2359       if (m == MATCH_YES)
2360         return MATCH_YES;
2361       if (m == MATCH_NO)
2362         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2363                    "with an intrinsic", sym->name, &expr->where);
2364
2365       return MATCH_ERROR;
2366     }
2367
2368   return MATCH_NO;
2369
2370 found:
2371   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2372
2373   if (sym->result)
2374     expr->ts = sym->result->ts;
2375   else
2376     expr->ts = sym->ts;
2377   expr->value.function.name = sym->name;
2378   expr->value.function.esym = sym;
2379   if (sym->as != NULL)
2380     expr->rank = sym->as->rank;
2381
2382   return MATCH_YES;
2383 }
2384
2385
2386 static gfc_try
2387 resolve_specific_f (gfc_expr *expr)
2388 {
2389   gfc_symbol *sym;
2390   match m;
2391
2392   sym = expr->symtree->n.sym;
2393
2394   for (;;)
2395     {
2396       m = resolve_specific_f0 (sym, expr);
2397       if (m == MATCH_YES)
2398         return SUCCESS;
2399       if (m == MATCH_ERROR)
2400         return FAILURE;
2401
2402       if (sym->ns->parent == NULL)
2403         break;
2404
2405       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2406
2407       if (sym == NULL)
2408         break;
2409     }
2410
2411   gfc_error ("Unable to resolve the specific function '%s' at %L",
2412              expr->symtree->n.sym->name, &expr->where);
2413
2414   return SUCCESS;
2415 }
2416
2417
2418 /* Resolve a procedure call not known to be generic nor specific.  */
2419
2420 static gfc_try
2421 resolve_unknown_f (gfc_expr *expr)
2422 {
2423   gfc_symbol *sym;
2424   gfc_typespec *ts;
2425
2426   sym = expr->symtree->n.sym;
2427
2428   if (sym->attr.dummy)
2429     {
2430       sym->attr.proc = PROC_DUMMY;
2431       expr->value.function.name = sym->name;
2432       goto set_type;
2433     }
2434
2435   /* See if we have an intrinsic function reference.  */
2436
2437   if (gfc_is_intrinsic (sym, 0, expr->where))
2438     {
2439       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2440         return SUCCESS;
2441       return FAILURE;
2442     }
2443
2444   /* The reference is to an external name.  */
2445
2446   sym->attr.proc = PROC_EXTERNAL;
2447   expr->value.function.name = sym->name;
2448   expr->value.function.esym = expr->symtree->n.sym;
2449
2450   if (sym->as != NULL)
2451     expr->rank = sym->as->rank;
2452
2453   /* Type of the expression is either the type of the symbol or the
2454      default type of the symbol.  */
2455
2456 set_type:
2457   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2458
2459   if (sym->ts.type != BT_UNKNOWN)
2460     expr->ts = sym->ts;
2461   else
2462     {
2463       ts = gfc_get_default_type (sym->name, sym->ns);
2464
2465       if (ts->type == BT_UNKNOWN)
2466         {
2467           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2468                      sym->name, &expr->where);
2469           return FAILURE;
2470         }
2471       else
2472         expr->ts = *ts;
2473     }
2474
2475   return SUCCESS;
2476 }
2477
2478
2479 /* Return true, if the symbol is an external procedure.  */
2480 static bool
2481 is_external_proc (gfc_symbol *sym)
2482 {
2483   if (!sym->attr.dummy && !sym->attr.contained
2484         && !(sym->attr.intrinsic
2485               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2486         && sym->attr.proc != PROC_ST_FUNCTION
2487         && !sym->attr.proc_pointer
2488         && !sym->attr.use_assoc
2489         && sym->name)
2490     return true;
2491
2492   return false;
2493 }
2494
2495
2496 /* Figure out if a function reference is pure or not.  Also set the name
2497    of the function for a potential error message.  Return nonzero if the
2498    function is PURE, zero if not.  */
2499 static int
2500 pure_stmt_function (gfc_expr *, gfc_symbol *);
2501
2502 static int
2503 pure_function (gfc_expr *e, const char **name)
2504 {
2505   int pure;
2506
2507   *name = NULL;
2508
2509   if (e->symtree != NULL
2510         && e->symtree->n.sym != NULL
2511         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2512     return pure_stmt_function (e, e->symtree->n.sym);
2513
2514   if (e->value.function.esym)
2515     {
2516       pure = gfc_pure (e->value.function.esym);
2517       *name = e->value.function.esym->name;
2518     }
2519   else if (e->value.function.isym)
2520     {
2521       pure = e->value.function.isym->pure
2522              || e->value.function.isym->elemental;
2523       *name = e->value.function.isym->name;
2524     }
2525   else
2526     {
2527       /* Implicit functions are not pure.  */
2528       pure = 0;
2529       *name = e->value.function.name;
2530     }
2531
2532   return pure;
2533 }
2534
2535
2536 static bool
2537 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2538                  int *f ATTRIBUTE_UNUSED)
2539 {
2540   const char *name;
2541
2542   /* Don't bother recursing into other statement functions
2543      since they will be checked individually for purity.  */
2544   if (e->expr_type != EXPR_FUNCTION
2545         || !e->symtree
2546         || e->symtree->n.sym == sym
2547         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2548     return false;
2549
2550   return pure_function (e, &name) ? false : true;
2551 }
2552
2553
2554 static int
2555 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2556 {
2557   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2558 }
2559
2560
2561 static gfc_try
2562 is_scalar_expr_ptr (gfc_expr *expr)
2563 {
2564   gfc_try retval = SUCCESS;
2565   gfc_ref *ref;
2566   int start;
2567   int end;
2568
2569   /* See if we have a gfc_ref, which means we have a substring, array
2570      reference, or a component.  */
2571   if (expr->ref != NULL)
2572     {
2573       ref = expr->ref;
2574       while (ref->next != NULL)
2575         ref = ref->next;
2576
2577       switch (ref->type)
2578         {
2579         case REF_SUBSTRING:
2580           if (ref->u.ss.start == NULL || ref->u.ss.end == NULL
2581               || gfc_dep_compare_expr (ref->u.ss.start, ref->u.ss.end) != 0)
2582             retval = FAILURE;
2583           break;
2584
2585         case REF_ARRAY:
2586           if (ref->u.ar.type == AR_ELEMENT)
2587             retval = SUCCESS;
2588           else if (ref->u.ar.type == AR_FULL)
2589             {
2590               /* The user can give a full array if the array is of size 1.  */
2591               if (ref->u.ar.as != NULL
2592                   && ref->u.ar.as->rank == 1
2593                   && ref->u.ar.as->type == AS_EXPLICIT
2594                   && ref->u.ar.as->lower[0] != NULL
2595                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2596                   && ref->u.ar.as->upper[0] != NULL
2597                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2598                 {
2599                   /* If we have a character string, we need to check if
2600                      its length is one.  */
2601                   if (expr->ts.type == BT_CHARACTER)
2602                     {
2603                       if (expr->ts.u.cl == NULL
2604                           || expr->ts.u.cl->length == NULL
2605                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2606                           != 0)
2607                         retval = FAILURE;
2608                     }
2609                   else
2610                     {
2611                       /* We have constant lower and upper bounds.  If the
2612                          difference between is 1, it can be considered a
2613                          scalar.  
2614                          FIXME: Use gfc_dep_compare_expr instead.  */
2615                       start = (int) mpz_get_si
2616                                 (ref->u.ar.as->lower[0]->value.integer);
2617                       end = (int) mpz_get_si
2618                                 (ref->u.ar.as->upper[0]->value.integer);
2619                       if (end - start + 1 != 1)
2620                         retval = FAILURE;
2621                    }
2622                 }
2623               else
2624                 retval = FAILURE;
2625             }
2626           else
2627             retval = FAILURE;
2628           break;
2629         default:
2630           retval = SUCCESS;
2631           break;
2632         }
2633     }
2634   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2635     {
2636       /* Character string.  Make sure it's of length 1.  */
2637       if (expr->ts.u.cl == NULL
2638           || expr->ts.u.cl->length == NULL
2639           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2640         retval = FAILURE;
2641     }
2642   else if (expr->rank != 0)
2643     retval = FAILURE;
2644
2645   return retval;
2646 }
2647
2648
2649 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2650    and, in the case of c_associated, set the binding label based on
2651    the arguments.  */
2652
2653 static gfc_try
2654 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2655                           gfc_symbol **new_sym)
2656 {
2657   char name[GFC_MAX_SYMBOL_LEN + 1];
2658   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2659   int optional_arg = 0;
2660   gfc_try retval = SUCCESS;
2661   gfc_symbol *args_sym;
2662   gfc_typespec *arg_ts;
2663   symbol_attribute arg_attr;
2664
2665   if (args->expr->expr_type == EXPR_CONSTANT
2666       || args->expr->expr_type == EXPR_OP
2667       || args->expr->expr_type == EXPR_NULL)
2668     {
2669       gfc_error ("Argument to '%s' at %L is not a variable",
2670                  sym->name, &(args->expr->where));
2671       return FAILURE;
2672     }
2673
2674   args_sym = args->expr->symtree->n.sym;
2675
2676   /* The typespec for the actual arg should be that stored in the expr
2677      and not necessarily that of the expr symbol (args_sym), because
2678      the actual expression could be a part-ref of the expr symbol.  */
2679   arg_ts = &(args->expr->ts);
2680   arg_attr = gfc_expr_attr (args->expr);
2681     
2682   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2683     {
2684       /* If the user gave two args then they are providing something for
2685          the optional arg (the second cptr).  Therefore, set the name and
2686          binding label to the c_associated for two cptrs.  Otherwise,
2687          set c_associated to expect one cptr.  */
2688       if (args->next)
2689         {
2690           /* two args.  */
2691           sprintf (name, "%s_2", sym->name);
2692           sprintf (binding_label, "%s_2", sym->binding_label);
2693           optional_arg = 1;
2694         }
2695       else
2696         {
2697           /* one arg.  */
2698           sprintf (name, "%s_1", sym->name);
2699           sprintf (binding_label, "%s_1", sym->binding_label);
2700           optional_arg = 0;
2701         }
2702
2703       /* Get a new symbol for the version of c_associated that
2704          will get called.  */
2705       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2706     }
2707   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2708            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2709     {
2710       sprintf (name, "%s", sym->name);
2711       sprintf (binding_label, "%s", sym->binding_label);
2712
2713       /* Error check the call.  */
2714       if (args->next != NULL)
2715         {
2716           gfc_error_now ("More actual than formal arguments in '%s' "
2717                          "call at %L", name, &(args->expr->where));
2718           retval = FAILURE;
2719         }
2720       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2721         {
2722           gfc_ref *ref;
2723           bool seen_section;
2724
2725           /* Make sure we have either the target or pointer attribute.  */
2726           if (!arg_attr.target && !arg_attr.pointer)
2727             {
2728               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2729                              "a TARGET or an associated pointer",
2730                              args_sym->name,
2731                              sym->name, &(args->expr->where));
2732               retval = FAILURE;
2733             }
2734
2735           if (gfc_is_coindexed (args->expr))
2736             {
2737               gfc_error_now ("Coindexed argument not permitted"
2738                              " in '%s' call at %L", name,
2739                              &(args->expr->where));
2740               retval = FAILURE;
2741             }
2742
2743           /* Follow references to make sure there are no array
2744              sections.  */
2745           seen_section = false;
2746
2747           for (ref=args->expr->ref; ref; ref = ref->next)
2748             {
2749               if (ref->type == REF_ARRAY)
2750                 {
2751                   if (ref->u.ar.type == AR_SECTION)
2752                     seen_section = true;
2753
2754                   if (ref->u.ar.type != AR_ELEMENT)
2755                     {
2756                       gfc_ref *r;
2757                       for (r = ref->next; r; r=r->next)
2758                         if (r->type == REF_COMPONENT)
2759                           {
2760                             gfc_error_now ("Array section not permitted"
2761                                            " in '%s' call at %L", name,
2762                                            &(args->expr->where));
2763                             retval = FAILURE;
2764                             break;
2765                           }
2766                     }
2767                 }
2768             }
2769
2770           if (seen_section && retval == SUCCESS)
2771             gfc_warning ("Array section in '%s' call at %L", name,
2772                          &(args->expr->where));
2773                          
2774           /* See if we have interoperable type and type param.  */
2775           if (verify_c_interop (arg_ts) == SUCCESS
2776               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2777             {
2778               if (args_sym->attr.target == 1)
2779                 {
2780                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2781                      has the target attribute and is interoperable.  */
2782                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2783                      allocatable variable that has the TARGET attribute and
2784                      is not an array of zero size.  */
2785                   if (args_sym->attr.allocatable == 1)
2786                     {
2787                       if (args_sym->attr.dimension != 0 
2788                           && (args_sym->as && args_sym->as->rank == 0))
2789                         {
2790                           gfc_error_now ("Allocatable variable '%s' used as a "
2791                                          "parameter to '%s' at %L must not be "
2792                                          "an array of zero size",
2793                                          args_sym->name, sym->name,
2794                                          &(args->expr->where));
2795                           retval = FAILURE;
2796                         }
2797                     }
2798                   else
2799                     {
2800                       /* A non-allocatable target variable with C
2801                          interoperable type and type parameters must be
2802                          interoperable.  */
2803                       if (args_sym && args_sym->attr.dimension)
2804                         {
2805                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2806                             {
2807                               gfc_error ("Assumed-shape array '%s' at %L "
2808                                          "cannot be an argument to the "
2809                                          "procedure '%s' because "
2810                                          "it is not C interoperable",
2811                                          args_sym->name,
2812                                          &(args->expr->where), sym->name);
2813                               retval = FAILURE;
2814                             }
2815                           else if (args_sym->as->type == AS_DEFERRED)
2816                             {
2817                               gfc_error ("Deferred-shape array '%s' at %L "
2818                                          "cannot be an argument to the "
2819                                          "procedure '%s' because "
2820                                          "it is not C interoperable",
2821                                          args_sym->name,
2822                                          &(args->expr->where), sym->name);
2823                               retval = FAILURE;
2824                             }
2825                         }
2826                               
2827                       /* Make sure it's not a character string.  Arrays of
2828                          any type should be ok if the variable is of a C
2829                          interoperable type.  */
2830                       if (arg_ts->type == BT_CHARACTER)
2831                         if (arg_ts->u.cl != NULL
2832                             && (arg_ts->u.cl->length == NULL
2833                                 || arg_ts->u.cl->length->expr_type
2834                                    != EXPR_CONSTANT
2835                                 || mpz_cmp_si
2836                                     (arg_ts->u.cl->length->value.integer, 1)
2837                                    != 0)
2838                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2839                           {
2840                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2841                                            "at %L must have a length of 1",
2842                                            args_sym->name, sym->name,
2843                                            &(args->expr->where));
2844                             retval = FAILURE;
2845                           }
2846                     }
2847                 }
2848               else if (arg_attr.pointer
2849                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2850                 {
2851                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2852                      scalar pointer.  */
2853                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2854                                  "associated scalar POINTER", args_sym->name,
2855                                  sym->name, &(args->expr->where));
2856                   retval = FAILURE;
2857                 }
2858             }
2859           else
2860             {
2861               /* The parameter is not required to be C interoperable.  If it
2862                  is not C interoperable, it must be a nonpolymorphic scalar
2863                  with no length type parameters.  It still must have either
2864                  the pointer or target attribute, and it can be
2865                  allocatable (but must be allocated when c_loc is called).  */
2866               if (args->expr->rank != 0 
2867                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2868                 {
2869                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2870                                  "scalar", args_sym->name, sym->name,
2871                                  &(args->expr->where));
2872                   retval = FAILURE;
2873                 }
2874               else if (arg_ts->type == BT_CHARACTER 
2875                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2876                 {
2877                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2878                                  "%L must have a length of 1",
2879                                  args_sym->name, sym->name,
2880                                  &(args->expr->where));
2881                   retval = FAILURE;
2882                 }
2883               else if (arg_ts->type == BT_CLASS)
2884                 {
2885                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
2886                                  "polymorphic", args_sym->name, sym->name,
2887                                  &(args->expr->where));
2888                   retval = FAILURE;
2889                 }
2890             }
2891         }
2892       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2893         {
2894           if (args_sym->attr.flavor != FL_PROCEDURE)
2895             {
2896               /* TODO: Update this error message to allow for procedure
2897                  pointers once they are implemented.  */
2898               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2899                              "procedure",
2900                              args_sym->name, sym->name,
2901                              &(args->expr->where));
2902               retval = FAILURE;
2903             }
2904           else if (args_sym->attr.is_bind_c != 1)
2905             {
2906               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2907                              "BIND(C)",
2908                              args_sym->name, sym->name,
2909                              &(args->expr->where));
2910               retval = FAILURE;
2911             }
2912         }
2913       
2914       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2915       *new_sym = sym;
2916     }
2917   else
2918     {
2919       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2920                           "iso_c_binding function: '%s'!\n", sym->name);
2921     }
2922
2923   return retval;
2924 }
2925
2926
2927 /* Resolve a function call, which means resolving the arguments, then figuring
2928    out which entity the name refers to.  */
2929
2930 static gfc_try
2931 resolve_function (gfc_expr *expr)
2932 {
2933   gfc_actual_arglist *arg;
2934   gfc_symbol *sym;
2935   const char *name;
2936   gfc_try t;
2937   int temp;
2938   procedure_type p = PROC_INTRINSIC;
2939   bool no_formal_args;
2940
2941   sym = NULL;
2942   if (expr->symtree)
2943     sym = expr->symtree->n.sym;
2944
2945   /* If this is a procedure pointer component, it has already been resolved.  */
2946   if (gfc_is_proc_ptr_comp (expr, NULL))
2947     return SUCCESS;
2948   
2949   if (sym && sym->attr.intrinsic
2950       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2951     return FAILURE;
2952
2953   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2954     {
2955       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2956       return FAILURE;
2957     }
2958
2959   /* If this ia a deferred TBP with an abstract interface (which may
2960      of course be referenced), expr->value.function.esym will be set.  */
2961   if (sym && sym->attr.abstract && !expr->value.function.esym)
2962     {
2963       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2964                  sym->name, &expr->where);
2965       return FAILURE;
2966     }
2967
2968   /* Switch off assumed size checking and do this again for certain kinds
2969      of procedure, once the procedure itself is resolved.  */
2970   need_full_assumed_size++;
2971
2972   if (expr->symtree && expr->symtree->n.sym)
2973     p = expr->symtree->n.sym->attr.proc;
2974
2975   if (expr->value.function.isym && expr->value.function.isym->inquiry)
2976     inquiry_argument = true;
2977   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2978
2979   if (resolve_actual_arglist (expr->value.function.actual,
2980                               p, no_formal_args) == FAILURE)
2981     {
2982       inquiry_argument = false;
2983       return FAILURE;
2984     }
2985
2986   inquiry_argument = false;
2987  
2988   /* Need to setup the call to the correct c_associated, depending on
2989      the number of cptrs to user gives to compare.  */
2990   if (sym && sym->attr.is_iso_c == 1)
2991     {
2992       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2993           == FAILURE)
2994         return FAILURE;
2995       
2996       /* Get the symtree for the new symbol (resolved func).
2997          the old one will be freed later, when it's no longer used.  */
2998       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2999     }
3000   
3001   /* Resume assumed_size checking.  */
3002   need_full_assumed_size--;
3003
3004   /* If the procedure is external, check for usage.  */
3005   if (sym && is_external_proc (sym))
3006     resolve_global_procedure (sym, &expr->where,
3007                               &expr->value.function.actual, 0);
3008
3009   if (sym && sym->ts.type == BT_CHARACTER
3010       && sym->ts.u.cl
3011       && sym->ts.u.cl->length == NULL
3012       && !sym->attr.dummy
3013       && !sym->ts.deferred
3014       && expr->value.function.esym == NULL
3015       && !sym->attr.contained)
3016     {
3017       /* Internal procedures are taken care of in resolve_contained_fntype.  */
3018       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
3019                  "be used at %L since it is not a dummy argument",
3020                  sym->name, &expr->where);
3021       return FAILURE;
3022     }
3023
3024   /* See if function is already resolved.  */
3025
3026   if (expr->value.function.name != NULL)
3027     {
3028       if (expr->ts.type == BT_UNKNOWN)
3029         expr->ts = sym->ts;
3030       t = SUCCESS;
3031     }
3032   else
3033     {
3034       /* Apply the rules of section 14.1.2.  */
3035
3036       switch (procedure_kind (sym))
3037         {
3038         case PTYPE_GENERIC:
3039           t = resolve_generic_f (expr);
3040           break;
3041
3042         case PTYPE_SPECIFIC:
3043           t = resolve_specific_f (expr);
3044           break;
3045
3046         case PTYPE_UNKNOWN:
3047           t = resolve_unknown_f (expr);
3048           break;
3049
3050         default:
3051           gfc_internal_error ("resolve_function(): bad function type");
3052         }
3053     }
3054
3055   /* If the expression is still a function (it might have simplified),
3056      then we check to see if we are calling an elemental function.  */
3057
3058   if (expr->expr_type != EXPR_FUNCTION)
3059     return t;
3060
3061   temp = need_full_assumed_size;
3062   need_full_assumed_size = 0;
3063
3064   if (resolve_elemental_actual (expr, NULL) == FAILURE)
3065     return FAILURE;
3066
3067   if (omp_workshare_flag
3068       && expr->value.function.esym
3069       && ! gfc_elemental (expr->value.function.esym))
3070     {
3071       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
3072                  "in WORKSHARE construct", expr->value.function.esym->name,
3073                  &expr->where);
3074       t = FAILURE;
3075     }
3076
3077 #define GENERIC_ID expr->value.function.isym->id
3078   else if (expr->value.function.actual != NULL
3079            && expr->value.function.isym != NULL
3080            && GENERIC_ID != GFC_ISYM_LBOUND
3081            && GENERIC_ID != GFC_ISYM_LEN
3082            && GENERIC_ID != GFC_ISYM_LOC
3083            && GENERIC_ID != GFC_ISYM_PRESENT)
3084     {
3085       /* Array intrinsics must also have the last upper bound of an
3086          assumed size array argument.  UBOUND and SIZE have to be
3087          excluded from the check if the second argument is anything
3088          than a constant.  */
3089
3090       for (arg = expr->value.function.actual; arg; arg = arg->next)
3091         {
3092           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3093               && arg->next != NULL && arg->next->expr)
3094             {
3095               if (arg->next->expr->expr_type != EXPR_CONSTANT)
3096                 break;
3097
3098               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
3099                 break;
3100
3101               if ((int)mpz_get_si (arg->next->expr->value.integer)
3102                         < arg->expr->rank)
3103                 break;
3104             }
3105
3106           if (arg->expr != NULL
3107               && arg->expr->rank > 0
3108               && resolve_assumed_size_actual (arg->expr))
3109             return FAILURE;
3110         }
3111     }
3112 #undef GENERIC_ID
3113
3114   need_full_assumed_size = temp;
3115   name = NULL;
3116
3117   if (!pure_function (expr, &name) && name)
3118     {
3119       if (forall_flag)
3120         {
3121           gfc_error ("reference to non-PURE function '%s' at %L inside a "
3122                      "FORALL %s", name, &expr->where,
3123                      forall_flag == 2 ? "mask" : "block");
3124           t = FAILURE;
3125         }
3126       else if (gfc_pure (NULL))
3127         {
3128           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
3129                      "procedure within a PURE procedure", name, &expr->where);
3130           t = FAILURE;
3131         }
3132     }
3133
3134   if (!pure_function (expr, &name) && name && gfc_implicit_pure (NULL))
3135     gfc_current_ns->proc_name->attr.implicit_pure = 0;
3136
3137   /* Functions without the RECURSIVE attribution are not allowed to
3138    * call themselves.  */
3139   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3140     {
3141       gfc_symbol *esym;
3142       esym = expr->value.function.esym;
3143
3144       if (is_illegal_recursion (esym, gfc_current_ns))
3145       {
3146         if (esym->attr.entry && esym->ns->entries)
3147           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3148                      " function '%s' is not RECURSIVE",
3149                      esym->name, &expr->where, esym->ns->entries->sym->name);
3150         else
3151           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
3152                      " is not RECURSIVE", esym->name, &expr->where);
3153
3154         t = FAILURE;
3155       }
3156     }
3157
3158   /* Character lengths of use associated functions may contains references to
3159      symbols not referenced from the current program unit otherwise.  Make sure
3160      those symbols are marked as referenced.  */
3161
3162   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3163       && expr->value.function.esym->attr.use_assoc)
3164     {
3165       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3166     }
3167
3168   /* Make sure that the expression has a typespec that works.  */
3169   if (expr->ts.type == BT_UNKNOWN)
3170     {
3171       if (expr->symtree->n.sym->result
3172             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3173             && !expr->symtree->n.sym->result->attr.proc_pointer)
3174         expr->ts = expr->symtree->n.sym->result->ts;
3175     }
3176
3177   return t;
3178 }
3179
3180
3181 /************* Subroutine resolution *************/
3182
3183 static void
3184 pure_subroutine (gfc_code *c, gfc_symbol *sym)
3185 {
3186   if (gfc_pure (sym))
3187     return;
3188
3189   if (forall_flag)
3190     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
3191                sym->name, &c->loc);
3192   else if (gfc_pure (NULL))
3193     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
3194                &c->loc);
3195 }
3196
3197
3198 static match
3199 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3200 {
3201   gfc_symbol *s;
3202
3203   if (sym->attr.generic)
3204     {
3205       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3206       if (s != NULL)
3207         {
3208           c->resolved_sym = s;
3209           pure_subroutine (c, s);
3210           return MATCH_YES;
3211         }
3212
3213       /* TODO: Need to search for elemental references in generic interface.  */
3214     }
3215
3216   if (sym->attr.intrinsic)
3217     return gfc_intrinsic_sub_interface (c, 0);
3218
3219   return MATCH_NO;
3220 }
3221
3222
3223 static gfc_try
3224 resolve_generic_s (gfc_code *c)
3225 {
3226   gfc_symbol *sym;
3227   match m;
3228
3229   sym = c->symtree->n.sym;
3230
3231   for (;;)
3232     {
3233       m = resolve_generic_s0 (c, sym);
3234       if (m == MATCH_YES)
3235         return SUCCESS;
3236       else if (m == MATCH_ERROR)
3237         return FAILURE;
3238
3239 generic:
3240       if (sym->ns->parent == NULL)
3241         break;
3242       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3243
3244       if (sym == NULL)
3245         break;
3246       if (!generic_sym (sym))
3247         goto generic;
3248     }
3249
3250   /* Last ditch attempt.  See if the reference is to an intrinsic
3251      that possesses a matching interface.  14.1.2.4  */
3252   sym = c->symtree->n.sym;
3253
3254   if (!gfc_is_intrinsic (sym, 1, c->loc))
3255     {
3256       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3257                  sym->name, &c->loc);
3258       return FAILURE;
3259     }
3260
3261   m = gfc_intrinsic_sub_interface (c, 0);
3262   if (m == MATCH_YES)
3263     return SUCCESS;
3264   if (m == MATCH_NO)
3265     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3266                "intrinsic subroutine interface", sym->name, &c->loc);
3267
3268   return FAILURE;
3269 }
3270
3271
3272 /* Set the name and binding label of the subroutine symbol in the call
3273    expression represented by 'c' to include the type and kind of the
3274    second parameter.  This function is for resolving the appropriate
3275    version of c_f_pointer() and c_f_procpointer().  For example, a
3276    call to c_f_pointer() for a default integer pointer could have a
3277    name of c_f_pointer_i4.  If no second arg exists, which is an error
3278    for these two functions, it defaults to the generic symbol's name
3279    and binding label.  */
3280
3281 static void
3282 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3283                     char *name, char *binding_label)
3284 {
3285   gfc_expr *arg = NULL;
3286   char type;
3287   int kind;
3288
3289   /* The second arg of c_f_pointer and c_f_procpointer determines
3290      the type and kind for the procedure name.  */
3291   arg = c->ext.actual->next->expr;
3292
3293   if (arg != NULL)
3294     {
3295       /* Set up the name to have the given symbol's name,
3296          plus the type and kind.  */
3297       /* a derived type is marked with the type letter 'u' */
3298       if (arg->ts.type == BT_DERIVED)
3299         {
3300           type = 'd';
3301           kind = 0; /* set the kind as 0 for now */
3302         }
3303       else
3304         {
3305           type = gfc_type_letter (arg->ts.type);
3306           kind = arg->ts.kind;
3307         }
3308
3309       if (arg->ts.type == BT_CHARACTER)
3310         /* Kind info for character strings not needed.  */
3311         kind = 0;
3312
3313       sprintf (name, "%s_%c%d", sym->name, type, kind);
3314       /* Set up the binding label as the given symbol's label plus
3315          the type and kind.  */
3316       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
3317     }
3318   else
3319     {
3320       /* If the second arg is missing, set the name and label as
3321          was, cause it should at least be found, and the missing
3322          arg error will be caught by compare_parameters().  */
3323       sprintf (name, "%s", sym->name);
3324       sprintf (binding_label, "%s", sym->binding_label);
3325     }
3326    
3327   return;
3328 }
3329
3330
3331 /* Resolve a generic version of the iso_c_binding procedure given
3332    (sym) to the specific one based on the type and kind of the
3333    argument(s).  Currently, this function resolves c_f_pointer() and
3334    c_f_procpointer based on the type and kind of the second argument
3335    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3336    Upon successfully exiting, c->resolved_sym will hold the resolved
3337    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3338    otherwise.  */
3339
3340 match
3341 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3342 {
3343   gfc_symbol *new_sym;
3344   /* this is fine, since we know the names won't use the max */
3345   char name[GFC_MAX_SYMBOL_LEN + 1];
3346   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3347   /* default to success; will override if find error */
3348   match m = MATCH_YES;
3349
3350   /* Make sure the actual arguments are in the necessary order (based on the 
3351      formal args) before resolving.  */
3352   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3353
3354   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3355       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3356     {
3357       set_name_and_label (c, sym, name, binding_label);
3358       
3359       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3360         {
3361           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3362             {
3363               /* Make sure we got a third arg if the second arg has non-zero
3364                  rank.  We must also check that the type and rank are
3365                  correct since we short-circuit this check in
3366                  gfc_procedure_use() (called above to sort actual args).  */
3367               if (c->ext.actual->next->expr->rank != 0)
3368                 {
3369                   if(c->ext.actual->next->next == NULL 
3370                      || c->ext.actual->next->next->expr == NULL)
3371                     {
3372                       m = MATCH_ERROR;
3373                       gfc_error ("Missing SHAPE parameter for call to %s "
3374                                  "at %L", sym->name, &(c->loc));
3375                     }
3376                   else if (c->ext.actual->next->next->expr->ts.type
3377                            != BT_INTEGER
3378                            || c->ext.actual->next->next->expr->rank != 1)
3379                     {
3380                       m = MATCH_ERROR;
3381                       gfc_error ("SHAPE parameter for call to %s at %L must "
3382                                  "be a rank 1 INTEGER array", sym->name,
3383                                  &(c->loc));
3384                     }
3385                 }
3386             }
3387         }
3388       
3389       if (m != MATCH_ERROR)
3390         {
3391           /* the 1 means to add the optional arg to formal list */
3392           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3393          
3394           /* for error reporting, say it's declared where the original was */
3395           new_sym->declared_at = sym->declared_at;
3396         }
3397     }
3398   else
3399     {
3400       /* no differences for c_loc or c_funloc */
3401       new_sym = sym;
3402     }
3403
3404   /* set the resolved symbol */
3405   if (m != MATCH_ERROR)
3406     c->resolved_sym = new_sym;
3407   else
3408     c->resolved_sym = sym;
3409   
3410   return m;
3411 }
3412
3413
3414 /* Resolve a subroutine call known to be specific.  */
3415
3416 static match
3417 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3418 {
3419   match m;
3420
3421   if(sym->attr.is_iso_c)
3422     {
3423       m = gfc_iso_c_sub_interface (c,sym);
3424       return m;
3425     }
3426   
3427   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3428     {
3429       if (sym->attr.dummy)
3430         {
3431           sym->attr.proc = PROC_DUMMY;
3432           goto found;
3433         }
3434
3435       sym->attr.proc = PROC_EXTERNAL;
3436       goto found;
3437     }
3438
3439   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3440     goto found;
3441
3442   if (sym->attr.intrinsic)
3443     {
3444       m = gfc_intrinsic_sub_interface (c, 1);
3445       if (m == MATCH_YES)
3446         return MATCH_YES;
3447       if (m == MATCH_NO)
3448         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3449                    "with an intrinsic", sym->name, &c->loc);
3450
3451       return MATCH_ERROR;
3452     }
3453
3454   return MATCH_NO;
3455
3456 found:
3457   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3458
3459   c->resolved_sym = sym;
3460   pure_subroutine (c, sym);
3461
3462   return MATCH_YES;
3463 }
3464
3465
3466 static gfc_try
3467 resolve_specific_s (gfc_code *c)
3468 {
3469   gfc_symbol *sym;
3470   match m;
3471
3472   sym = c->symtree->n.sym;
3473
3474   for (;;)
3475     {
3476       m = resolve_specific_s0 (c, sym);
3477       if (m == MATCH_YES)
3478         return SUCCESS;
3479       if (m == MATCH_ERROR)
3480         return FAILURE;
3481
3482       if (sym->ns->parent == NULL)
3483         break;
3484
3485       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3486
3487       if (sym == NULL)
3488         break;
3489     }
3490
3491   sym = c->symtree->n.sym;
3492   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3493              sym->name, &c->loc);
3494
3495   return FAILURE;
3496 }
3497
3498
3499 /* Resolve a subroutine call not known to be generic nor specific.  */
3500
3501 static gfc_try
3502 resolve_unknown_s (gfc_code *c)
3503 {
3504   gfc_symbol *sym;
3505
3506   sym = c->symtree->n.sym;
3507
3508   if (sym->attr.dummy)
3509     {
3510       sym->attr.proc = PROC_DUMMY;
3511       goto found;
3512     }
3513
3514   /* See if we have an intrinsic function reference.  */
3515
3516   if (gfc_is_intrinsic (sym, 1, c->loc))
3517     {
3518       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3519         return SUCCESS;
3520       return FAILURE;
3521     }
3522
3523   /* The reference is to an external name.  */
3524
3525 found:
3526   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3527
3528   c->resolved_sym = sym;
3529
3530   pure_subroutine (c, sym);
3531
3532   return SUCCESS;
3533 }
3534
3535
3536 /* Resolve a subroutine call.  Although it was tempting to use the same code
3537    for functions, subroutines and functions are stored differently and this
3538    makes things awkward.  */
3539
3540 static gfc_try
3541 resolve_call (gfc_code *c)
3542 {
3543   gfc_try t;
3544   procedure_type ptype = PROC_INTRINSIC;
3545   gfc_symbol *csym, *sym;
3546   bool no_formal_args;
3547
3548   csym = c->symtree ? c->symtree->n.sym : NULL;
3549
3550   if (csym && csym->ts.type != BT_UNKNOWN)
3551     {
3552       gfc_error ("'%s' at %L has a type, which is not consistent with "
3553                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3554       return FAILURE;
3555     }
3556
3557   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3558     {
3559       gfc_symtree *st;
3560       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3561       sym = st ? st->n.sym : NULL;
3562       if (sym && csym != sym
3563               && sym->ns == gfc_current_ns
3564               && sym->attr.flavor == FL_PROCEDURE
3565               && sym->attr.contained)
3566         {
3567           sym->refs++;
3568           if (csym->attr.generic)
3569             c->symtree->n.sym = sym;
3570           else
3571             c->symtree = st;
3572           csym = c->symtree->n.sym;
3573         }
3574     }
3575
3576   /* If this ia a deferred TBP with an abstract interface
3577      (which may of course be referenced), c->expr1 will be set.  */
3578   if (csym && csym->attr.abstract && !c->expr1)
3579     {
3580       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3581                  csym->name, &c->loc);
3582       return FAILURE;
3583     }
3584
3585   /* Subroutines without the RECURSIVE attribution are not allowed to
3586    * call themselves.  */
3587   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3588     {
3589       if (csym->attr.entry && csym->ns->entries)
3590         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3591                    " subroutine '%s' is not RECURSIVE",
3592                    csym->name, &c->loc, csym->ns->entries->sym->name);
3593       else
3594         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3595                    " is not RECURSIVE", csym->name, &c->loc);
3596
3597       t = FAILURE;
3598     }
3599
3600   /* Switch off assumed size checking and do this again for certain kinds
3601      of procedure, once the procedure itself is resolved.  */
3602   need_full_assumed_size++;
3603
3604   if (csym)
3605     ptype = csym->attr.proc;
3606
3607   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3608   if (resolve_actual_arglist (c->ext.actual, ptype,
3609                               no_formal_args) == FAILURE)
3610     return FAILURE;
3611
3612   /* Resume assumed_size checking.  */
3613   need_full_assumed_size--;
3614
3615   /* If external, check for usage.  */
3616   if (csym && is_external_proc (csym))
3617     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3618
3619   t = SUCCESS;
3620   if (c->resolved_sym == NULL)
3621     {
3622       c->resolved_isym = NULL;
3623       switch (procedure_kind (csym))
3624         {
3625         case PTYPE_GENERIC:
3626           t = resolve_generic_s (c);
3627           break;
3628
3629         case PTYPE_SPECIFIC:
3630           t = resolve_specific_s (c);
3631           break;
3632
3633         case PTYPE_UNKNOWN:
3634           t = resolve_unknown_s (c);
3635           break;
3636
3637         default:
3638           gfc_internal_error ("resolve_subroutine(): bad function type");
3639         }
3640     }
3641
3642   /* Some checks of elemental subroutine actual arguments.  */
3643   if (resolve_elemental_actual (NULL, c) == FAILURE)
3644     return FAILURE;
3645
3646   return t;
3647 }
3648
3649
3650 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3651    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3652    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3653    if their shapes do not match.  If either op1->shape or op2->shape is
3654    NULL, return SUCCESS.  */
3655
3656 static gfc_try
3657 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3658 {
3659   gfc_try t;
3660   int i;
3661
3662   t = SUCCESS;
3663
3664   if (op1->shape != NULL && op2->shape != NULL)
3665     {
3666       for (i = 0; i < op1->rank; i++)
3667         {
3668           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3669            {
3670              gfc_error ("Shapes for operands at %L and %L are not conformable",
3671                          &op1->where, &op2->where);
3672              t = FAILURE;
3673              break;
3674            }
3675         }
3676     }
3677
3678   return t;
3679 }
3680
3681
3682 /* Resolve an operator expression node.  This can involve replacing the
3683    operation with a user defined function call.  */
3684
3685 static gfc_try
3686 resolve_operator (gfc_expr *e)
3687 {
3688   gfc_expr *op1, *op2;
3689   char msg[200];
3690   bool dual_locus_error;
3691   gfc_try t;
3692
3693   /* Resolve all subnodes-- give them types.  */
3694
3695   switch (e->value.op.op)
3696     {
3697     default:
3698       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3699         return FAILURE;
3700
3701     /* Fall through...  */
3702
3703     case INTRINSIC_NOT:
3704     case INTRINSIC_UPLUS:
3705     case INTRINSIC_UMINUS:
3706     case INTRINSIC_PARENTHESES:
3707       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3708         return FAILURE;
3709       break;
3710     }
3711
3712   /* Typecheck the new node.  */
3713
3714   op1 = e->value.op.op1;
3715   op2 = e->value.op.op2;
3716   dual_locus_error = false;
3717
3718   if ((op1 && op1->expr_type == EXPR_NULL)
3719       || (op2 && op2->expr_type == EXPR_NULL))
3720     {
3721       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3722       goto bad_op;
3723     }
3724
3725   switch (e->value.op.op)
3726     {
3727     case INTRINSIC_UPLUS:
3728     case INTRINSIC_UMINUS:
3729       if (op1->ts.type == BT_INTEGER
3730           || op1->ts.type == BT_REAL
3731           || op1->ts.type == BT_COMPLEX)
3732         {
3733           e->ts = op1->ts;
3734           break;
3735         }
3736
3737       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3738                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3739       goto bad_op;
3740
3741     case INTRINSIC_PLUS:
3742     case INTRINSIC_MINUS:
3743     case INTRINSIC_TIMES:
3744     case INTRINSIC_DIVIDE:
3745     case INTRINSIC_POWER:
3746       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3747         {
3748           gfc_type_convert_binary (e, 1);
3749           break;
3750         }
3751
3752       sprintf (msg,
3753                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3754                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3755                gfc_typename (&op2->ts));
3756       goto bad_op;
3757
3758     case INTRINSIC_CONCAT:
3759       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3760           && op1->ts.kind == op2->ts.kind)
3761         {
3762           e->ts.type = BT_CHARACTER;
3763           e->ts.kind = op1->ts.kind;
3764           break;
3765         }
3766
3767       sprintf (msg,
3768                _("Operands of string concatenation operator at %%L are %s/%s"),
3769                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3770       goto bad_op;
3771
3772     case INTRINSIC_AND:
3773     case INTRINSIC_OR:
3774     case INTRINSIC_EQV:
3775     case INTRINSIC_NEQV:
3776       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3777         {
3778           e->ts.type = BT_LOGICAL;
3779           e->ts.kind = gfc_kind_max (op1, op2);
3780           if (op1->ts.kind < e->ts.kind)
3781             gfc_convert_type (op1, &e->ts, 2);
3782           else if (op2->ts.kind < e->ts.kind)
3783             gfc_convert_type (op2, &e->ts, 2);
3784           break;
3785         }
3786
3787       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3788                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3789                gfc_typename (&op2->ts));
3790
3791       goto bad_op;
3792
3793     case INTRINSIC_NOT:
3794       if (op1->ts.type == BT_LOGICAL)
3795         {
3796           e->ts.type = BT_LOGICAL;
3797           e->ts.kind = op1->ts.kind;
3798           break;
3799         }
3800
3801       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3802                gfc_typename (&op1->ts));
3803       goto bad_op;
3804
3805     case INTRINSIC_GT:
3806     case INTRINSIC_GT_OS:
3807     case INTRINSIC_GE:
3808     case INTRINSIC_GE_OS:
3809     case INTRINSIC_LT:
3810     case INTRINSIC_LT_OS:
3811     case INTRINSIC_LE:
3812     case INTRINSIC_LE_OS:
3813       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3814         {
3815           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3816           goto bad_op;
3817         }
3818
3819       /* Fall through...  */
3820
3821     case INTRINSIC_EQ:
3822     case INTRINSIC_EQ_OS:
3823     case INTRINSIC_NE:
3824     case INTRINSIC_NE_OS:
3825       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3826           && op1->ts.kind == op2->ts.kind)
3827         {
3828           e->ts.type = BT_LOGICAL;
3829           e->ts.kind = gfc_default_logical_kind;
3830           break;
3831         }
3832
3833       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3834         {
3835           gfc_type_convert_binary (e, 1);
3836
3837           e->ts.type = BT_LOGICAL;
3838           e->ts.kind = gfc_default_logical_kind;
3839           break;
3840         }
3841
3842       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3843         sprintf (msg,
3844                  _("Logicals at %%L must be compared with %s instead of %s"),
3845                  (e->value.op.op == INTRINSIC_EQ 
3846                   || e->value.op.op == INTRINSIC_EQ_OS)
3847                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3848       else
3849         sprintf (msg,
3850                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3851                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3852                  gfc_typename (&op2->ts));
3853
3854       goto bad_op;
3855
3856     case INTRINSIC_USER:
3857       if (e->value.op.uop->op == NULL)
3858         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3859       else if (op2 == NULL)
3860         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3861                  e->value.op.uop->name, gfc_typename (&op1->ts));
3862       else
3863         {
3864           sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3865                    e->value.op.uop->name, gfc_typename (&op1->ts),
3866                    gfc_typename (&op2->ts));
3867           e->value.op.uop->op->sym->attr.referenced = 1;
3868         }
3869
3870       goto bad_op;
3871
3872     case INTRINSIC_PARENTHESES:
3873       e->ts = op1->ts;
3874       if (e->ts.type == BT_CHARACTER)
3875         e->ts.u.cl = op1->ts.u.cl;
3876       break;
3877
3878     default:
3879       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3880     }
3881
3882   /* Deal with arrayness of an operand through an operator.  */
3883
3884   t = SUCCESS;
3885
3886   switch (e->value.op.op)
3887     {
3888     case INTRINSIC_PLUS:
3889     case INTRINSIC_MINUS:
3890     case INTRINSIC_TIMES:
3891     case INTRINSIC_DIVIDE:
3892     case INTRINSIC_POWER:
3893     case INTRINSIC_CONCAT:
3894     case INTRINSIC_AND:
3895     case INTRINSIC_OR:
3896     case INTRINSIC_EQV:
3897     case INTRINSIC_NEQV:
3898     case INTRINSIC_EQ:
3899     case INTRINSIC_EQ_OS:
3900     case INTRINSIC_NE:
3901     case INTRINSIC_NE_OS:
3902     case INTRINSIC_GT:
3903     case INTRINSIC_GT_OS:
3904     case INTRINSIC_GE:
3905     case INTRINSIC_GE_OS:
3906     case INTRINSIC_LT:
3907     case INTRINSIC_LT_OS:
3908     case INTRINSIC_LE:
3909     case INTRINSIC_LE_OS:
3910
3911       if (op1->rank == 0 && op2->rank == 0)
3912         e->rank = 0;
3913
3914       if (op1->rank == 0 && op2->rank != 0)
3915         {
3916           e->rank = op2->rank;
3917
3918           if (e->shape == NULL)
3919             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3920         }
3921
3922       if (op1->rank != 0 && op2->rank == 0)
3923         {
3924           e->rank = op1->rank;
3925
3926           if (e->shape == NULL)
3927             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3928         }
3929
3930       if (op1->rank != 0 && op2->rank != 0)
3931         {
3932           if (op1->rank == op2->rank)
3933             {
3934               e->rank = op1->rank;
3935               if (e->shape == NULL)
3936                 {
3937                   t = compare_shapes (op1, op2);
3938                   if (t == FAILURE)
3939                     e->shape = NULL;
3940                   else
3941                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
3942                 }
3943             }
3944           else
3945             {
3946               /* Allow higher level expressions to work.  */
3947               e->rank = 0;
3948
3949               /* Try user-defined operators, and otherwise throw an error.  */
3950               dual_locus_error = true;
3951               sprintf (msg,
3952                        _("Inconsistent ranks for operator at %%L and %%L"));
3953               goto bad_op;
3954             }
3955         }
3956
3957       break;
3958
3959     case INTRINSIC_PARENTHESES:
3960     case INTRINSIC_NOT:
3961     case INTRINSIC_UPLUS:
3962     case INTRINSIC_UMINUS:
3963       /* Simply copy arrayness attribute */
3964       e->rank = op1->rank;
3965
3966       if (e->shape == NULL)
3967         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3968
3969       break;
3970
3971     default:
3972       break;
3973     }
3974
3975   /* Attempt to simplify the expression.  */
3976   if (t == SUCCESS)
3977     {
3978       t = gfc_simplify_expr (e, 0);
3979       /* Some calls do not succeed in simplification and return FAILURE
3980          even though there is no error; e.g. variable references to
3981          PARAMETER arrays.  */
3982       if (!gfc_is_constant_expr (e))
3983         t = SUCCESS;
3984     }
3985   return t;
3986
3987 bad_op:
3988
3989   {
3990     bool real_error;
3991     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3992       return SUCCESS;
3993
3994     if (real_error)
3995       return FAILURE;
3996   }
3997
3998   if (dual_locus_error)
3999     gfc_error (msg, &op1->where, &op2->where);
4000   else
4001     gfc_error (msg, &e->where);
4002
4003   return FAILURE;
4004 }
4005
4006
4007 /************** Array resolution subroutines **************/
4008
4009 typedef enum
4010 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
4011 comparison;
4012
4013 /* Compare two integer expressions.  */
4014
4015 static comparison
4016 compare_bound (gfc_expr *a, gfc_expr *b)
4017 {
4018   int i;
4019
4020   if (a == NULL || a->expr_type != EXPR_CONSTANT
4021       || b == NULL || b->expr_type != EXPR_CONSTANT)
4022     return CMP_UNKNOWN;
4023
4024   /* If either of the types isn't INTEGER, we must have
4025      raised an error earlier.  */
4026
4027   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
4028     return CMP_UNKNOWN;
4029
4030   i = mpz_cmp (a->value.integer, b->value.integer);
4031
4032   if (i < 0)
4033     return CMP_LT;
4034   if (i > 0)
4035     return CMP_GT;
4036   return CMP_EQ;
4037 }
4038
4039
4040 /* Compare an integer expression with an integer.  */
4041
4042 static comparison
4043 compare_bound_int (gfc_expr *a, int b)
4044 {
4045   int i;
4046
4047   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4048     return CMP_UNKNOWN;
4049
4050   if (a->ts.type != BT_INTEGER)
4051     gfc_internal_error ("compare_bound_int(): Bad expression");
4052
4053   i = mpz_cmp_si (a->value.integer, b);
4054
4055   if (i < 0)
4056     return CMP_LT;
4057   if (i > 0)
4058     return CMP_GT;
4059   return CMP_EQ;
4060 }
4061
4062
4063 /* Compare an integer expression with a mpz_t.  */
4064
4065 static comparison
4066 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
4067 {
4068   int i;
4069
4070   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4071     return CMP_UNKNOWN;
4072
4073   if (a->ts.type != BT_INTEGER)
4074     gfc_internal_error ("compare_bound_int(): Bad expression");
4075
4076   i = mpz_cmp (a->value.integer, b);
4077
4078   if (i < 0)
4079     return CMP_LT;
4080   if (i > 0)
4081     return CMP_GT;
4082   return CMP_EQ;
4083 }
4084
4085
4086 /* Compute the last value of a sequence given by a triplet.  
4087    Return 0 if it wasn't able to compute the last value, or if the
4088    sequence if empty, and 1 otherwise.  */
4089
4090 static int
4091 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
4092                                 gfc_expr *stride, mpz_t last)
4093 {
4094   mpz_t rem;
4095
4096   if (start == NULL || start->expr_type != EXPR_CONSTANT
4097       || end == NULL || end->expr_type != EXPR_CONSTANT
4098       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
4099     return 0;
4100
4101   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
4102       || (stride != NULL && stride->ts.type != BT_INTEGER))
4103     return 0;
4104
4105   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
4106     {
4107       if (compare_bound (start, end) == CMP_GT)
4108         return 0;
4109       mpz_set (last, end->value.integer);
4110       return 1;
4111     }
4112
4113   if (compare_bound_int (stride, 0) == CMP_GT)
4114     {
4115       /* Stride is positive */
4116       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
4117         return 0;
4118     }
4119   else
4120     {
4121       /* Stride is negative */
4122       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
4123         return 0;
4124     }
4125
4126   mpz_init (rem);
4127   mpz_sub (rem, end->value.integer, start->value.integer);
4128   mpz_tdiv_r (rem, rem, stride->value.integer);
4129   mpz_sub (last, end->value.integer, rem);
4130   mpz_clear (rem);
4131
4132   return 1;
4133 }
4134
4135
4136 /* Compare a single dimension of an array reference to the array
4137    specification.  */
4138
4139 static gfc_try
4140 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
4141 {
4142   mpz_t last_value;
4143
4144   if (ar->dimen_type[i] == DIMEN_STAR)
4145     {
4146       gcc_assert (ar->stride[i] == NULL);
4147       /* This implies [*] as [*:] and [*:3] are not possible.  */
4148       if (ar->start[i] == NULL)
4149         {
4150           gcc_assert (ar->end[i] == NULL);
4151           return SUCCESS;
4152         }
4153     }
4154
4155 /* Given start, end and stride values, calculate the minimum and
4156    maximum referenced indexes.  */
4157
4158   switch (ar->dimen_type[i])
4159     {
4160     case DIMEN_VECTOR:
4161     case DIMEN_THIS_IMAGE:
4162       break;
4163
4164     case DIMEN_STAR:
4165     case DIMEN_ELEMENT:
4166       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4167         {
4168           if (i < as->rank)
4169             gfc_warning ("Array reference at %L is out of bounds "
4170                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
4171                          mpz_get_si (ar->start[i]->value.integer),
4172                          mpz_get_si (as->lower[i]->value.integer), i+1);
4173           else
4174             gfc_warning ("Array reference at %L is out of bounds "
4175                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
4176                          mpz_get_si (ar->start[i]->value.integer),
4177                          mpz_get_si (as->lower[i]->value.integer),
4178                          i + 1 - as->rank);
4179           return SUCCESS;
4180         }
4181       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4182         {
4183           if (i < as->rank)
4184             gfc_warning ("Array reference at %L is out of bounds "
4185                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
4186                          mpz_get_si (ar->start[i]->value.integer),
4187                          mpz_get_si (as->upper[i]->value.integer), i+1);
4188           else
4189             gfc_warning ("Array reference at %L is out of bounds "
4190                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
4191                          mpz_get_si (ar->start[i]->value.integer),
4192                          mpz_get_si (as->upper[i]->value.integer),
4193                          i + 1 - as->rank);
4194           return SUCCESS;
4195         }
4196
4197       break;
4198
4199     case DIMEN_RANGE:
4200       {
4201 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4202 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4203
4204         comparison comp_start_end = compare_bound (AR_START, AR_END);
4205
4206         /* Check for zero stride, which is not allowed.  */
4207         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4208           {
4209             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4210             return FAILURE;
4211           }
4212
4213         /* if start == len || (stride > 0 && start < len)
4214                            || (stride < 0 && start > len),
4215            then the array section contains at least one element.  In this
4216            case, there is an out-of-bounds access if
4217            (start < lower || start > upper).  */
4218         if (compare_bound (AR_START, AR_END) == CMP_EQ
4219             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4220                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4221             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4222                 && comp_start_end == CMP_GT))
4223           {
4224             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4225               {
4226                 gfc_warning ("Lower array reference at %L is out of bounds "
4227                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4228                        mpz_get_si (AR_START->value.integer),
4229                        mpz_get_si (as->lower[i]->value.integer), i+1);
4230                 return SUCCESS;
4231               }
4232             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4233               {
4234                 gfc_warning ("Lower array reference at %L is out of bounds "
4235                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4236                        mpz_get_si (AR_START->value.integer),
4237                        mpz_get_si (as->upper[i]->value.integer), i+1);
4238                 return SUCCESS;
4239               }
4240           }
4241
4242         /* If we can compute the highest index of the array section,
4243            then it also has to be between lower and upper.  */
4244         mpz_init (last_value);
4245         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4246                                             last_value))
4247           {
4248             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4249               {
4250                 gfc_warning ("Upper array reference at %L is out of bounds "
4251                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4252                        mpz_get_si (last_value),
4253                        mpz_get_si (as->lower[i]->value.integer), i+1);
4254                 mpz_clear (last_value);
4255                 return SUCCESS;
4256               }
4257             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4258               {
4259                 gfc_warning ("Upper array reference at %L is out of bounds "
4260                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4261                        mpz_get_si (last_value),
4262                        mpz_get_si (as->upper[i]->value.integer), i+1);
4263                 mpz_clear (last_value);
4264                 return SUCCESS;
4265               }
4266           }
4267         mpz_clear (last_value);
4268
4269 #undef AR_START
4270 #undef AR_END
4271       }
4272       break;
4273
4274     default:
4275       gfc_internal_error ("check_dimension(): Bad array reference");
4276     }
4277
4278   return SUCCESS;
4279 }
4280
4281
4282 /* Compare an array reference with an array specification.  */
4283
4284 static gfc_try
4285 compare_spec_to_ref (gfc_array_ref *ar)
4286 {
4287   gfc_array_spec *as;
4288   int i;
4289
4290   as = ar->as;
4291   i = as->rank - 1;
4292   /* TODO: Full array sections are only allowed as actual parameters.  */
4293   if (as->type == AS_ASSUMED_SIZE
4294       && (/*ar->type == AR_FULL
4295           ||*/ (ar->type == AR_SECTION
4296               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4297     {
4298       gfc_error ("Rightmost upper bound of assumed size array section "
4299                  "not specified at %L", &ar->where);
4300       return FAILURE;
4301     }
4302
4303   if (ar->type == AR_FULL)
4304     return SUCCESS;
4305
4306   if (as->rank != ar->dimen)
4307     {
4308       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4309                  &ar->where, ar->dimen, as->rank);
4310       return FAILURE;
4311     }
4312
4313   /* ar->codimen == 0 is a local array.  */
4314   if (as->corank != ar->codimen && ar->codimen != 0)
4315     {
4316       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4317                  &ar->where, ar->codimen, as->corank);
4318       return FAILURE;
4319     }
4320
4321   for (i = 0; i < as->rank; i++)
4322     if (check_dimension (i, ar, as) == FAILURE)
4323       return FAILURE;
4324
4325   /* Local access has no coarray spec.  */
4326   if (ar->codimen != 0)
4327     for (i = as->rank; i < as->rank + as->corank; i++)
4328       {
4329         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate
4330             && ar->dimen_type[i] != DIMEN_THIS_IMAGE)
4331           {
4332             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4333                        i + 1 - as->rank, &ar->where);
4334             return FAILURE;
4335           }
4336         if (check_dimension (i, ar, as) == FAILURE)
4337           return FAILURE;
4338       }
4339
4340   if (as->corank && ar->codimen == 0)
4341     {
4342       int n;
4343       ar->codimen = as->corank;
4344       for (n = ar->dimen; n < ar->dimen + ar->codimen; n++)
4345         ar->dimen_type[n] = DIMEN_THIS_IMAGE;
4346     }
4347
4348   return SUCCESS;
4349 }
4350
4351
4352 /* Resolve one part of an array index.  */
4353
4354 static gfc_try
4355 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4356                      int force_index_integer_kind)
4357 {
4358   gfc_typespec ts;
4359
4360   if (index == NULL)
4361     return SUCCESS;
4362
4363   if (gfc_resolve_expr (index) == FAILURE)
4364     return FAILURE;
4365
4366   if (check_scalar && index->rank != 0)
4367     {
4368       gfc_error ("Array index at %L must be scalar", &index->where);
4369       return FAILURE;
4370     }
4371
4372   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4373     {
4374       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4375                  &index->where, gfc_basic_typename (index->ts.type));
4376       return FAILURE;
4377     }
4378
4379   if (index->ts.type == BT_REAL)
4380     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4381                         &index->where) == FAILURE)
4382       return FAILURE;
4383
4384   if ((index->ts.kind != gfc_index_integer_kind
4385        && force_index_integer_kind)
4386       || index->ts.type != BT_INTEGER)
4387     {
4388       gfc_clear_ts (&ts);
4389       ts.type = BT_INTEGER;
4390       ts.kind = gfc_index_integer_kind;
4391
4392       gfc_convert_type_warn (index, &ts, 2, 0);
4393     }
4394
4395   return SUCCESS;
4396 }
4397
4398 /* Resolve one part of an array index.  */
4399
4400 gfc_try
4401 gfc_resolve_index (gfc_expr *index, int check_scalar)
4402 {
4403   return gfc_resolve_index_1 (index, check_scalar, 1);
4404 }
4405
4406 /* Resolve a dim argument to an intrinsic function.  */
4407
4408 gfc_try
4409 gfc_resolve_dim_arg (gfc_expr *dim)
4410 {
4411   if (dim == NULL)
4412     return SUCCESS;
4413
4414   if (gfc_resolve_expr (dim) == FAILURE)
4415     return FAILURE;
4416
4417   if (dim->rank != 0)
4418     {
4419       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4420       return FAILURE;
4421
4422     }
4423
4424   if (dim->ts.type != BT_INTEGER)
4425     {
4426       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4427       return FAILURE;
4428     }
4429
4430   if (dim->ts.kind != gfc_index_integer_kind)
4431     {
4432       gfc_typespec ts;
4433
4434       gfc_clear_ts (&ts);
4435       ts.type = BT_INTEGER;
4436       ts.kind = gfc_index_integer_kind;
4437
4438       gfc_convert_type_warn (dim, &ts, 2, 0);
4439     }
4440
4441   return SUCCESS;
4442 }
4443
4444 /* Given an expression that contains array references, update those array
4445    references to point to the right array specifications.  While this is
4446    filled in during matching, this information is difficult to save and load
4447    in a module, so we take care of it here.
4448
4449    The idea here is that the original array reference comes from the
4450    base symbol.  We traverse the list of reference structures, setting
4451    the stored reference to references.  Component references can
4452    provide an additional array specification.  */
4453
4454 static void
4455 find_array_spec (gfc_expr *e)
4456 {
4457   gfc_array_spec *as;
4458   gfc_component *c;
4459   gfc_symbol *derived;
4460   gfc_ref *ref;
4461
4462   if (e->symtree->n.sym->ts.type == BT_CLASS)
4463     as = CLASS_DATA (e->symtree->n.sym)->as;
4464   else
4465     as = e->symtree->n.sym->as;
4466   derived = NULL;
4467
4468   for (ref = e->ref; ref; ref = ref->next)
4469     switch (ref->type)
4470       {
4471       case REF_ARRAY:
4472         if (as == NULL)
4473           gfc_internal_error ("find_array_spec(): Missing spec");
4474
4475         ref->u.ar.as = as;
4476         as = NULL;
4477         break;
4478
4479       case REF_COMPONENT:
4480         if (derived == NULL)
4481           derived = e->symtree->n.sym->ts.u.derived;
4482
4483         if (derived->attr.is_class)
4484           derived = derived->components->ts.u.derived;
4485
4486         c = derived->components;
4487
4488         for (; c; c = c->next)
4489           if (c == ref->u.c.component)
4490             {
4491               /* Track the sequence of component references.  */
4492               if (c->ts.type == BT_DERIVED)
4493                 derived = c->ts.u.derived;
4494               break;
4495             }
4496
4497         if (c == NULL)
4498           gfc_internal_error ("find_array_spec(): Component not found");
4499
4500         if (c->attr.dimension)
4501           {
4502             if (as != NULL)
4503               gfc_internal_error ("find_array_spec(): unused as(1)");
4504             as = c->as;
4505           }
4506
4507         break;
4508
4509       case REF_SUBSTRING:
4510         break;
4511       }
4512
4513   if (as != NULL)
4514     gfc_internal_error ("find_array_spec(): unused as(2)");
4515 }
4516
4517
4518 /* Resolve an array reference.  */
4519
4520 static gfc_try
4521 resolve_array_ref (gfc_array_ref *ar)
4522 {
4523   int i, check_scalar;
4524   gfc_expr *e;
4525
4526   for (i = 0; i < ar->dimen + ar->codimen; i++)
4527     {
4528       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4529
4530       /* Do not force gfc_index_integer_kind for the start.  We can
4531          do fine with any integer kind.  This avoids temporary arrays
4532          created for indexing with a vector.  */
4533       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4534         return FAILURE;
4535       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4536         return FAILURE;
4537       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4538         return FAILURE;
4539
4540       e = ar->start[i];
4541
4542       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4543         switch (e->rank)
4544           {
4545           case 0:
4546             ar->dimen_type[i] = DIMEN_ELEMENT;
4547             break;
4548
4549           case 1:
4550             ar->dimen_type[i] = DIMEN_VECTOR;
4551             if (e->expr_type == EXPR_VARIABLE
4552                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4553               ar->start[i] = gfc_get_parentheses (e);
4554             break;
4555
4556           default:
4557             gfc_error ("Array index at %L is an array of rank %d",
4558                        &ar->c_where[i], e->rank);
4559             return FAILURE;
4560           }
4561
4562       /* Fill in the upper bound, which may be lower than the
4563          specified one for something like a(2:10:5), which is
4564          identical to a(2:7:5).  Only relevant for strides not equal
4565          to one.  */
4566       if (ar->dimen_type[i] == DIMEN_RANGE
4567           && ar->stride[i] != NULL && ar->stride[i]->expr_type == EXPR_CONSTANT
4568           && mpz_cmp_si (ar->stride[i]->value.integer, 1L) != 0)
4569         {
4570           mpz_t size, end;
4571
4572           if (gfc_ref_dimen_size (ar, i, &size, &end) == SUCCESS)
4573             {
4574               if (ar->end[i] == NULL)
4575                 {
4576                   ar->end[i] =
4577                     gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
4578                                            &ar->where);
4579                   mpz_set (ar->end[i]->value.integer, end);
4580                 }
4581               else if (ar->end[i]->ts.type == BT_INTEGER
4582                        && ar->end[i]->expr_type == EXPR_CONSTANT)
4583                 {
4584                   mpz_set (ar->end[i]->value.integer, end);
4585                 }
4586               else
4587                 gcc_unreachable ();
4588
4589               mpz_clear (size);
4590               mpz_clear (end);
4591             }
4592         }
4593     }
4594
4595   if (ar->type == AR_FULL && ar->as->rank == 0)
4596     ar->type = AR_ELEMENT;
4597
4598   /* If the reference type is unknown, figure out what kind it is.  */
4599
4600   if (ar->type == AR_UNKNOWN)
4601     {
4602       ar->type = AR_ELEMENT;
4603       for (i = 0; i < ar->dimen; i++)
4604         if (ar->dimen_type[i] == DIMEN_RANGE
4605             || ar->dimen_type[i] == DIMEN_VECTOR)
4606           {
4607             ar->type = AR_SECTION;
4608             break;
4609           }
4610     }
4611
4612   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4613     return FAILURE;
4614
4615   return SUCCESS;
4616 }
4617
4618
4619 static gfc_try
4620 resolve_substring (gfc_ref *ref)
4621 {
4622   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4623
4624   if (ref->u.ss.start != NULL)
4625     {
4626       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4627         return FAILURE;
4628
4629       if (ref->u.ss.start->ts.type != BT_INTEGER)
4630         {
4631           gfc_error ("Substring start index at %L must be of type INTEGER",
4632                      &ref->u.ss.start->where);
4633           return FAILURE;
4634         }
4635
4636       if (ref->u.ss.start->rank != 0)
4637         {
4638           gfc_error ("Substring start index at %L must be scalar",
4639                      &ref->u.ss.start->where);
4640           return FAILURE;
4641         }
4642
4643       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4644           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4645               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4646         {
4647           gfc_error ("Substring start index at %L is less than one",
4648                      &ref->u.ss.start->where);
4649           return FAILURE;
4650         }
4651     }
4652
4653   if (ref->u.ss.end != NULL)
4654     {
4655       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4656         return FAILURE;
4657
4658       if (ref->u.ss.end->ts.type != BT_INTEGER)
4659         {
4660           gfc_error ("Substring end index at %L must be of type INTEGER",
4661                      &ref->u.ss.end->where);
4662           return FAILURE;
4663         }
4664
4665       if (ref->u.ss.end->rank != 0)
4666         {
4667           gfc_error ("Substring end index at %L must be scalar",
4668                      &ref->u.ss.end->where);
4669           return FAILURE;
4670         }
4671
4672       if (ref->u.ss.length != NULL
4673           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4674           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4675               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4676         {
4677           gfc_error ("Substring end index at %L exceeds the string length",
4678                      &ref->u.ss.start->where);
4679           return FAILURE;
4680         }
4681
4682       if (compare_bound_mpz_t (ref->u.ss.end,
4683                                gfc_integer_kinds[k].huge) == CMP_GT
4684           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4685               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4686         {
4687           gfc_error ("Substring end index at %L is too large",
4688                      &ref->u.ss.end->where);
4689           return FAILURE;
4690         }
4691     }
4692
4693   return SUCCESS;
4694 }
4695
4696
4697 /* This function supplies missing substring charlens.  */
4698
4699 void
4700 gfc_resolve_substring_charlen (gfc_expr *e)
4701 {
4702   gfc_ref *char_ref;
4703   gfc_expr *start, *end;
4704
4705   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4706     if (char_ref->type == REF_SUBSTRING)
4707       break;
4708
4709   if (!char_ref)
4710     return;
4711
4712   gcc_assert (char_ref->next == NULL);
4713
4714   if (e->ts.u.cl)
4715     {
4716       if (e->ts.u.cl->length)
4717         gfc_free_expr (e->ts.u.cl->length);
4718       else if (e->expr_type == EXPR_VARIABLE
4719                  && e->symtree->n.sym->attr.dummy)
4720         return;
4721     }
4722
4723   e->ts.type = BT_CHARACTER;
4724   e->ts.kind = gfc_default_character_kind;
4725
4726   if (!e->ts.u.cl)
4727     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4728
4729   if (char_ref->u.ss.start)
4730     start = gfc_copy_expr (char_ref->u.ss.start);
4731   else
4732     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4733
4734   if (char_ref->u.ss.end)
4735     end = gfc_copy_expr (char_ref->u.ss.end);
4736   else if (e->expr_type == EXPR_VARIABLE)
4737     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4738   else
4739     end = NULL;
4740
4741   if (!start || !end)
4742     return;
4743
4744   /* Length = (end - start +1).  */
4745   e->ts.u.cl->length = gfc_subtract (end, start);
4746   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4747                                 gfc_get_int_expr (gfc_default_integer_kind,
4748                                                   NULL, 1));
4749
4750   e->ts.u.cl->length->ts.type = BT_INTEGER;
4751   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4752
4753   /* Make sure that the length is simplified.  */
4754   gfc_simplify_expr (e->ts.u.cl->length, 1);
4755   gfc_resolve_expr (e->ts.u.cl->length);
4756 }
4757
4758
4759 /* Resolve subtype references.  */
4760
4761 static gfc_try
4762 resolve_ref (gfc_expr *expr)
4763 {
4764   int current_part_dimension, n_components, seen_part_dimension;
4765   gfc_ref *ref;
4766
4767   for (ref = expr->ref; ref; ref = ref->next)
4768     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4769       {
4770         find_array_spec (expr);
4771         break;
4772       }
4773
4774   for (ref = expr->ref; ref; ref = ref->next)
4775     switch (ref->type)
4776       {
4777       case REF_ARRAY:
4778         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4779           return FAILURE;
4780         break;
4781
4782       case REF_COMPONENT:
4783         break;
4784
4785       case REF_SUBSTRING:
4786         resolve_substring (ref);
4787         break;
4788       }
4789
4790   /* Check constraints on part references.  */
4791
4792   current_part_dimension = 0;
4793   seen_part_dimension = 0;
4794   n_components = 0;
4795
4796   for (ref = expr->ref; ref; ref = ref->next)
4797     {
4798       switch (ref->type)
4799         {
4800         case REF_ARRAY:
4801           switch (ref->u.ar.type)
4802             {
4803             case AR_FULL:
4804               /* Coarray scalar.  */
4805               if (ref->u.ar.as->rank == 0)
4806                 {
4807                   current_part_dimension = 0;
4808                   break;
4809                 }
4810               /* Fall through.  */
4811             case AR_SECTION:
4812               current_part_dimension = 1;
4813               break;
4814
4815             case AR_ELEMENT:
4816               current_part_dimension = 0;
4817               break;
4818
4819             case AR_UNKNOWN:
4820               gfc_internal_error ("resolve_ref(): Bad array reference");
4821             }
4822
4823           break;
4824
4825         case REF_COMPONENT:
4826           if (current_part_dimension || seen_part_dimension)
4827             {
4828               /* F03:C614.  */
4829               if (ref->u.c.component->attr.pointer
4830                   || ref->u.c.component->attr.proc_pointer)
4831                 {
4832                   gfc_error ("Component to the right of a part reference "
4833                              "with nonzero rank must not have the POINTER "
4834                              "attribute at %L", &expr->where);
4835                   return FAILURE;
4836                 }
4837               else if (ref->u.c.component->attr.allocatable)
4838                 {
4839                   gfc_error ("Component to the right of a part reference "
4840                              "with nonzero rank must not have the ALLOCATABLE "
4841                              "attribute at %L", &expr->where);
4842                   return FAILURE;
4843                 }
4844             }
4845
4846           n_components++;
4847           break;
4848
4849         case REF_SUBSTRING:
4850           break;
4851         }
4852
4853       if (((ref->type == REF_COMPONENT && n_components > 1)
4854            || ref->next == NULL)
4855           && current_part_dimension
4856           && seen_part_dimension)
4857         {
4858           gfc_error ("Two or more part references with nonzero rank must "
4859                      "not be specified at %L", &expr->where);
4860           return FAILURE;
4861         }
4862
4863       if (ref->type == REF_COMPONENT)
4864         {
4865           if (current_part_dimension)
4866             seen_part_dimension = 1;
4867
4868           /* reset to make sure */
4869           current_part_dimension = 0;
4870         }
4871     }
4872
4873   return SUCCESS;
4874 }
4875
4876
4877 /* Given an expression, determine its shape.  This is easier than it sounds.
4878    Leaves the shape array NULL if it is not possible to determine the shape.  */
4879
4880 static void
4881 expression_shape (gfc_expr *e)
4882 {
4883   mpz_t array[GFC_MAX_DIMENSIONS];
4884   int i;
4885
4886   if (e->rank == 0 || e->shape != NULL)
4887     return;
4888
4889   for (i = 0; i < e->rank; i++)
4890     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4891       goto fail;
4892
4893   e->shape = gfc_get_shape (e->rank);
4894
4895   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4896
4897   return;
4898
4899 fail:
4900   for (i--; i >= 0; i--)
4901     mpz_clear (array[i]);
4902 }
4903
4904
4905 /* Given a variable expression node, compute the rank of the expression by
4906    examining the base symbol and any reference structures it may have.  */
4907
4908 static void
4909 expression_rank (gfc_expr *e)
4910 {
4911   gfc_ref *ref;
4912   int i, rank;
4913
4914   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4915      could lead to serious confusion...  */
4916   gcc_assert (e->expr_type != EXPR_COMPCALL);
4917
4918   if (e->ref == NULL)
4919     {
4920       if (e->expr_type == EXPR_ARRAY)
4921         goto done;
4922       /* Constructors can have a rank different from one via RESHAPE().  */
4923
4924       if (e->symtree == NULL)
4925         {
4926           e->rank = 0;
4927           goto done;
4928         }
4929
4930       e->rank = (e->symtree->n.sym->as == NULL)
4931                 ? 0 : e->symtree->n.sym->as->rank;
4932       goto done;
4933     }
4934
4935   rank = 0;
4936
4937   for (ref = e->ref; ref; ref = ref->next)
4938     {
4939       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.proc_pointer
4940           && ref->u.c.component->attr.function && !ref->next)
4941         rank = ref->u.c.component->as ? ref->u.c.component->as->rank : 0;
4942
4943       if (ref->type != REF_ARRAY)
4944         continue;
4945
4946       if (ref->u.ar.type == AR_FULL)
4947         {
4948           rank = ref->u.ar.as->rank;
4949           break;
4950         }
4951
4952       if (ref->u.ar.type == AR_SECTION)
4953         {
4954           /* Figure out the rank of the section.  */
4955           if (rank != 0)
4956             gfc_internal_error ("expression_rank(): Two array specs");
4957
4958           for (i = 0; i < ref->u.ar.dimen; i++)
4959             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4960                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4961               rank++;
4962
4963           break;
4964         }
4965     }
4966
4967   e->rank = rank;
4968
4969 done:
4970   expression_shape (e);
4971 }
4972
4973
4974 /* Resolve a variable expression.  */
4975
4976 static gfc_try
4977 resolve_variable (gfc_expr *e)
4978 {
4979   gfc_symbol *sym;
4980   gfc_try t;
4981
4982   t = SUCCESS;
4983
4984   if (e->symtree == NULL)
4985     return FAILURE;
4986   sym = e->symtree->n.sym;
4987
4988   /* If this is an associate-name, it may be parsed with an array reference
4989      in error even though the target is scalar.  Fail directly in this case.  */
4990   if (sym->assoc && !sym->attr.dimension && e->ref && e->ref->type == REF_ARRAY)
4991     return FAILURE;
4992
4993   /* On the other hand, the parser may not have known this is an array;
4994      in this case, we have to add a FULL reference.  */
4995   if (sym->assoc && sym->attr.dimension && !e->ref)
4996     {
4997       e->ref = gfc_get_ref ();
4998       e->ref->type = REF_ARRAY;
4999       e->ref->u.ar.type = AR_FULL;
5000       e->ref->u.ar.dimen = 0;
5001     }
5002
5003   if (e->ref && resolve_ref (e) == FAILURE)
5004     return FAILURE;
5005
5006   if (sym->attr.flavor == FL_PROCEDURE
5007       && (!sym->attr.function
5008           || (sym->attr.function && sym->result
5009               && sym->result->attr.proc_pointer
5010               && !sym->result->attr.function)))
5011     {
5012       e->ts.type = BT_PROCEDURE;
5013       goto resolve_procedure;
5014     }
5015
5016   if (sym->ts.type != BT_UNKNOWN)
5017     gfc_variable_attr (e, &e->ts);
5018   else
5019     {
5020       /* Must be a simple variable reference.  */
5021       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
5022         return FAILURE;
5023       e->ts = sym->ts;
5024     }
5025
5026   if (check_assumed_size_reference (sym, e))
5027     return FAILURE;
5028
5029   /* Deal with forward references to entries during resolve_code, to
5030      satisfy, at least partially, 12.5.2.5.  */
5031   if (gfc_current_ns->entries
5032       && current_entry_id == sym->entry_id
5033       && cs_base
5034       && cs_base->current
5035       && cs_base->current->op != EXEC_ENTRY)
5036     {
5037       gfc_entry_list *entry;
5038       gfc_formal_arglist *formal;
5039       int n;
5040       bool seen;
5041
5042       /* If the symbol is a dummy...  */
5043       if (sym->attr.dummy && sym->ns == gfc_current_ns)
5044         {
5045           entry = gfc_current_ns->entries;
5046           seen = false;
5047
5048           /* ...test if the symbol is a parameter of previous entries.  */
5049           for (; entry && entry->id <= current_entry_id; entry = entry->next)
5050             for (formal = entry->sym->formal; formal; formal = formal->next)
5051               {
5052                 if (formal->sym && sym->name == formal->sym->name)
5053                   seen = true;
5054               }
5055
5056           /*  If it has not been seen as a dummy, this is an error.  */
5057           if (!seen)
5058             {
5059               if (specification_expr)
5060                 gfc_error ("Variable '%s', used in a specification expression"
5061                            ", is referenced at %L before the ENTRY statement "
5062                            "in which it is a parameter",
5063                            sym->name, &cs_base->current->loc);
5064               else
5065                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
5066                            "statement in which it is a parameter",
5067                            sym->name, &cs_base->current->loc);
5068               t = FAILURE;
5069             }
5070         }
5071
5072       /* Now do the same check on the specification expressions.  */
5073       specification_expr = 1;
5074       if (sym->ts.type == BT_CHARACTER
5075           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
5076         t = FAILURE;
5077
5078       if (sym->as)
5079         for (n = 0; n < sym->as->rank; n++)
5080           {
5081              specification_expr = 1;
5082              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
5083                t = FAILURE;
5084              specification_expr = 1;
5085              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
5086                t = FAILURE;
5087           }
5088       specification_expr = 0;
5089
5090       if (t == SUCCESS)
5091         /* Update the symbol's entry level.  */
5092         sym->entry_id = current_entry_id + 1;
5093     }
5094
5095   /* If a symbol has been host_associated mark it.  This is used latter,
5096      to identify if aliasing is possible via host association.  */
5097   if (sym->attr.flavor == FL_VARIABLE
5098         && gfc_current_ns->parent
5099         && (gfc_current_ns->parent == sym->ns
5100               || (gfc_current_ns->parent->parent
5101                     && gfc_current_ns->parent->parent == sym->ns)))
5102     sym->attr.host_assoc = 1;
5103
5104 resolve_procedure:
5105   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
5106     t = FAILURE;
5107
5108   /* F2008, C617 and C1229.  */
5109   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5110       && gfc_is_coindexed (e))
5111     {
5112       gfc_ref *ref, *ref2 = NULL;
5113
5114       for (ref = e->ref; ref; ref = ref->next)
5115         {
5116           if (ref->type == REF_COMPONENT)
5117             ref2 = ref;
5118           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5119             break;
5120         }
5121
5122       for ( ; ref; ref = ref->next)
5123         if (ref->type == REF_COMPONENT)
5124           break;
5125
5126       /* Expression itself is not coindexed object.  */
5127       if (ref && e->ts.type == BT_CLASS)
5128         {
5129           gfc_error ("Polymorphic subobject of coindexed object at %L",
5130                      &e->where);
5131           t = FAILURE;
5132         }
5133
5134       /* Expression itself is coindexed object.  */
5135       if (ref == NULL)
5136         {
5137           gfc_component *c;
5138           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5139           for ( ; c; c = c->next)
5140             if (c->attr.allocatable && c->ts.type == BT_CLASS)
5141               {
5142                 gfc_error ("Coindexed object with polymorphic allocatable "
5143                          "subcomponent at %L", &e->where);
5144                 t = FAILURE;
5145                 break;
5146               }
5147         }
5148     }
5149
5150   return t;
5151 }
5152
5153
5154 /* Checks to see that the correct symbol has been host associated.
5155    The only situation where this arises is that in which a twice
5156    contained function is parsed after the host association is made.
5157    Therefore, on detecting this, change the symbol in the expression
5158    and convert the array reference into an actual arglist if the old
5159    symbol is a variable.  */
5160 static bool
5161 check_host_association (gfc_expr *e)
5162 {
5163   gfc_symbol *sym, *old_sym;
5164   gfc_symtree *st;
5165   int n;
5166   gfc_ref *ref;
5167   gfc_actual_arglist *arg, *tail = NULL;
5168   bool retval = e->expr_type == EXPR_FUNCTION;
5169
5170   /*  If the expression is the result of substitution in
5171       interface.c(gfc_extend_expr) because there is no way in
5172       which the host association can be wrong.  */
5173   if (e->symtree == NULL
5174         || e->symtree->n.sym == NULL
5175         || e->user_operator)
5176     return retval;
5177
5178   old_sym = e->symtree->n.sym;
5179
5180   if (gfc_current_ns->parent
5181         && old_sym->ns != gfc_current_ns)
5182     {
5183       /* Use the 'USE' name so that renamed module symbols are
5184          correctly handled.  */
5185       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5186
5187       if (sym && old_sym != sym
5188               && sym->ts.type == old_sym->ts.type
5189               && sym->attr.flavor == FL_PROCEDURE
5190               && sym->attr.contained)
5191         {
5192           /* Clear the shape, since it might not be valid.  */
5193           if (e->shape != NULL)
5194             {
5195               for (n = 0; n < e->rank; n++)
5196                 mpz_clear (e->shape[n]);
5197
5198               free (e->shape);
5199             }
5200
5201           /* Give the expression the right symtree!  */
5202           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5203           gcc_assert (st != NULL);
5204
5205           if (old_sym->attr.flavor == FL_PROCEDURE
5206                 || e->expr_type == EXPR_FUNCTION)
5207             {
5208               /* Original was function so point to the new symbol, since
5209                  the actual argument list is already attached to the
5210                  expression. */
5211               e->value.function.esym = NULL;
5212               e->symtree = st;
5213             }
5214           else
5215             {
5216               /* Original was variable so convert array references into
5217                  an actual arglist. This does not need any checking now
5218                  since gfc_resolve_function will take care of it.  */
5219               e->value.function.actual = NULL;
5220               e->expr_type = EXPR_FUNCTION;
5221               e->symtree = st;
5222
5223               /* Ambiguity will not arise if the array reference is not
5224                  the last reference.  */
5225               for (ref = e->ref; ref; ref = ref->next)
5226                 if (ref->type == REF_ARRAY && ref->next == NULL)
5227                   break;
5228
5229               gcc_assert (ref->type == REF_ARRAY);
5230
5231               /* Grab the start expressions from the array ref and
5232                  copy them into actual arguments.  */
5233               for (n = 0; n < ref->u.ar.dimen; n++)
5234                 {
5235                   arg = gfc_get_actual_arglist ();
5236                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5237                   if (e->value.function.actual == NULL)
5238                     tail = e->value.function.actual = arg;
5239                   else
5240                     {
5241                       tail->next = arg;
5242                       tail = arg;
5243                     }
5244                 }
5245
5246               /* Dump the reference list and set the rank.  */
5247               gfc_free_ref_list (e->ref);
5248               e->ref = NULL;
5249               e->rank = sym->as ? sym->as->rank : 0;
5250             }
5251
5252           gfc_resolve_expr (e);
5253           sym->refs++;
5254         }
5255     }
5256   /* This might have changed!  */
5257   return e->expr_type == EXPR_FUNCTION;
5258 }
5259
5260
5261 static void
5262 gfc_resolve_character_operator (gfc_expr *e)
5263 {
5264   gfc_expr *op1 = e->value.op.op1;
5265   gfc_expr *op2 = e->value.op.op2;
5266   gfc_expr *e1 = NULL;
5267   gfc_expr *e2 = NULL;
5268
5269   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5270
5271   if (op1->ts.u.cl && op1->ts.u.cl->length)
5272     e1 = gfc_copy_expr (op1->ts.u.cl->length);
5273   else if (op1->expr_type == EXPR_CONSTANT)
5274     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5275                            op1->value.character.length);
5276
5277   if (op2->ts.u.cl && op2->ts.u.cl->length)
5278     e2 = gfc_copy_expr (op2->ts.u.cl->length);
5279   else if (op2->expr_type == EXPR_CONSTANT)
5280     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5281                            op2->value.character.length);
5282
5283   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5284
5285   if (!e1 || !e2)
5286     return;
5287
5288   e->ts.u.cl->length = gfc_add (e1, e2);
5289   e->ts.u.cl->length->ts.type = BT_INTEGER;
5290   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5291   gfc_simplify_expr (e->ts.u.cl->length, 0);
5292   gfc_resolve_expr (e->ts.u.cl->length);
5293
5294   return;
5295 }
5296
5297
5298 /*  Ensure that an character expression has a charlen and, if possible, a
5299     length expression.  */
5300
5301 static void
5302 fixup_charlen (gfc_expr *e)
5303 {
5304   /* The cases fall through so that changes in expression type and the need
5305      for multiple fixes are picked up.  In all circumstances, a charlen should
5306      be available for the middle end to hang a backend_decl on.  */
5307   switch (e->expr_type)
5308     {
5309     case EXPR_OP:
5310       gfc_resolve_character_operator (e);
5311
5312     case EXPR_ARRAY:
5313       if (e->expr_type == EXPR_ARRAY)
5314         gfc_resolve_character_array_constructor (e);
5315
5316     case EXPR_SUBSTRING:
5317       if (!e->ts.u.cl && e->ref)
5318         gfc_resolve_substring_charlen (e);
5319
5320     default:
5321       if (!e->ts.u.cl)
5322         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5323
5324       break;
5325     }
5326 }
5327
5328
5329 /* Update an actual argument to include the passed-object for type-bound
5330    procedures at the right position.  */
5331
5332 static gfc_actual_arglist*
5333 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5334                      const char *name)
5335 {
5336   gcc_assert (argpos > 0);
5337
5338   if (argpos == 1)
5339     {
5340       gfc_actual_arglist* result;
5341
5342       result = gfc_get_actual_arglist ();
5343       result->expr = po;
5344       result->next = lst;
5345       if (name)
5346         result->name = name;
5347
5348       return result;
5349     }
5350
5351   if (lst)
5352     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5353   else
5354     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5355   return lst;
5356 }
5357
5358
5359 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5360
5361 static gfc_expr*
5362 extract_compcall_passed_object (gfc_expr* e)
5363 {
5364   gfc_expr* po;
5365
5366   gcc_assert (e->expr_type == EXPR_COMPCALL);
5367
5368   if (e->value.compcall.base_object)
5369     po = gfc_copy_expr (e->value.compcall.base_object);
5370   else
5371     {
5372       po = gfc_get_expr ();
5373       po->expr_type = EXPR_VARIABLE;
5374       po->symtree = e->symtree;
5375       po->ref = gfc_copy_ref (e->ref);
5376       po->where = e->where;
5377     }
5378
5379   if (gfc_resolve_expr (po) == FAILURE)
5380     return NULL;
5381
5382   return po;
5383 }
5384
5385
5386 /* Update the arglist of an EXPR_COMPCALL expression to include the
5387    passed-object.  */
5388
5389 static gfc_try
5390 update_compcall_arglist (gfc_expr* e)
5391 {
5392   gfc_expr* po;
5393   gfc_typebound_proc* tbp;
5394
5395   tbp = e->value.compcall.tbp;
5396
5397   if (tbp->error)
5398     return FAILURE;
5399
5400   po = extract_compcall_passed_object (e);
5401   if (!po)
5402     return FAILURE;
5403
5404   if (tbp->nopass || e->value.compcall.ignore_pass)
5405     {
5406       gfc_free_expr (po);
5407       return SUCCESS;
5408     }
5409
5410   gcc_assert (tbp->pass_arg_num > 0);
5411   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5412                                                   tbp->pass_arg_num,
5413                                                   tbp->pass_arg);
5414
5415   return SUCCESS;
5416 }
5417
5418
5419 /* Extract the passed object from a PPC call (a copy of it).  */
5420
5421 static gfc_expr*
5422 extract_ppc_passed_object (gfc_expr *e)
5423 {
5424   gfc_expr *po;
5425   gfc_ref **ref;
5426
5427   po = gfc_get_expr ();
5428   po->expr_type = EXPR_VARIABLE;
5429   po->symtree = e->symtree;
5430   po->ref = gfc_copy_ref (e->ref);
5431   po->where = e->where;
5432
5433   /* Remove PPC reference.  */
5434   ref = &po->ref;
5435   while ((*ref)->next)
5436     ref = &(*ref)->next;
5437   gfc_free_ref_list (*ref);
5438   *ref = NULL;
5439
5440   if (gfc_resolve_expr (po) == FAILURE)
5441     return NULL;
5442
5443   return po;
5444 }
5445
5446
5447 /* Update the actual arglist of a procedure pointer component to include the
5448    passed-object.  */
5449
5450 static gfc_try
5451 update_ppc_arglist (gfc_expr* e)
5452 {
5453   gfc_expr* po;
5454   gfc_component *ppc;
5455   gfc_typebound_proc* tb;
5456
5457   if (!gfc_is_proc_ptr_comp (e, &ppc))
5458     return FAILURE;
5459
5460   tb = ppc->tb;
5461
5462   if (tb->error)
5463     return FAILURE;
5464   else if (tb->nopass)
5465     return SUCCESS;
5466
5467   po = extract_ppc_passed_object (e);
5468   if (!po)
5469     return FAILURE;
5470
5471   /* F08:R739.  */
5472   if (po->rank > 0)
5473     {
5474       gfc_error ("Passed-object at %L must be scalar", &e->where);
5475       return FAILURE;
5476     }
5477
5478   /* F08:C611.  */
5479   if (po->ts.type == BT_DERIVED && po->ts.u.derived->attr.abstract)
5480     {
5481       gfc_error ("Base object for procedure-pointer component call at %L is of"
5482                  " ABSTRACT type '%s'", &e->where, po->ts.u.derived->name);
5483       return FAILURE;
5484     }
5485
5486   gcc_assert (tb->pass_arg_num > 0);
5487   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5488                                                   tb->pass_arg_num,
5489                                                   tb->pass_arg);
5490
5491   return SUCCESS;
5492 }
5493
5494
5495 /* Check that the object a TBP is called on is valid, i.e. it must not be
5496    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5497
5498 static gfc_try
5499 check_typebound_baseobject (gfc_expr* e)
5500 {
5501   gfc_expr* base;
5502   gfc_try return_value = FAILURE;
5503
5504   base = extract_compcall_passed_object (e);
5505   if (!base)
5506     return FAILURE;
5507
5508   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5509
5510   /* F08:C611.  */
5511   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5512     {
5513       gfc_error ("Base object for type-bound procedure call at %L is of"
5514                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5515       goto cleanup;
5516     }
5517
5518   /* F08:C1230. If the procedure called is NOPASS,
5519      the base object must be scalar.  */
5520   if (e->value.compcall.tbp->nopass && base->rank > 0)
5521     {
5522       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5523                  " be scalar", &e->where);
5524       goto cleanup;
5525     }
5526
5527   /* FIXME: Remove once PR 43214 is fixed (TBP with non-scalar PASS).  */
5528   if (base->rank > 0)
5529     {
5530       gfc_error ("Non-scalar base object at %L currently not implemented",
5531                  &e->where);
5532       goto cleanup;
5533     }
5534
5535   return_value = SUCCESS;
5536
5537 cleanup:
5538   gfc_free_expr (base);
5539   return return_value;
5540 }
5541
5542
5543 /* Resolve a call to a type-bound procedure, either function or subroutine,
5544    statically from the data in an EXPR_COMPCALL expression.  The adapted
5545    arglist and the target-procedure symtree are returned.  */
5546
5547 static gfc_try
5548 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5549                           gfc_actual_arglist** actual)
5550 {
5551   gcc_assert (e->expr_type == EXPR_COMPCALL);
5552   gcc_assert (!e->value.compcall.tbp->is_generic);
5553
5554   /* Update the actual arglist for PASS.  */
5555   if (update_compcall_arglist (e) == FAILURE)
5556     return FAILURE;
5557
5558   *actual = e->value.compcall.actual;
5559   *target = e->value.compcall.tbp->u.specific;
5560
5561   gfc_free_ref_list (e->ref);
5562   e->ref = NULL;
5563   e->value.compcall.actual = NULL;
5564
5565   return SUCCESS;
5566 }
5567
5568
5569 /* Get the ultimate declared type from an expression.  In addition,
5570    return the last class/derived type reference and the copy of the
5571    reference list.  */
5572 static gfc_symbol*
5573 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5574                         gfc_expr *e)
5575 {
5576   gfc_symbol *declared;
5577   gfc_ref *ref;
5578
5579   declared = NULL;
5580   if (class_ref)
5581     *class_ref = NULL;
5582   if (new_ref)
5583     *new_ref = gfc_copy_ref (e->ref);
5584
5585   for (ref = e->ref; ref; ref = ref->next)
5586     {
5587       if (ref->type != REF_COMPONENT)
5588         continue;
5589
5590       if (ref->u.c.component->ts.type == BT_CLASS
5591             || ref->u.c.component->ts.type == BT_DERIVED)
5592         {
5593           declared = ref->u.c.component->ts.u.derived;
5594           if (class_ref)
5595             *class_ref = ref;
5596         }
5597     }
5598
5599   if (declared == NULL)
5600     declared = e->symtree->n.sym->ts.u.derived;
5601
5602   return declared;
5603 }
5604
5605
5606 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5607    which of the specific bindings (if any) matches the arglist and transform
5608    the expression into a call of that binding.  */
5609
5610 static gfc_try
5611 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5612 {
5613   gfc_typebound_proc* genproc;
5614   const char* genname;
5615   gfc_symtree *st;
5616   gfc_symbol *derived;
5617
5618   gcc_assert (e->expr_type == EXPR_COMPCALL);
5619   genname = e->value.compcall.name;
5620   genproc = e->value.compcall.tbp;
5621
5622   if (!genproc->is_generic)
5623     return SUCCESS;
5624
5625   /* Try the bindings on this type and in the inheritance hierarchy.  */
5626   for (; genproc; genproc = genproc->overridden)
5627     {
5628       gfc_tbp_generic* g;
5629
5630       gcc_assert (genproc->is_generic);
5631       for (g = genproc->u.generic; g; g = g->next)
5632         {
5633           gfc_symbol* target;
5634           gfc_actual_arglist* args;
5635           bool matches;
5636
5637           gcc_assert (g->specific);
5638
5639           if (g->specific->error)
5640             continue;
5641
5642           target = g->specific->u.specific->n.sym;
5643
5644           /* Get the right arglist by handling PASS/NOPASS.  */
5645           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5646           if (!g->specific->nopass)
5647             {
5648               gfc_expr* po;
5649               po = extract_compcall_passed_object (e);
5650               if (!po)
5651                 return FAILURE;
5652
5653               gcc_assert (g->specific->pass_arg_num > 0);
5654               gcc_assert (!g->specific->error);
5655               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5656                                           g->specific->pass_arg);
5657             }
5658           resolve_actual_arglist (args, target->attr.proc,
5659                                   is_external_proc (target) && !target->formal);
5660
5661           /* Check if this arglist matches the formal.  */
5662           matches = gfc_arglist_matches_symbol (&args, target);
5663
5664           /* Clean up and break out of the loop if we've found it.  */
5665           gfc_free_actual_arglist (args);
5666           if (matches)
5667             {
5668               e->value.compcall.tbp = g->specific;
5669               genname = g->specific_st->name;
5670               /* Pass along the name for CLASS methods, where the vtab
5671                  procedure pointer component has to be referenced.  */
5672               if (name)
5673                 *name = genname;
5674               goto success;
5675             }
5676         }
5677     }
5678
5679   /* Nothing matching found!  */
5680   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5681              " '%s' at %L", genname, &e->where);
5682   return FAILURE;
5683
5684 success:
5685   /* Make sure that we have the right specific instance for the name.  */
5686   derived = get_declared_from_expr (NULL, NULL, e);
5687
5688   st = gfc_find_typebound_proc (derived, NULL, genname, true, &e->where);
5689   if (st)
5690     e->value.compcall.tbp = st->n.tb;
5691
5692   return SUCCESS;
5693 }
5694
5695
5696 /* Resolve a call to a type-bound subroutine.  */
5697
5698 static gfc_try
5699 resolve_typebound_call (gfc_code* c, const char **name)
5700 {
5701   gfc_actual_arglist* newactual;
5702   gfc_symtree* target;
5703
5704   /* Check that's really a SUBROUTINE.  */
5705   if (!c->expr1->value.compcall.tbp->subroutine)
5706     {
5707       gfc_error ("'%s' at %L should be a SUBROUTINE",
5708                  c->expr1->value.compcall.name, &c->loc);
5709       return FAILURE;
5710     }
5711
5712   if (check_typebound_baseobject (c->expr1) == FAILURE)
5713     return FAILURE;
5714
5715   /* Pass along the name for CLASS methods, where the vtab
5716      procedure pointer component has to be referenced.  */
5717   if (name)
5718     *name = c->expr1->value.compcall.name;
5719
5720   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5721     return FAILURE;
5722
5723   /* Transform into an ordinary EXEC_CALL for now.  */
5724
5725   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5726     return FAILURE;
5727
5728   c->ext.actual = newactual;
5729   c->symtree = target;
5730   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5731
5732   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5733
5734   gfc_free_expr (c->expr1);
5735   c->expr1 = gfc_get_expr ();
5736   c->expr1->expr_type = EXPR_FUNCTION;
5737   c->expr1->symtree = target;
5738   c->expr1->where = c->loc;
5739
5740   return resolve_call (c);
5741 }
5742
5743
5744 /* Resolve a component-call expression.  */
5745 static gfc_try
5746 resolve_compcall (gfc_expr* e, const char **name)
5747 {
5748   gfc_actual_arglist* newactual;
5749   gfc_symtree* target;
5750
5751   /* Check that's really a FUNCTION.  */
5752   if (!e->value.compcall.tbp->function)
5753     {
5754       gfc_error ("'%s' at %L should be a FUNCTION",
5755                  e->value.compcall.name, &e->where);
5756       return FAILURE;
5757     }
5758
5759   /* These must not be assign-calls!  */
5760   gcc_assert (!e->value.compcall.assign);
5761
5762   if (check_typebound_baseobject (e) == FAILURE)
5763     return FAILURE;
5764
5765   /* Pass along the name for CLASS methods, where the vtab
5766      procedure pointer component has to be referenced.  */
5767   if (name)
5768     *name = e->value.compcall.name;
5769
5770   if (resolve_typebound_generic_call (e, name) == FAILURE)
5771     return FAILURE;
5772   gcc_assert (!e->value.compcall.tbp->is_generic);
5773
5774   /* Take the rank from the function's symbol.  */
5775   if (e->value.compcall.tbp->u.specific->n.sym->as)
5776     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5777
5778   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5779      arglist to the TBP's binding target.  */
5780
5781   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5782     return FAILURE;
5783
5784   e->value.function.actual = newactual;
5785   e->value.function.name = NULL;
5786   e->value.function.esym = target->n.sym;
5787   e->value.function.isym = NULL;
5788   e->symtree = target;
5789   e->ts = target->n.sym->ts;
5790   e->expr_type = EXPR_FUNCTION;
5791
5792   /* Resolution is not necessary if this is a class subroutine; this
5793      function only has to identify the specific proc. Resolution of
5794      the call will be done next in resolve_typebound_call.  */
5795   return gfc_resolve_expr (e);
5796 }
5797
5798
5799
5800 /* Resolve a typebound function, or 'method'. First separate all
5801    the non-CLASS references by calling resolve_compcall directly.  */
5802
5803 static gfc_try
5804 resolve_typebound_function (gfc_expr* e)
5805 {
5806   gfc_symbol *declared;
5807   gfc_component *c;
5808   gfc_ref *new_ref;
5809   gfc_ref *class_ref;
5810   gfc_symtree *st;
5811   const char *name;
5812   gfc_typespec ts;
5813   gfc_expr *expr;
5814
5815   st = e->symtree;
5816
5817   /* Deal with typebound operators for CLASS objects.  */
5818   expr = e->value.compcall.base_object;
5819   if (expr && expr->ts.type == BT_CLASS && e->value.compcall.name)
5820     {
5821       /* Since the typebound operators are generic, we have to ensure
5822          that any delays in resolution are corrected and that the vtab
5823          is present.  */
5824       ts = expr->ts;
5825       declared = ts.u.derived;
5826       c = gfc_find_component (declared, "_vptr", true, true);
5827       if (c->ts.u.derived == NULL)
5828         c->ts.u.derived = gfc_find_derived_vtab (declared);
5829
5830       if (resolve_compcall (e, &name) == FAILURE)
5831         return FAILURE;
5832
5833       /* Use the generic name if it is there.  */
5834       name = name ? name : e->value.function.esym->name;
5835       e->symtree = expr->symtree;
5836       e->ref = gfc_copy_ref (expr->ref);
5837       gfc_add_vptr_component (e);
5838       gfc_add_component_ref (e, name);
5839       e->value.function.esym = NULL;
5840       return SUCCESS;
5841     }
5842
5843   if (st == NULL)
5844     return resolve_compcall (e, NULL);
5845
5846   if (resolve_ref (e) == FAILURE)
5847     return FAILURE;
5848
5849   /* Get the CLASS declared type.  */
5850   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5851
5852   /* Weed out cases of the ultimate component being a derived type.  */
5853   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5854          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5855     {
5856       gfc_free_ref_list (new_ref);
5857       return resolve_compcall (e, NULL);
5858     }
5859
5860   c = gfc_find_component (declared, "_data", true, true);
5861   declared = c->ts.u.derived;
5862
5863   /* Treat the call as if it is a typebound procedure, in order to roll
5864      out the correct name for the specific function.  */
5865   if (resolve_compcall (e, &name) == FAILURE)
5866     return FAILURE;
5867   ts = e->ts;
5868
5869   /* Then convert the expression to a procedure pointer component call.  */
5870   e->value.function.esym = NULL;
5871   e->symtree = st;
5872
5873   if (new_ref)  
5874     e->ref = new_ref;
5875
5876   /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5877   gfc_add_vptr_component (e);
5878   gfc_add_component_ref (e, name);
5879
5880   /* Recover the typespec for the expression.  This is really only
5881      necessary for generic procedures, where the additional call
5882      to gfc_add_component_ref seems to throw the collection of the
5883      correct typespec.  */
5884   e->ts = ts;
5885   return SUCCESS;
5886 }
5887
5888 /* Resolve a typebound subroutine, or 'method'. First separate all
5889    the non-CLASS references by calling resolve_typebound_call
5890    directly.  */
5891
5892 static gfc_try
5893 resolve_typebound_subroutine (gfc_code *code)
5894 {
5895   gfc_symbol *declared;
5896   gfc_component *c;
5897   gfc_ref *new_ref;
5898   gfc_ref *class_ref;
5899   gfc_symtree *st;
5900   const char *name;
5901   gfc_typespec ts;
5902   gfc_expr *expr;
5903
5904   st = code->expr1->symtree;
5905
5906   /* Deal with typebound operators for CLASS objects.  */
5907   expr = code->expr1->value.compcall.base_object;
5908   if (expr && expr->ts.type == BT_CLASS && code->expr1->value.compcall.name)
5909     {
5910       /* Since the typebound operators are generic, we have to ensure
5911          that any delays in resolution are corrected and that the vtab
5912          is present.  */
5913       declared = expr->ts.u.derived;
5914       c = gfc_find_component (declared, "_vptr", true, true);
5915       if (c->ts.u.derived == NULL)
5916         c->ts.u.derived = gfc_find_derived_vtab (declared);
5917
5918       if (resolve_typebound_call (code, &name) == FAILURE)
5919         return FAILURE;
5920
5921       /* Use the generic name if it is there.  */
5922       name = name ? name : code->expr1->value.function.esym->name;
5923       code->expr1->symtree = expr->symtree;
5924       code->expr1->ref = gfc_copy_ref (expr->ref);
5925       gfc_add_vptr_component (code->expr1);
5926       gfc_add_component_ref (code->expr1, name);
5927       code->expr1->value.function.esym = NULL;
5928       return SUCCESS;
5929     }
5930
5931   if (st == NULL)
5932     return resolve_typebound_call (code, NULL);
5933
5934   if (resolve_ref (code->expr1) == FAILURE)
5935     return FAILURE;
5936
5937   /* Get the CLASS declared type.  */
5938   get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5939
5940   /* Weed out cases of the ultimate component being a derived type.  */
5941   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5942          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5943     {
5944       gfc_free_ref_list (new_ref);
5945       return resolve_typebound_call (code, NULL);
5946     }
5947
5948   if (resolve_typebound_call (code, &name) == FAILURE)
5949     return FAILURE;
5950   ts = code->expr1->ts;
5951
5952   /* Then convert the expression to a procedure pointer component call.  */
5953   code->expr1->value.function.esym = NULL;
5954   code->expr1->symtree = st;
5955
5956   if (new_ref)
5957     code->expr1->ref = new_ref;
5958
5959   /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5960   gfc_add_vptr_component (code->expr1);
5961   gfc_add_component_ref (code->expr1, name);
5962
5963   /* Recover the typespec for the expression.  This is really only
5964      necessary for generic procedures, where the additional call
5965      to gfc_add_component_ref seems to throw the collection of the
5966      correct typespec.  */
5967   code->expr1->ts = ts;
5968   return SUCCESS;
5969 }
5970
5971
5972 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5973
5974 static gfc_try
5975 resolve_ppc_call (gfc_code* c)
5976 {
5977   gfc_component *comp;
5978   bool b;
5979
5980   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5981   gcc_assert (b);
5982
5983   c->resolved_sym = c->expr1->symtree->n.sym;
5984   c->expr1->expr_type = EXPR_VARIABLE;
5985
5986   if (!comp->attr.subroutine)
5987     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5988
5989   if (resolve_ref (c->expr1) == FAILURE)
5990     return FAILURE;
5991
5992   if (update_ppc_arglist (c->expr1) == FAILURE)
5993     return FAILURE;
5994
5995   c->ext.actual = c->expr1->value.compcall.actual;
5996
5997   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5998                               comp->formal == NULL) == FAILURE)
5999     return FAILURE;
6000
6001   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
6002
6003   return SUCCESS;
6004 }
6005
6006
6007 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
6008
6009 static gfc_try
6010 resolve_expr_ppc (gfc_expr* e)
6011 {
6012   gfc_component *comp;
6013   bool b;
6014
6015   b = gfc_is_proc_ptr_comp (e, &comp);
6016   gcc_assert (b);
6017
6018   /* Convert to EXPR_FUNCTION.  */
6019   e->expr_type = EXPR_FUNCTION;
6020   e->value.function.isym = NULL;
6021   e->value.function.actual = e->value.compcall.actual;
6022   e->ts = comp->ts;
6023   if (comp->as != NULL)
6024     e->rank = comp->as->rank;
6025
6026   if (!comp->attr.function)
6027     gfc_add_function (&comp->attr, comp->name, &e->where);
6028
6029   if (resolve_ref (e) == FAILURE)
6030     return FAILURE;
6031
6032   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
6033                               comp->formal == NULL) == FAILURE)
6034     return FAILURE;
6035
6036   if (update_ppc_arglist (e) == FAILURE)
6037     return FAILURE;
6038
6039   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
6040
6041   return SUCCESS;
6042 }
6043
6044
6045 static bool
6046 gfc_is_expandable_expr (gfc_expr *e)
6047 {
6048   gfc_constructor *con;
6049
6050   if (e->expr_type == EXPR_ARRAY)
6051     {
6052       /* Traverse the constructor looking for variables that are flavor
6053          parameter.  Parameters must be expanded since they are fully used at
6054          compile time.  */
6055       con = gfc_constructor_first (e->value.constructor);
6056       for (; con; con = gfc_constructor_next (con))
6057         {
6058           if (con->expr->expr_type == EXPR_VARIABLE
6059               && con->expr->symtree
6060               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
6061               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
6062             return true;
6063           if (con->expr->expr_type == EXPR_ARRAY
6064               && gfc_is_expandable_expr (con->expr))
6065             return true;
6066         }
6067     }
6068
6069   return false;
6070 }
6071
6072 /* Resolve an expression.  That is, make sure that types of operands agree
6073    with their operators, intrinsic operators are converted to function calls
6074    for overloaded types and unresolved function references are resolved.  */
6075
6076 gfc_try
6077 gfc_resolve_expr (gfc_expr *e)
6078 {
6079   gfc_try t;
6080   bool inquiry_save;
6081
6082   if (e == NULL)
6083     return SUCCESS;
6084
6085   /* inquiry_argument only applies to variables.  */
6086   inquiry_save = inquiry_argument;
6087   if (e->expr_type != EXPR_VARIABLE)
6088     inquiry_argument = false;
6089
6090   switch (e->expr_type)
6091     {
6092     case EXPR_OP:
6093       t = resolve_operator (e);
6094       break;
6095
6096     case EXPR_FUNCTION:
6097     case EXPR_VARIABLE:
6098
6099       if (check_host_association (e))
6100         t = resolve_function (e);
6101       else
6102         {
6103           t = resolve_variable (e);
6104           if (t == SUCCESS)
6105             expression_rank (e);
6106         }
6107
6108       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6109           && e->ref->type != REF_SUBSTRING)
6110         gfc_resolve_substring_charlen (e);
6111
6112       break;
6113
6114     case EXPR_COMPCALL:
6115       t = resolve_typebound_function (e);
6116       break;
6117
6118     case EXPR_SUBSTRING:
6119       t = resolve_ref (e);
6120       break;
6121
6122     case EXPR_CONSTANT:
6123     case EXPR_NULL:
6124       t = SUCCESS;
6125       break;
6126
6127     case EXPR_PPC:
6128       t = resolve_expr_ppc (e);
6129       break;
6130
6131     case EXPR_ARRAY:
6132       t = FAILURE;
6133       if (resolve_ref (e) == FAILURE)
6134         break;
6135
6136       t = gfc_resolve_array_constructor (e);
6137       /* Also try to expand a constructor.  */
6138       if (t == SUCCESS)
6139         {
6140           expression_rank (e);
6141           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6142             gfc_expand_constructor (e, false);
6143         }
6144
6145       /* This provides the opportunity for the length of constructors with
6146          character valued function elements to propagate the string length
6147          to the expression.  */
6148       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
6149         {
6150           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6151              here rather then add a duplicate test for it above.  */ 
6152           gfc_expand_constructor (e, false);
6153           t = gfc_resolve_character_array_constructor (e);
6154         }
6155
6156       break;
6157
6158     case EXPR_STRUCTURE:
6159       t = resolve_ref (e);
6160       if (t == FAILURE)
6161         break;
6162
6163       t = resolve_structure_cons (e, 0);
6164       if (t == FAILURE)
6165         break;
6166
6167       t = gfc_simplify_expr (e, 0);
6168       break;
6169
6170     default:
6171       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6172     }
6173
6174   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
6175     fixup_charlen (e);
6176
6177   inquiry_argument = inquiry_save;
6178
6179   return t;
6180 }
6181
6182
6183 /* Resolve an expression from an iterator.  They must be scalar and have
6184    INTEGER or (optionally) REAL type.  */
6185
6186 static gfc_try
6187 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6188                            const char *name_msgid)
6189 {
6190   if (gfc_resolve_expr (expr) == FAILURE)
6191     return FAILURE;
6192
6193   if (expr->rank != 0)
6194     {
6195       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6196       return FAILURE;
6197     }
6198
6199   if (expr->ts.type != BT_INTEGER)
6200     {
6201       if (expr->ts.type == BT_REAL)
6202         {
6203           if (real_ok)
6204             return gfc_notify_std (GFC_STD_F95_DEL,
6205                                    "Deleted feature: %s at %L must be integer",
6206                                    _(name_msgid), &expr->where);
6207           else
6208             {
6209               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6210                          &expr->where);
6211               return FAILURE;
6212             }
6213         }
6214       else
6215         {
6216           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6217           return FAILURE;
6218         }
6219     }
6220   return SUCCESS;
6221 }
6222
6223
6224 /* Resolve the expressions in an iterator structure.  If REAL_OK is
6225    false allow only INTEGER type iterators, otherwise allow REAL types.  */
6226
6227 gfc_try
6228 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
6229 {
6230   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
6231       == FAILURE)
6232     return FAILURE;
6233
6234   if (gfc_check_vardef_context (iter->var, false, _("iterator variable"))
6235       == FAILURE)
6236     return FAILURE;
6237
6238   if (gfc_resolve_iterator_expr (iter->start, real_ok,
6239                                  "Start expression in DO loop") == FAILURE)
6240     return FAILURE;
6241
6242   if (gfc_resolve_iterator_expr (iter->end, real_ok,
6243                                  "End expression in DO loop") == FAILURE)
6244     return FAILURE;
6245
6246   if (gfc_resolve_iterator_expr (iter->step, real_ok,
6247                                  "Step expression in DO loop") == FAILURE)
6248     return FAILURE;
6249
6250   if (iter->step->expr_type == EXPR_CONSTANT)
6251     {
6252       if ((iter->step->ts.type == BT_INTEGER
6253            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6254           || (iter->step->ts.type == BT_REAL
6255               && mpfr_sgn (iter->step->value.real) == 0))
6256         {
6257           gfc_error ("Step expression in DO loop at %L cannot be zero",
6258                      &iter->step->where);
6259           return FAILURE;
6260         }
6261     }
6262
6263   /* Convert start, end, and step to the same type as var.  */
6264   if (iter->start->ts.kind != iter->var->ts.kind
6265       || iter->start->ts.type != iter->var->ts.type)
6266     gfc_convert_type (iter->start, &iter->var->ts, 2);
6267
6268   if (iter->end->ts.kind != iter->var->ts.kind
6269       || iter->end->ts.type != iter->var->ts.type)
6270     gfc_convert_type (iter->end, &iter->var->ts, 2);
6271
6272   if (iter->step->ts.kind != iter->var->ts.kind
6273       || iter->step->ts.type != iter->var->ts.type)
6274     gfc_convert_type (iter->step, &iter->var->ts, 2);
6275
6276   if (iter->start->expr_type == EXPR_CONSTANT
6277       && iter->end->expr_type == EXPR_CONSTANT
6278       && iter->step->expr_type == EXPR_CONSTANT)
6279     {
6280       int sgn, cmp;
6281       if (iter->start->ts.type == BT_INTEGER)
6282         {
6283           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6284           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6285         }
6286       else
6287         {
6288           sgn = mpfr_sgn (iter->step->value.real);
6289           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6290         }
6291       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
6292         gfc_warning ("DO loop at %L will be executed zero times",
6293                      &iter->step->where);
6294     }
6295
6296   return SUCCESS;
6297 }
6298
6299
6300 /* Traversal function for find_forall_index.  f == 2 signals that
6301    that variable itself is not to be checked - only the references.  */
6302
6303 static bool
6304 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6305 {
6306   if (expr->expr_type != EXPR_VARIABLE)
6307     return false;
6308   
6309   /* A scalar assignment  */
6310   if (!expr->ref || *f == 1)
6311     {
6312       if (expr->symtree->n.sym == sym)
6313         return true;
6314       else
6315         return false;
6316     }
6317
6318   if (*f == 2)
6319     *f = 1;
6320   return false;
6321 }
6322
6323
6324 /* Check whether the FORALL index appears in the expression or not.
6325    Returns SUCCESS if SYM is found in EXPR.  */
6326
6327 gfc_try
6328 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6329 {
6330   if (gfc_traverse_expr (expr, sym, forall_index, f))
6331     return SUCCESS;
6332   else
6333     return FAILURE;
6334 }
6335
6336
6337 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6338    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6339    INTEGERs, and if stride is a constant it must be nonzero.
6340    Furthermore "A subscript or stride in a forall-triplet-spec shall
6341    not contain a reference to any index-name in the
6342    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6343
6344 static void
6345 resolve_forall_iterators (gfc_forall_iterator *it)
6346 {
6347   gfc_forall_iterator *iter, *iter2;
6348
6349   for (iter = it; iter; iter = iter->next)
6350     {
6351       if (gfc_resolve_expr (iter->var) == SUCCESS
6352           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6353         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6354                    &iter->var->where);
6355
6356       if (gfc_resolve_expr (iter->start) == SUCCESS
6357           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6358         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6359                    &iter->start->where);
6360       if (iter->var->ts.kind != iter->start->ts.kind)
6361         gfc_convert_type (iter->start, &iter->var->ts, 2);
6362
6363       if (gfc_resolve_expr (iter->end) == SUCCESS
6364           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6365         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6366                    &iter->end->where);
6367       if (iter->var->ts.kind != iter->end->ts.kind)
6368         gfc_convert_type (iter->end, &iter->var->ts, 2);
6369
6370       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6371         {
6372           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6373             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6374                        &iter->stride->where, "INTEGER");
6375
6376           if (iter->stride->expr_type == EXPR_CONSTANT
6377               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6378             gfc_error ("FORALL stride expression at %L cannot be zero",
6379                        &iter->stride->where);
6380         }
6381       if (iter->var->ts.kind != iter->stride->ts.kind)
6382         gfc_convert_type (iter->stride, &iter->var->ts, 2);
6383     }
6384
6385   for (iter = it; iter; iter = iter->next)
6386     for (iter2 = iter; iter2; iter2 = iter2->next)
6387       {
6388         if (find_forall_index (iter2->start,
6389                                iter->var->symtree->n.sym, 0) == SUCCESS
6390             || find_forall_index (iter2->end,
6391                                   iter->var->symtree->n.sym, 0) == SUCCESS
6392             || find_forall_index (iter2->stride,
6393                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6394           gfc_error ("FORALL index '%s' may not appear in triplet "
6395                      "specification at %L", iter->var->symtree->name,
6396                      &iter2->start->where);
6397       }
6398 }
6399
6400
6401 /* Given a pointer to a symbol that is a derived type, see if it's
6402    inaccessible, i.e. if it's defined in another module and the components are
6403    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6404    inaccessible components are found, nonzero otherwise.  */
6405
6406 static int
6407 derived_inaccessible (gfc_symbol *sym)
6408 {
6409   gfc_component *c;
6410
6411   if (sym->attr.use_assoc && sym->attr.private_comp)
6412     return 1;
6413
6414   for (c = sym->components; c; c = c->next)
6415     {
6416         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6417           return 1;
6418     }
6419
6420   return 0;
6421 }
6422
6423
6424 /* Resolve the argument of a deallocate expression.  The expression must be
6425    a pointer or a full array.  */
6426
6427 static gfc_try
6428 resolve_deallocate_expr (gfc_expr *e)
6429 {
6430   symbol_attribute attr;
6431   int allocatable, pointer;
6432   gfc_ref *ref;
6433   gfc_symbol *sym;
6434   gfc_component *c;
6435
6436   if (gfc_resolve_expr (e) == FAILURE)
6437     return FAILURE;
6438
6439   if (e->expr_type != EXPR_VARIABLE)
6440     goto bad;
6441
6442   sym = e->symtree->n.sym;
6443
6444   if (sym->ts.type == BT_CLASS)
6445     {
6446       allocatable = CLASS_DATA (sym)->attr.allocatable;
6447       pointer = CLASS_DATA (sym)->attr.class_pointer;
6448     }
6449   else
6450     {
6451       allocatable = sym->attr.allocatable;
6452       pointer = sym->attr.pointer;
6453     }
6454   for (ref = e->ref; ref; ref = ref->next)
6455     {
6456       switch (ref->type)
6457         {
6458         case REF_ARRAY:
6459           if (ref->u.ar.type != AR_FULL)
6460             allocatable = 0;
6461           break;
6462
6463         case REF_COMPONENT:
6464           c = ref->u.c.component;
6465           if (c->ts.type == BT_CLASS)
6466             {
6467               allocatable = CLASS_DATA (c)->attr.allocatable;
6468               pointer = CLASS_DATA (c)->attr.class_pointer;
6469             }
6470           else
6471             {
6472               allocatable = c->attr.allocatable;
6473               pointer = c->attr.pointer;
6474             }
6475           break;
6476
6477         case REF_SUBSTRING:
6478           allocatable = 0;
6479           break;
6480         }
6481     }
6482
6483   attr = gfc_expr_attr (e);
6484
6485   if (allocatable == 0 && attr.pointer == 0)
6486     {
6487     bad:
6488       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6489                  &e->where);
6490       return FAILURE;
6491     }
6492
6493   if (pointer
6494       && gfc_check_vardef_context (e, true, _("DEALLOCATE object")) == FAILURE)
6495     return FAILURE;
6496   if (gfc_check_vardef_context (e, false, _("DEALLOCATE object")) == FAILURE)
6497     return FAILURE;
6498
6499   return SUCCESS;
6500 }
6501
6502
6503 /* Returns true if the expression e contains a reference to the symbol sym.  */
6504 static bool
6505 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6506 {
6507   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6508     return true;
6509
6510   return false;
6511 }
6512
6513 bool
6514 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6515 {
6516   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6517 }
6518
6519
6520 /* Given the expression node e for an allocatable/pointer of derived type to be
6521    allocated, get the expression node to be initialized afterwards (needed for
6522    derived types with default initializers, and derived types with allocatable
6523    components that need nullification.)  */
6524
6525 gfc_expr *
6526 gfc_expr_to_initialize (gfc_expr *e)
6527 {
6528   gfc_expr *result;
6529   gfc_ref *ref;
6530   int i;
6531
6532   result = gfc_copy_expr (e);
6533
6534   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6535   for (ref = result->ref; ref; ref = ref->next)
6536     if (ref->type == REF_ARRAY && ref->next == NULL)
6537       {
6538         ref->u.ar.type = AR_FULL;
6539
6540         for (i = 0; i < ref->u.ar.dimen; i++)
6541           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6542
6543         result->rank = ref->u.ar.dimen;
6544         break;
6545       }
6546
6547   return result;
6548 }
6549
6550
6551 /* If the last ref of an expression is an array ref, return a copy of the
6552    expression with that one removed.  Otherwise, a copy of the original
6553    expression.  This is used for allocate-expressions and pointer assignment
6554    LHS, where there may be an array specification that needs to be stripped
6555    off when using gfc_check_vardef_context.  */
6556
6557 static gfc_expr*
6558 remove_last_array_ref (gfc_expr* e)
6559 {
6560   gfc_expr* e2;
6561   gfc_ref** r;
6562
6563   e2 = gfc_copy_expr (e);
6564   for (r = &e2->ref; *r; r = &(*r)->next)
6565     if ((*r)->type == REF_ARRAY && !(*r)->next)
6566       {
6567         gfc_free_ref_list (*r);
6568         *r = NULL;
6569         break;
6570       }
6571
6572   return e2;
6573 }
6574
6575
6576 /* Used in resolve_allocate_expr to check that a allocation-object and
6577    a source-expr are conformable.  This does not catch all possible 
6578    cases; in particular a runtime checking is needed.  */
6579
6580 static gfc_try
6581 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6582 {
6583   gfc_ref *tail;
6584   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6585   
6586   /* First compare rank.  */
6587   if (tail && e1->rank != tail->u.ar.as->rank)
6588     {
6589       gfc_error ("Source-expr at %L must be scalar or have the "
6590                  "same rank as the allocate-object at %L",
6591                  &e1->where, &e2->where);
6592       return FAILURE;
6593     }
6594
6595   if (e1->shape)
6596     {
6597       int i;
6598       mpz_t s;
6599
6600       mpz_init (s);
6601
6602       for (i = 0; i < e1->rank; i++)
6603         {
6604           if (tail->u.ar.end[i])
6605             {
6606               mpz_set (s, tail->u.ar.end[i]->value.integer);
6607               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6608               mpz_add_ui (s, s, 1);
6609             }
6610           else
6611             {
6612               mpz_set (s, tail->u.ar.start[i]->value.integer);
6613             }
6614
6615           if (mpz_cmp (e1->shape[i], s) != 0)
6616             {
6617               gfc_error ("Source-expr at %L and allocate-object at %L must "
6618                          "have the same shape", &e1->where, &e2->where);
6619               mpz_clear (s);
6620               return FAILURE;
6621             }
6622         }
6623
6624       mpz_clear (s);
6625     }
6626
6627   return SUCCESS;
6628 }
6629
6630
6631 /* Resolve the expression in an ALLOCATE statement, doing the additional
6632    checks to see whether the expression is OK or not.  The expression must
6633    have a trailing array reference that gives the size of the array.  */
6634
6635 static gfc_try
6636 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6637 {
6638   int i, pointer, allocatable, dimension, is_abstract;
6639   int codimension;
6640   bool coindexed;
6641   symbol_attribute attr;
6642   gfc_ref *ref, *ref2;
6643   gfc_expr *e2;
6644   gfc_array_ref *ar;
6645   gfc_symbol *sym = NULL;
6646   gfc_alloc *a;
6647   gfc_component *c;
6648   gfc_try t;
6649
6650   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6651      checking of coarrays.  */
6652   for (ref = e->ref; ref; ref = ref->next)
6653     if (ref->next == NULL)
6654       break;
6655
6656   if (ref && ref->type == REF_ARRAY)
6657     ref->u.ar.in_allocate = true;
6658
6659   if (gfc_resolve_expr (e) == FAILURE)
6660     goto failure;
6661
6662   /* Make sure the expression is allocatable or a pointer.  If it is
6663      pointer, the next-to-last reference must be a pointer.  */
6664
6665   ref2 = NULL;
6666   if (e->symtree)
6667     sym = e->symtree->n.sym;
6668
6669   /* Check whether ultimate component is abstract and CLASS.  */
6670   is_abstract = 0;
6671
6672   if (e->expr_type != EXPR_VARIABLE)
6673     {
6674       allocatable = 0;
6675       attr = gfc_expr_attr (e);
6676       pointer = attr.pointer;
6677       dimension = attr.dimension;
6678       codimension = attr.codimension;
6679     }
6680   else
6681     {
6682       if (sym->ts.type == BT_CLASS)
6683         {
6684           allocatable = CLASS_DATA (sym)->attr.allocatable;
6685           pointer = CLASS_DATA (sym)->attr.class_pointer;
6686           dimension = CLASS_DATA (sym)->attr.dimension;
6687           codimension = CLASS_DATA (sym)->attr.codimension;
6688           is_abstract = CLASS_DATA (sym)->attr.abstract;
6689         }
6690       else
6691         {
6692           allocatable = sym->attr.allocatable;
6693           pointer = sym->attr.pointer;
6694           dimension = sym->attr.dimension;
6695           codimension = sym->attr.codimension;
6696         }
6697
6698       coindexed = false;
6699
6700       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6701         {
6702           switch (ref->type)
6703             {
6704               case REF_ARRAY:
6705                 if (ref->u.ar.codimen > 0)
6706                   {
6707                     int n;
6708                     for (n = ref->u.ar.dimen;
6709                          n < ref->u.ar.dimen + ref->u.ar.codimen; n++)
6710                       if (ref->u.ar.dimen_type[n] != DIMEN_THIS_IMAGE)
6711                         {
6712                           coindexed = true;
6713                           break;
6714                         }
6715                    }
6716
6717                 if (ref->next != NULL)
6718                   pointer = 0;
6719                 break;
6720
6721               case REF_COMPONENT:
6722                 /* F2008, C644.  */
6723                 if (coindexed)
6724                   {
6725                     gfc_error ("Coindexed allocatable object at %L",
6726                                &e->where);
6727                     goto failure;
6728                   }
6729
6730                 c = ref->u.c.component;
6731                 if (c->ts.type == BT_CLASS)
6732                   {
6733                     allocatable = CLASS_DATA (c)->attr.allocatable;
6734                     pointer = CLASS_DATA (c)->attr.class_pointer;
6735                     dimension = CLASS_DATA (c)->attr.dimension;
6736                     codimension = CLASS_DATA (c)->attr.codimension;
6737                     is_abstract = CLASS_DATA (c)->attr.abstract;
6738                   }
6739                 else
6740                   {
6741                     allocatable = c->attr.allocatable;
6742                     pointer = c->attr.pointer;
6743                     dimension = c->attr.dimension;
6744                     codimension = c->attr.codimension;
6745                     is_abstract = c->attr.abstract;
6746                   }
6747                 break;
6748
6749               case REF_SUBSTRING:
6750                 allocatable = 0;
6751                 pointer = 0;
6752                 break;
6753             }
6754         }
6755     }
6756
6757   if (allocatable == 0 && pointer == 0)
6758     {
6759       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6760                  &e->where);
6761       goto failure;
6762     }
6763
6764   /* Some checks for the SOURCE tag.  */
6765   if (code->expr3)
6766     {
6767       /* Check F03:C631.  */
6768       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6769         {
6770           gfc_error ("Type of entity at %L is type incompatible with "
6771                       "source-expr at %L", &e->where, &code->expr3->where);
6772           goto failure;
6773         }
6774
6775       /* Check F03:C632 and restriction following Note 6.18.  */
6776       if (code->expr3->rank > 0
6777           && conformable_arrays (code->expr3, e) == FAILURE)
6778         goto failure;
6779
6780       /* Check F03:C633.  */
6781       if (code->expr3->ts.kind != e->ts.kind)
6782         {
6783           gfc_error ("The allocate-object at %L and the source-expr at %L "
6784                       "shall have the same kind type parameter",
6785                       &e->where, &code->expr3->where);
6786           goto failure;
6787         }
6788     }
6789
6790   /* Check F08:C629.  */
6791   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
6792       && !code->expr3)
6793     {
6794       gcc_assert (e->ts.type == BT_CLASS);
6795       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6796                  "type-spec or source-expr", sym->name, &e->where);
6797       goto failure;
6798     }
6799
6800   /* In the variable definition context checks, gfc_expr_attr is used
6801      on the expression.  This is fooled by the array specification
6802      present in e, thus we have to eliminate that one temporarily.  */
6803   e2 = remove_last_array_ref (e);
6804   t = SUCCESS;
6805   if (t == SUCCESS && pointer)
6806     t = gfc_check_vardef_context (e2, true, _("ALLOCATE object"));
6807   if (t == SUCCESS)
6808     t = gfc_check_vardef_context (e2, false, _("ALLOCATE object"));
6809   gfc_free_expr (e2);
6810   if (t == FAILURE)
6811     goto failure;
6812
6813   if (!code->expr3)
6814     {
6815       /* Set up default initializer if needed.  */
6816       gfc_typespec ts;
6817       gfc_expr *init_e;
6818
6819       if (code->ext.alloc.ts.type == BT_DERIVED)
6820         ts = code->ext.alloc.ts;
6821       else
6822         ts = e->ts;
6823
6824       if (ts.type == BT_CLASS)
6825         ts = ts.u.derived->components->ts;
6826
6827       if (ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&ts)))
6828         {
6829           gfc_code *init_st = gfc_get_code ();
6830           init_st->loc = code->loc;
6831           init_st->op = EXEC_INIT_ASSIGN;
6832           init_st->expr1 = gfc_expr_to_initialize (e);
6833           init_st->expr2 = init_e;
6834           init_st->next = code->next;
6835           code->next = init_st;
6836         }
6837     }
6838   else if (code->expr3->mold && code->expr3->ts.type == BT_DERIVED)
6839     {
6840       /* Default initialization via MOLD (non-polymorphic).  */
6841       gfc_expr *rhs = gfc_default_initializer (&code->expr3->ts);
6842       gfc_resolve_expr (rhs);
6843       gfc_free_expr (code->expr3);
6844       code->expr3 = rhs;
6845     }
6846
6847   if (e->ts.type == BT_CLASS)
6848     {
6849       /* Make sure the vtab symbol is present when
6850          the module variables are generated.  */
6851       gfc_typespec ts = e->ts;
6852       if (code->expr3)
6853         ts = code->expr3->ts;
6854       else if (code->ext.alloc.ts.type == BT_DERIVED)
6855         ts = code->ext.alloc.ts;
6856       gfc_find_derived_vtab (ts.u.derived);
6857     }
6858
6859   if (pointer || (dimension == 0 && codimension == 0))
6860     goto success;
6861
6862   /* Make sure the last reference node is an array specifiction.  */
6863
6864   if (!ref2 || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
6865       || (dimension && ref2->u.ar.dimen == 0))
6866     {
6867       gfc_error ("Array specification required in ALLOCATE statement "
6868                  "at %L", &e->where);
6869       goto failure;
6870     }
6871
6872   /* Make sure that the array section reference makes sense in the
6873     context of an ALLOCATE specification.  */
6874
6875   ar = &ref2->u.ar;
6876
6877   if (codimension)
6878     for (i = ar->dimen; i < ar->dimen + ar->codimen; i++)
6879       if (ar->dimen_type[i] == DIMEN_THIS_IMAGE)
6880         {
6881           gfc_error ("Coarray specification required in ALLOCATE statement "
6882                      "at %L", &e->where);
6883           goto failure;
6884         }
6885
6886   for (i = 0; i < ar->dimen; i++)
6887     {
6888       if (ref2->u.ar.type == AR_ELEMENT)
6889         goto check_symbols;
6890
6891       switch (ar->dimen_type[i])
6892         {
6893         case DIMEN_ELEMENT:
6894           break;
6895
6896         case DIMEN_RANGE:
6897           if (ar->start[i] != NULL
6898               && ar->end[i] != NULL
6899               && ar->stride[i] == NULL)
6900             break;
6901
6902           /* Fall Through...  */
6903
6904         case DIMEN_UNKNOWN:
6905         case DIMEN_VECTOR:
6906         case DIMEN_STAR:
6907         case DIMEN_THIS_IMAGE:
6908           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6909                      &e->where);
6910           goto failure;
6911         }
6912
6913 check_symbols:
6914       for (a = code->ext.alloc.list; a; a = a->next)
6915         {
6916           sym = a->expr->symtree->n.sym;
6917
6918           /* TODO - check derived type components.  */
6919           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6920             continue;
6921
6922           if ((ar->start[i] != NULL
6923                && gfc_find_sym_in_expr (sym, ar->start[i]))
6924               || (ar->end[i] != NULL
6925                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6926             {
6927               gfc_error ("'%s' must not appear in the array specification at "
6928                          "%L in the same ALLOCATE statement where it is "
6929                          "itself allocated", sym->name, &ar->where);
6930               goto failure;
6931             }
6932         }
6933     }
6934
6935   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
6936     {
6937       if (ar->dimen_type[i] == DIMEN_ELEMENT
6938           || ar->dimen_type[i] == DIMEN_RANGE)
6939         {
6940           if (i == (ar->dimen + ar->codimen - 1))
6941             {
6942               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
6943                          "statement at %L", &e->where);
6944               goto failure;
6945             }
6946           break;
6947         }
6948
6949       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
6950           && ar->stride[i] == NULL)
6951         break;
6952
6953       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
6954                  &e->where);
6955       goto failure;
6956     }
6957
6958   if (codimension && ar->as->rank == 0)
6959     {
6960       gfc_error ("Sorry, allocatable scalar coarrays are not yet supported "
6961                  "at %L", &e->where);
6962       goto failure;
6963     }
6964
6965 success:
6966   return SUCCESS;
6967
6968 failure:
6969   return FAILURE;
6970 }
6971
6972 static void
6973 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6974 {
6975   gfc_expr *stat, *errmsg, *pe, *qe;
6976   gfc_alloc *a, *p, *q;
6977
6978   stat = code->expr1;
6979   errmsg = code->expr2;
6980
6981   /* Check the stat variable.  */
6982   if (stat)
6983     {
6984       gfc_check_vardef_context (stat, false, _("STAT variable"));
6985
6986       if ((stat->ts.type != BT_INTEGER
6987            && !(stat->ref && (stat->ref->type == REF_ARRAY
6988                               || stat->ref->type == REF_COMPONENT)))
6989           || stat->rank > 0)
6990         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6991                    "variable", &stat->where);
6992
6993       for (p = code->ext.alloc.list; p; p = p->next)
6994         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6995           {
6996             gfc_ref *ref1, *ref2;
6997             bool found = true;
6998
6999             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
7000                  ref1 = ref1->next, ref2 = ref2->next)
7001               {
7002                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7003                   continue;
7004                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7005                   {
7006                     found = false;
7007                     break;
7008                   }
7009               }
7010
7011             if (found)
7012               {
7013                 gfc_error ("Stat-variable at %L shall not be %sd within "
7014                            "the same %s statement", &stat->where, fcn, fcn);
7015                 break;
7016               }
7017           }
7018     }
7019
7020   /* Check the errmsg variable.  */
7021   if (errmsg)
7022     {
7023       if (!stat)
7024         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
7025                      &errmsg->where);
7026
7027       gfc_check_vardef_context (errmsg, false, _("ERRMSG variable"));
7028
7029       if ((errmsg->ts.type != BT_CHARACTER
7030            && !(errmsg->ref
7031                 && (errmsg->ref->type == REF_ARRAY
7032                     || errmsg->ref->type == REF_COMPONENT)))
7033           || errmsg->rank > 0 )
7034         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
7035                    "variable", &errmsg->where);
7036
7037       for (p = code->ext.alloc.list; p; p = p->next)
7038         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
7039           {
7040             gfc_ref *ref1, *ref2;
7041             bool found = true;
7042
7043             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
7044                  ref1 = ref1->next, ref2 = ref2->next)
7045               {
7046                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7047                   continue;
7048                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7049                   {
7050                     found = false;
7051                     break;
7052                   }
7053               }
7054
7055             if (found)
7056               {
7057                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
7058                            "the same %s statement", &errmsg->where, fcn, fcn);
7059                 break;
7060               }
7061           }
7062     }
7063
7064   /* Check that an allocate-object appears only once in the statement.  
7065      FIXME: Checking derived types is disabled.  */
7066   for (p = code->ext.alloc.list; p; p = p->next)
7067     {
7068       pe = p->expr;
7069       for (q = p->next; q; q = q->next)
7070         {
7071           qe = q->expr;
7072           if (pe->symtree->n.sym->name == qe->symtree->n.sym->name)
7073             {
7074               /* This is a potential collision.  */
7075               gfc_ref *pr = pe->ref;
7076               gfc_ref *qr = qe->ref;
7077               
7078               /* Follow the references  until
7079                  a) They start to differ, in which case there is no error;
7080                  you can deallocate a%b and a%c in a single statement
7081                  b) Both of them stop, which is an error
7082                  c) One of them stops, which is also an error.  */
7083               while (1)
7084                 {
7085                   if (pr == NULL && qr == NULL)
7086                     {
7087                       gfc_error ("Allocate-object at %L also appears at %L",
7088                                  &pe->where, &qe->where);
7089                       break;
7090                     }
7091                   else if (pr != NULL && qr == NULL)
7092                     {
7093                       gfc_error ("Allocate-object at %L is subobject of"
7094                                  " object at %L", &pe->where, &qe->where);
7095                       break;
7096                     }
7097                   else if (pr == NULL && qr != NULL)
7098                     {
7099                       gfc_error ("Allocate-object at %L is subobject of"
7100                                  " object at %L", &qe->where, &pe->where);
7101                       break;
7102                     }
7103                   /* Here, pr != NULL && qr != NULL  */
7104                   gcc_assert(pr->type == qr->type);
7105                   if (pr->type == REF_ARRAY)
7106                     {
7107                       /* Handle cases like allocate(v(3)%x(3), v(2)%x(3)),
7108                          which are legal.  */
7109                       gcc_assert (qr->type == REF_ARRAY);
7110
7111                       if (pr->next && qr->next)
7112                         {
7113                           gfc_array_ref *par = &(pr->u.ar);
7114                           gfc_array_ref *qar = &(qr->u.ar);
7115                           if (gfc_dep_compare_expr (par->start[0],
7116                                                     qar->start[0]) != 0)
7117                               break;
7118                         }
7119                     }
7120                   else
7121                     {
7122                       if (pr->u.c.component->name != qr->u.c.component->name)
7123                         break;
7124                     }
7125                   
7126                   pr = pr->next;
7127                   qr = qr->next;
7128                 }
7129             }
7130         }
7131     }
7132
7133   if (strcmp (fcn, "ALLOCATE") == 0)
7134     {
7135       for (a = code->ext.alloc.list; a; a = a->next)
7136         resolve_allocate_expr (a->expr, code);
7137     }
7138   else
7139     {
7140       for (a = code->ext.alloc.list; a; a = a->next)
7141         resolve_deallocate_expr (a->expr);
7142     }
7143 }
7144
7145
7146 /************ SELECT CASE resolution subroutines ************/
7147
7148 /* Callback function for our mergesort variant.  Determines interval
7149    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7150    op1 > op2.  Assumes we're not dealing with the default case.  
7151    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7152    There are nine situations to check.  */
7153
7154 static int
7155 compare_cases (const gfc_case *op1, const gfc_case *op2)
7156 {
7157   int retval;
7158
7159   if (op1->low == NULL) /* op1 = (:L)  */
7160     {
7161       /* op2 = (:N), so overlap.  */
7162       retval = 0;
7163       /* op2 = (M:) or (M:N),  L < M  */
7164       if (op2->low != NULL
7165           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7166         retval = -1;
7167     }
7168   else if (op1->high == NULL) /* op1 = (K:)  */
7169     {
7170       /* op2 = (M:), so overlap.  */
7171       retval = 0;
7172       /* op2 = (:N) or (M:N), K > N  */
7173       if (op2->high != NULL
7174           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7175         retval = 1;
7176     }
7177   else /* op1 = (K:L)  */
7178     {
7179       if (op2->low == NULL)       /* op2 = (:N), K > N  */
7180         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7181                  ? 1 : 0;
7182       else if (op2->high == NULL) /* op2 = (M:), L < M  */
7183         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7184                  ? -1 : 0;
7185       else                      /* op2 = (M:N)  */
7186         {
7187           retval =  0;
7188           /* L < M  */
7189           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7190             retval =  -1;
7191           /* K > N  */
7192           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7193             retval =  1;
7194         }
7195     }
7196
7197   return retval;
7198 }
7199
7200
7201 /* Merge-sort a double linked case list, detecting overlap in the
7202    process.  LIST is the head of the double linked case list before it
7203    is sorted.  Returns the head of the sorted list if we don't see any
7204    overlap, or NULL otherwise.  */
7205
7206 static gfc_case *
7207 check_case_overlap (gfc_case *list)
7208 {
7209   gfc_case *p, *q, *e, *tail;
7210   int insize, nmerges, psize, qsize, cmp, overlap_seen;
7211
7212   /* If the passed list was empty, return immediately.  */
7213   if (!list)
7214     return NULL;
7215
7216   overlap_seen = 0;
7217   insize = 1;
7218
7219   /* Loop unconditionally.  The only exit from this loop is a return
7220      statement, when we've finished sorting the case list.  */
7221   for (;;)
7222     {
7223       p = list;
7224       list = NULL;
7225       tail = NULL;
7226
7227       /* Count the number of merges we do in this pass.  */
7228       nmerges = 0;
7229
7230       /* Loop while there exists a merge to be done.  */
7231       while (p)
7232         {
7233           int i;
7234
7235           /* Count this merge.  */
7236           nmerges++;
7237
7238           /* Cut the list in two pieces by stepping INSIZE places
7239              forward in the list, starting from P.  */
7240           psize = 0;
7241           q = p;
7242           for (i = 0; i < insize; i++)
7243             {
7244               psize++;
7245               q = q->right;
7246               if (!q)
7247                 break;
7248             }
7249           qsize = insize;
7250
7251           /* Now we have two lists.  Merge them!  */
7252           while (psize > 0 || (qsize > 0 && q != NULL))
7253             {
7254               /* See from which the next case to merge comes from.  */
7255               if (psize == 0)
7256                 {
7257                   /* P is empty so the next case must come from Q.  */
7258                   e = q;
7259                   q = q->right;
7260                   qsize--;
7261                 }
7262               else if (qsize == 0 || q == NULL)
7263                 {
7264                   /* Q is empty.  */
7265                   e = p;
7266                   p = p->right;
7267                   psize--;
7268                 }
7269               else
7270                 {
7271                   cmp = compare_cases (p, q);
7272                   if (cmp < 0)
7273                     {
7274                       /* The whole case range for P is less than the
7275                          one for Q.  */
7276                       e = p;
7277                       p = p->right;
7278                       psize--;
7279                     }
7280                   else if (cmp > 0)
7281                     {
7282                       /* The whole case range for Q is greater than
7283                          the case range for P.  */
7284                       e = q;
7285                       q = q->right;
7286                       qsize--;
7287                     }
7288                   else
7289                     {
7290                       /* The cases overlap, or they are the same
7291                          element in the list.  Either way, we must
7292                          issue an error and get the next case from P.  */
7293                       /* FIXME: Sort P and Q by line number.  */
7294                       gfc_error ("CASE label at %L overlaps with CASE "
7295                                  "label at %L", &p->where, &q->where);
7296                       overlap_seen = 1;
7297                       e = p;
7298                       p = p->right;
7299                       psize--;
7300                     }
7301                 }
7302
7303                 /* Add the next element to the merged list.  */
7304               if (tail)
7305                 tail->right = e;
7306               else
7307                 list = e;
7308               e->left = tail;
7309               tail = e;
7310             }
7311
7312           /* P has now stepped INSIZE places along, and so has Q.  So
7313              they're the same.  */
7314           p = q;
7315         }
7316       tail->right = NULL;
7317
7318       /* If we have done only one merge or none at all, we've
7319          finished sorting the cases.  */
7320       if (nmerges <= 1)
7321         {
7322           if (!overlap_seen)
7323             return list;
7324           else
7325             return NULL;
7326         }
7327
7328       /* Otherwise repeat, merging lists twice the size.  */
7329       insize *= 2;
7330     }
7331 }
7332
7333
7334 /* Check to see if an expression is suitable for use in a CASE statement.
7335    Makes sure that all case expressions are scalar constants of the same
7336    type.  Return FAILURE if anything is wrong.  */
7337
7338 static gfc_try
7339 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7340 {
7341   if (e == NULL) return SUCCESS;
7342
7343   if (e->ts.type != case_expr->ts.type)
7344     {
7345       gfc_error ("Expression in CASE statement at %L must be of type %s",
7346                  &e->where, gfc_basic_typename (case_expr->ts.type));
7347       return FAILURE;
7348     }
7349
7350   /* C805 (R808) For a given case-construct, each case-value shall be of
7351      the same type as case-expr.  For character type, length differences
7352      are allowed, but the kind type parameters shall be the same.  */
7353
7354   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7355     {
7356       gfc_error ("Expression in CASE statement at %L must be of kind %d",
7357                  &e->where, case_expr->ts.kind);
7358       return FAILURE;
7359     }
7360
7361   /* Convert the case value kind to that of case expression kind,
7362      if needed */
7363
7364   if (e->ts.kind != case_expr->ts.kind)
7365     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7366
7367   if (e->rank != 0)
7368     {
7369       gfc_error ("Expression in CASE statement at %L must be scalar",
7370                  &e->where);
7371       return FAILURE;
7372     }
7373
7374   return SUCCESS;
7375 }
7376
7377
7378 /* Given a completely parsed select statement, we:
7379
7380      - Validate all expressions and code within the SELECT.
7381      - Make sure that the selection expression is not of the wrong type.
7382      - Make sure that no case ranges overlap.
7383      - Eliminate unreachable cases and unreachable code resulting from
7384        removing case labels.
7385
7386    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7387    they are a hassle for code generation, and to prevent that, we just
7388    cut them out here.  This is not necessary for overlapping cases
7389    because they are illegal and we never even try to generate code.
7390
7391    We have the additional caveat that a SELECT construct could have
7392    been a computed GOTO in the source code. Fortunately we can fairly
7393    easily work around that here: The case_expr for a "real" SELECT CASE
7394    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7395    we have to do is make sure that the case_expr is a scalar integer
7396    expression.  */
7397
7398 static void
7399 resolve_select (gfc_code *code)
7400 {
7401   gfc_code *body;
7402   gfc_expr *case_expr;
7403   gfc_case *cp, *default_case, *tail, *head;
7404   int seen_unreachable;
7405   int seen_logical;
7406   int ncases;
7407   bt type;
7408   gfc_try t;
7409
7410   if (code->expr1 == NULL)
7411     {
7412       /* This was actually a computed GOTO statement.  */
7413       case_expr = code->expr2;
7414       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7415         gfc_error ("Selection expression in computed GOTO statement "
7416                    "at %L must be a scalar integer expression",
7417                    &case_expr->where);
7418
7419       /* Further checking is not necessary because this SELECT was built
7420          by the compiler, so it should always be OK.  Just move the
7421          case_expr from expr2 to expr so that we can handle computed
7422          GOTOs as normal SELECTs from here on.  */
7423       code->expr1 = code->expr2;
7424       code->expr2 = NULL;
7425       return;
7426     }
7427
7428   case_expr = code->expr1;
7429
7430   type = case_expr->ts.type;
7431   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7432     {
7433       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7434                  &case_expr->where, gfc_typename (&case_expr->ts));
7435
7436       /* Punt. Going on here just produce more garbage error messages.  */
7437       return;
7438     }
7439
7440   if (case_expr->rank != 0)
7441     {
7442       gfc_error ("Argument of SELECT statement at %L must be a scalar "
7443                  "expression", &case_expr->where);
7444
7445       /* Punt.  */
7446       return;
7447     }
7448
7449
7450   /* Raise a warning if an INTEGER case value exceeds the range of
7451      the case-expr. Later, all expressions will be promoted to the
7452      largest kind of all case-labels.  */
7453
7454   if (type == BT_INTEGER)
7455     for (body = code->block; body; body = body->block)
7456       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7457         {
7458           if (cp->low
7459               && gfc_check_integer_range (cp->low->value.integer,
7460                                           case_expr->ts.kind) != ARITH_OK)
7461             gfc_warning ("Expression in CASE statement at %L is "
7462                          "not in the range of %s", &cp->low->where,
7463                          gfc_typename (&case_expr->ts));
7464
7465           if (cp->high
7466               && cp->low != cp->high
7467               && gfc_check_integer_range (cp->high->value.integer,
7468                                           case_expr->ts.kind) != ARITH_OK)
7469             gfc_warning ("Expression in CASE statement at %L is "
7470                          "not in the range of %s", &cp->high->where,
7471                          gfc_typename (&case_expr->ts));
7472         }
7473
7474   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7475      of the SELECT CASE expression and its CASE values.  Walk the lists
7476      of case values, and if we find a mismatch, promote case_expr to
7477      the appropriate kind.  */
7478
7479   if (type == BT_LOGICAL || type == BT_INTEGER)
7480     {
7481       for (body = code->block; body; body = body->block)
7482         {
7483           /* Walk the case label list.  */
7484           for (cp = body->ext.block.case_list; cp; cp = cp->next)
7485             {
7486               /* Intercept the DEFAULT case.  It does not have a kind.  */
7487               if (cp->low == NULL && cp->high == NULL)
7488                 continue;
7489
7490               /* Unreachable case ranges are discarded, so ignore.  */
7491               if (cp->low != NULL && cp->high != NULL
7492                   && cp->low != cp->high
7493                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7494                 continue;
7495
7496               if (cp->low != NULL
7497                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7498                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7499
7500               if (cp->high != NULL
7501                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7502                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7503             }
7504          }
7505     }
7506
7507   /* Assume there is no DEFAULT case.  */
7508   default_case = NULL;
7509   head = tail = NULL;
7510   ncases = 0;
7511   seen_logical = 0;
7512
7513   for (body = code->block; body; body = body->block)
7514     {
7515       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7516       t = SUCCESS;
7517       seen_unreachable = 0;
7518
7519       /* Walk the case label list, making sure that all case labels
7520          are legal.  */
7521       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7522         {
7523           /* Count the number of cases in the whole construct.  */
7524           ncases++;
7525
7526           /* Intercept the DEFAULT case.  */
7527           if (cp->low == NULL && cp->high == NULL)
7528             {
7529               if (default_case != NULL)
7530                 {
7531                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7532                              "by a second DEFAULT CASE at %L",
7533                              &default_case->where, &cp->where);
7534                   t = FAILURE;
7535                   break;
7536                 }
7537               else
7538                 {
7539                   default_case = cp;
7540                   continue;
7541                 }
7542             }
7543
7544           /* Deal with single value cases and case ranges.  Errors are
7545              issued from the validation function.  */
7546           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7547               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7548             {
7549               t = FAILURE;
7550               break;
7551             }
7552
7553           if (type == BT_LOGICAL
7554               && ((cp->low == NULL || cp->high == NULL)
7555                   || cp->low != cp->high))
7556             {
7557               gfc_error ("Logical range in CASE statement at %L is not "
7558                          "allowed", &cp->low->where);
7559               t = FAILURE;
7560               break;
7561             }
7562
7563           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7564             {
7565               int value;
7566               value = cp->low->value.logical == 0 ? 2 : 1;
7567               if (value & seen_logical)
7568                 {
7569                   gfc_error ("Constant logical value in CASE statement "
7570                              "is repeated at %L",
7571                              &cp->low->where);
7572                   t = FAILURE;
7573                   break;
7574                 }
7575               seen_logical |= value;
7576             }
7577
7578           if (cp->low != NULL && cp->high != NULL
7579               && cp->low != cp->high
7580               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7581             {
7582               if (gfc_option.warn_surprising)
7583                 gfc_warning ("Range specification at %L can never "
7584                              "be matched", &cp->where);
7585
7586               cp->unreachable = 1;
7587               seen_unreachable = 1;
7588             }
7589           else
7590             {
7591               /* If the case range can be matched, it can also overlap with
7592                  other cases.  To make sure it does not, we put it in a
7593                  double linked list here.  We sort that with a merge sort
7594                  later on to detect any overlapping cases.  */
7595               if (!head)
7596                 {
7597                   head = tail = cp;
7598                   head->right = head->left = NULL;
7599                 }
7600               else
7601                 {
7602                   tail->right = cp;
7603                   tail->right->left = tail;
7604                   tail = tail->right;
7605                   tail->right = NULL;
7606                 }
7607             }
7608         }
7609
7610       /* It there was a failure in the previous case label, give up
7611          for this case label list.  Continue with the next block.  */
7612       if (t == FAILURE)
7613         continue;
7614
7615       /* See if any case labels that are unreachable have been seen.
7616          If so, we eliminate them.  This is a bit of a kludge because
7617          the case lists for a single case statement (label) is a
7618          single forward linked lists.  */
7619       if (seen_unreachable)
7620       {
7621         /* Advance until the first case in the list is reachable.  */
7622         while (body->ext.block.case_list != NULL
7623                && body->ext.block.case_list->unreachable)
7624           {
7625             gfc_case *n = body->ext.block.case_list;
7626             body->ext.block.case_list = body->ext.block.case_list->next;
7627             n->next = NULL;
7628             gfc_free_case_list (n);
7629           }
7630
7631         /* Strip all other unreachable cases.  */
7632         if (body->ext.block.case_list)
7633           {
7634             for (cp = body->ext.block.case_list; cp->next; cp = cp->next)
7635               {
7636                 if (cp->next->unreachable)
7637                   {
7638                     gfc_case *n = cp->next;
7639                     cp->next = cp->next->next;
7640                     n->next = NULL;
7641                     gfc_free_case_list (n);
7642                   }
7643               }
7644           }
7645       }
7646     }
7647
7648   /* See if there were overlapping cases.  If the check returns NULL,
7649      there was overlap.  In that case we don't do anything.  If head
7650      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7651      then used during code generation for SELECT CASE constructs with
7652      a case expression of a CHARACTER type.  */
7653   if (head)
7654     {
7655       head = check_case_overlap (head);
7656
7657       /* Prepend the default_case if it is there.  */
7658       if (head != NULL && default_case)
7659         {
7660           default_case->left = NULL;
7661           default_case->right = head;
7662           head->left = default_case;
7663         }
7664     }
7665
7666   /* Eliminate dead blocks that may be the result if we've seen
7667      unreachable case labels for a block.  */
7668   for (body = code; body && body->block; body = body->block)
7669     {
7670       if (body->block->ext.block.case_list == NULL)
7671         {
7672           /* Cut the unreachable block from the code chain.  */
7673           gfc_code *c = body->block;
7674           body->block = c->block;
7675
7676           /* Kill the dead block, but not the blocks below it.  */
7677           c->block = NULL;
7678           gfc_free_statements (c);
7679         }
7680     }
7681
7682   /* More than two cases is legal but insane for logical selects.
7683      Issue a warning for it.  */
7684   if (gfc_option.warn_surprising && type == BT_LOGICAL
7685       && ncases > 2)
7686     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7687                  &code->loc);
7688 }
7689
7690
7691 /* Check if a derived type is extensible.  */
7692
7693 bool
7694 gfc_type_is_extensible (gfc_symbol *sym)
7695 {
7696   return !(sym->attr.is_bind_c || sym->attr.sequence);
7697 }
7698
7699
7700 /* Resolve an associate name:  Resolve target and ensure the type-spec is
7701    correct as well as possibly the array-spec.  */
7702
7703 static void
7704 resolve_assoc_var (gfc_symbol* sym, bool resolve_target)
7705 {
7706   gfc_expr* target;
7707
7708   gcc_assert (sym->assoc);
7709   gcc_assert (sym->attr.flavor == FL_VARIABLE);
7710
7711   /* If this is for SELECT TYPE, the target may not yet be set.  In that
7712      case, return.  Resolution will be called later manually again when
7713      this is done.  */
7714   target = sym->assoc->target;
7715   if (!target)
7716     return;
7717   gcc_assert (!sym->assoc->dangling);
7718
7719   if (resolve_target && gfc_resolve_expr (target) != SUCCESS)
7720     return;
7721
7722   /* For variable targets, we get some attributes from the target.  */
7723   if (target->expr_type == EXPR_VARIABLE)
7724     {
7725       gfc_symbol* tsym;
7726
7727       gcc_assert (target->symtree);
7728       tsym = target->symtree->n.sym;
7729
7730       sym->attr.asynchronous = tsym->attr.asynchronous;
7731       sym->attr.volatile_ = tsym->attr.volatile_;
7732
7733       sym->attr.target = (tsym->attr.target || tsym->attr.pointer);
7734     }
7735
7736   /* Get type if this was not already set.  Note that it can be
7737      some other type than the target in case this is a SELECT TYPE
7738      selector!  So we must not update when the type is already there.  */
7739   if (sym->ts.type == BT_UNKNOWN)
7740     sym->ts = target->ts;
7741   gcc_assert (sym->ts.type != BT_UNKNOWN);
7742
7743   /* See if this is a valid association-to-variable.  */
7744   sym->assoc->variable = (target->expr_type == EXPR_VARIABLE
7745                           && !gfc_has_vector_subscript (target));
7746
7747   /* Finally resolve if this is an array or not.  */
7748   if (sym->attr.dimension && target->rank == 0)
7749     {
7750       gfc_error ("Associate-name '%s' at %L is used as array",
7751                  sym->name, &sym->declared_at);
7752       sym->attr.dimension = 0;
7753       return;
7754     }
7755   if (target->rank > 0)
7756     sym->attr.dimension = 1;
7757
7758   if (sym->attr.dimension)
7759     {
7760       sym->as = gfc_get_array_spec ();
7761       sym->as->rank = target->rank;
7762       sym->as->type = AS_DEFERRED;
7763
7764       /* Target must not be coindexed, thus the associate-variable
7765          has no corank.  */
7766       sym->as->corank = 0;
7767     }
7768 }
7769
7770
7771 /* Resolve a SELECT TYPE statement.  */
7772
7773 static void
7774 resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
7775 {
7776   gfc_symbol *selector_type;
7777   gfc_code *body, *new_st, *if_st, *tail;
7778   gfc_code *class_is = NULL, *default_case = NULL;
7779   gfc_case *c;
7780   gfc_symtree *st;
7781   char name[GFC_MAX_SYMBOL_LEN];
7782   gfc_namespace *ns;
7783   int error = 0;
7784
7785   ns = code->ext.block.ns;
7786   gfc_resolve (ns);
7787
7788   /* Check for F03:C813.  */
7789   if (code->expr1->ts.type != BT_CLASS
7790       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
7791     {
7792       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
7793                  "at %L", &code->loc);
7794       return;
7795     }
7796
7797   if (code->expr2)
7798     {
7799       if (code->expr1->symtree->n.sym->attr.untyped)
7800         code->expr1->symtree->n.sym->ts = code->expr2->ts;
7801       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
7802     }
7803   else
7804     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
7805
7806   /* Loop over TYPE IS / CLASS IS cases.  */
7807   for (body = code->block; body; body = body->block)
7808     {
7809       c = body->ext.block.case_list;
7810
7811       /* Check F03:C815.  */
7812       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7813           && !gfc_type_is_extensible (c->ts.u.derived))
7814         {
7815           gfc_error ("Derived type '%s' at %L must be extensible",
7816                      c->ts.u.derived->name, &c->where);
7817           error++;
7818           continue;
7819         }
7820
7821       /* Check F03:C816.  */
7822       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7823           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
7824         {
7825           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
7826                      c->ts.u.derived->name, &c->where, selector_type->name);
7827           error++;
7828           continue;
7829         }
7830
7831       /* Intercept the DEFAULT case.  */
7832       if (c->ts.type == BT_UNKNOWN)
7833         {
7834           /* Check F03:C818.  */
7835           if (default_case)
7836             {
7837               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7838                          "by a second DEFAULT CASE at %L",
7839                          &default_case->ext.block.case_list->where, &c->where);
7840               error++;
7841               continue;
7842             }
7843
7844           default_case = body;
7845         }
7846     }
7847     
7848   if (error > 0)
7849     return;
7850
7851   /* Transform SELECT TYPE statement to BLOCK and associate selector to
7852      target if present.  If there are any EXIT statements referring to the
7853      SELECT TYPE construct, this is no problem because the gfc_code
7854      reference stays the same and EXIT is equally possible from the BLOCK
7855      it is changed to.  */
7856   code->op = EXEC_BLOCK;
7857   if (code->expr2)
7858     {
7859       gfc_association_list* assoc;
7860
7861       assoc = gfc_get_association_list ();
7862       assoc->st = code->expr1->symtree;
7863       assoc->target = gfc_copy_expr (code->expr2);
7864       /* assoc->variable will be set by resolve_assoc_var.  */
7865       
7866       code->ext.block.assoc = assoc;
7867       code->expr1->symtree->n.sym->assoc = assoc;
7868
7869       resolve_assoc_var (code->expr1->symtree->n.sym, false);
7870     }
7871   else
7872     code->ext.block.assoc = NULL;
7873
7874   /* Add EXEC_SELECT to switch on type.  */
7875   new_st = gfc_get_code ();
7876   new_st->op = code->op;
7877   new_st->expr1 = code->expr1;
7878   new_st->expr2 = code->expr2;
7879   new_st->block = code->block;
7880   code->expr1 = code->expr2 =  NULL;
7881   code->block = NULL;
7882   if (!ns->code)
7883     ns->code = new_st;
7884   else
7885     ns->code->next = new_st;
7886   code = new_st;
7887   code->op = EXEC_SELECT;
7888   gfc_add_vptr_component (code->expr1);
7889   gfc_add_hash_component (code->expr1);
7890
7891   /* Loop over TYPE IS / CLASS IS cases.  */
7892   for (body = code->block; body; body = body->block)
7893     {
7894       c = body->ext.block.case_list;
7895
7896       if (c->ts.type == BT_DERIVED)
7897         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
7898                                              c->ts.u.derived->hash_value);
7899
7900       else if (c->ts.type == BT_UNKNOWN)
7901         continue;
7902
7903       /* Associate temporary to selector.  This should only be done
7904          when this case is actually true, so build a new ASSOCIATE
7905          that does precisely this here (instead of using the
7906          'global' one).  */
7907
7908       if (c->ts.type == BT_CLASS)
7909         sprintf (name, "__tmp_class_%s", c->ts.u.derived->name);
7910       else
7911         sprintf (name, "__tmp_type_%s", c->ts.u.derived->name);
7912       st = gfc_find_symtree (ns->sym_root, name);
7913       gcc_assert (st->n.sym->assoc);
7914       st->n.sym->assoc->target = gfc_get_variable_expr (code->expr1->symtree);
7915       if (c->ts.type == BT_DERIVED)
7916         gfc_add_data_component (st->n.sym->assoc->target);
7917
7918       new_st = gfc_get_code ();
7919       new_st->op = EXEC_BLOCK;
7920       new_st->ext.block.ns = gfc_build_block_ns (ns);
7921       new_st->ext.block.ns->code = body->next;
7922       body->next = new_st;
7923
7924       /* Chain in the new list only if it is marked as dangling.  Otherwise
7925          there is a CASE label overlap and this is already used.  Just ignore,
7926          the error is diagonsed elsewhere.  */
7927       if (st->n.sym->assoc->dangling)
7928         {
7929           new_st->ext.block.assoc = st->n.sym->assoc;
7930           st->n.sym->assoc->dangling = 0;
7931         }
7932
7933       resolve_assoc_var (st->n.sym, false);
7934     }
7935     
7936   /* Take out CLASS IS cases for separate treatment.  */
7937   body = code;
7938   while (body && body->block)
7939     {
7940       if (body->block->ext.block.case_list->ts.type == BT_CLASS)
7941         {
7942           /* Add to class_is list.  */
7943           if (class_is == NULL)
7944             { 
7945               class_is = body->block;
7946               tail = class_is;
7947             }
7948           else
7949             {
7950               for (tail = class_is; tail->block; tail = tail->block) ;
7951               tail->block = body->block;
7952               tail = tail->block;
7953             }
7954           /* Remove from EXEC_SELECT list.  */
7955           body->block = body->block->block;
7956           tail->block = NULL;
7957         }
7958       else
7959         body = body->block;
7960     }
7961
7962   if (class_is)
7963     {
7964       gfc_symbol *vtab;
7965       
7966       if (!default_case)
7967         {
7968           /* Add a default case to hold the CLASS IS cases.  */
7969           for (tail = code; tail->block; tail = tail->block) ;
7970           tail->block = gfc_get_code ();
7971           tail = tail->block;
7972           tail->op = EXEC_SELECT_TYPE;
7973           tail->ext.block.case_list = gfc_get_case ();
7974           tail->ext.block.case_list->ts.type = BT_UNKNOWN;
7975           tail->next = NULL;
7976           default_case = tail;
7977         }
7978
7979       /* More than one CLASS IS block?  */
7980       if (class_is->block)
7981         {
7982           gfc_code **c1,*c2;
7983           bool swapped;
7984           /* Sort CLASS IS blocks by extension level.  */
7985           do
7986             {
7987               swapped = false;
7988               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
7989                 {
7990                   c2 = (*c1)->block;
7991                   /* F03:C817 (check for doubles).  */
7992                   if ((*c1)->ext.block.case_list->ts.u.derived->hash_value
7993                       == c2->ext.block.case_list->ts.u.derived->hash_value)
7994                     {
7995                       gfc_error ("Double CLASS IS block in SELECT TYPE "
7996                                  "statement at %L",
7997                                  &c2->ext.block.case_list->where);
7998                       return;
7999                     }
8000                   if ((*c1)->ext.block.case_list->ts.u.derived->attr.extension
8001                       < c2->ext.block.case_list->ts.u.derived->attr.extension)
8002                     {
8003                       /* Swap.  */
8004                       (*c1)->block = c2->block;
8005                       c2->block = *c1;
8006                       *c1 = c2;
8007                       swapped = true;
8008                     }
8009                 }
8010             }
8011           while (swapped);
8012         }
8013         
8014       /* Generate IF chain.  */
8015       if_st = gfc_get_code ();
8016       if_st->op = EXEC_IF;
8017       new_st = if_st;
8018       for (body = class_is; body; body = body->block)
8019         {
8020           new_st->block = gfc_get_code ();
8021           new_st = new_st->block;
8022           new_st->op = EXEC_IF;
8023           /* Set up IF condition: Call _gfortran_is_extension_of.  */
8024           new_st->expr1 = gfc_get_expr ();
8025           new_st->expr1->expr_type = EXPR_FUNCTION;
8026           new_st->expr1->ts.type = BT_LOGICAL;
8027           new_st->expr1->ts.kind = 4;
8028           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
8029           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
8030           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
8031           /* Set up arguments.  */
8032           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
8033           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
8034           new_st->expr1->value.function.actual->expr->where = code->loc;
8035           gfc_add_vptr_component (new_st->expr1->value.function.actual->expr);
8036           vtab = gfc_find_derived_vtab (body->ext.block.case_list->ts.u.derived);
8037           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
8038           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
8039           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
8040           new_st->next = body->next;
8041         }
8042         if (default_case->next)
8043           {
8044             new_st->block = gfc_get_code ();
8045             new_st = new_st->block;
8046             new_st->op = EXEC_IF;
8047             new_st->next = default_case->next;
8048           }
8049           
8050         /* Replace CLASS DEFAULT code by the IF chain.  */
8051         default_case->next = if_st;
8052     }
8053
8054   /* Resolve the internal code.  This can not be done earlier because
8055      it requires that the sym->assoc of selectors is set already.  */
8056   gfc_current_ns = ns;
8057   gfc_resolve_blocks (code->block, gfc_current_ns);
8058   gfc_current_ns = old_ns;
8059
8060   resolve_select (code);
8061 }
8062
8063
8064 /* Resolve a transfer statement. This is making sure that:
8065    -- a derived type being transferred has only non-pointer components
8066    -- a derived type being transferred doesn't have private components, unless 
8067       it's being transferred from the module where the type was defined
8068    -- we're not trying to transfer a whole assumed size array.  */
8069
8070 static void
8071 resolve_transfer (gfc_code *code)
8072 {
8073   gfc_typespec *ts;
8074   gfc_symbol *sym;
8075   gfc_ref *ref;
8076   gfc_expr *exp;
8077
8078   exp = code->expr1;
8079
8080   while (exp != NULL && exp->expr_type == EXPR_OP
8081          && exp->value.op.op == INTRINSIC_PARENTHESES)
8082     exp = exp->value.op.op1;
8083
8084   if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
8085                       && exp->expr_type != EXPR_FUNCTION))
8086     return;
8087
8088   /* If we are reading, the variable will be changed.  Note that
8089      code->ext.dt may be NULL if the TRANSFER is related to
8090      an INQUIRE statement -- but in this case, we are not reading, either.  */
8091   if (code->ext.dt && code->ext.dt->dt_io_kind->value.iokind == M_READ
8092       && gfc_check_vardef_context (exp, false, _("item in READ")) == FAILURE)
8093     return;
8094
8095   sym = exp->symtree->n.sym;
8096   ts = &sym->ts;
8097
8098   /* Go to actual component transferred.  */
8099   for (ref = exp->ref; ref; ref = ref->next)
8100     if (ref->type == REF_COMPONENT)
8101       ts = &ref->u.c.component->ts;
8102
8103   if (ts->type == BT_CLASS)
8104     {
8105       /* FIXME: Test for defined input/output.  */
8106       gfc_error ("Data transfer element at %L cannot be polymorphic unless "
8107                 "it is processed by a defined input/output procedure",
8108                 &code->loc);
8109       return;
8110     }
8111
8112   if (ts->type == BT_DERIVED)
8113     {
8114       /* Check that transferred derived type doesn't contain POINTER
8115          components.  */
8116       if (ts->u.derived->attr.pointer_comp)
8117         {
8118           gfc_error ("Data transfer element at %L cannot have "
8119                      "POINTER components", &code->loc);
8120           return;
8121         }
8122
8123       /* F08:C935.  */
8124       if (ts->u.derived->attr.proc_pointer_comp)
8125         {
8126           gfc_error ("Data transfer element at %L cannot have "
8127                      "procedure pointer components", &code->loc);
8128           return;
8129         }
8130
8131       if (ts->u.derived->attr.alloc_comp)
8132         {
8133           gfc_error ("Data transfer element at %L cannot have "
8134                      "ALLOCATABLE components", &code->loc);
8135           return;
8136         }
8137
8138       if (derived_inaccessible (ts->u.derived))
8139         {
8140           gfc_error ("Data transfer element at %L cannot have "
8141                      "PRIVATE components",&code->loc);
8142           return;
8143         }
8144     }
8145
8146   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
8147       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
8148     {
8149       gfc_error ("Data transfer element at %L cannot be a full reference to "
8150                  "an assumed-size array", &code->loc);
8151       return;
8152     }
8153 }
8154
8155
8156 /*********** Toplevel code resolution subroutines ***********/
8157
8158 /* Find the set of labels that are reachable from this block.  We also
8159    record the last statement in each block.  */
8160      
8161 static void
8162 find_reachable_labels (gfc_code *block)
8163 {
8164   gfc_code *c;
8165
8166   if (!block)
8167     return;
8168
8169   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
8170
8171   /* Collect labels in this block.  We don't keep those corresponding
8172      to END {IF|SELECT}, these are checked in resolve_branch by going
8173      up through the code_stack.  */
8174   for (c = block; c; c = c->next)
8175     {
8176       if (c->here && c->op != EXEC_END_BLOCK)
8177         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
8178     }
8179
8180   /* Merge with labels from parent block.  */
8181   if (cs_base->prev)
8182     {
8183       gcc_assert (cs_base->prev->reachable_labels);
8184       bitmap_ior_into (cs_base->reachable_labels,
8185                        cs_base->prev->reachable_labels);
8186     }
8187 }
8188
8189
8190 static void
8191 resolve_sync (gfc_code *code)
8192 {
8193   /* Check imageset. The * case matches expr1 == NULL.  */
8194   if (code->expr1)
8195     {
8196       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
8197         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
8198                    "INTEGER expression", &code->expr1->where);
8199       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
8200           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
8201         gfc_error ("Imageset argument at %L must between 1 and num_images()",
8202                    &code->expr1->where);
8203       else if (code->expr1->expr_type == EXPR_ARRAY
8204                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
8205         {
8206            gfc_constructor *cons;
8207            cons = gfc_constructor_first (code->expr1->value.constructor);
8208            for (; cons; cons = gfc_constructor_next (cons))
8209              if (cons->expr->expr_type == EXPR_CONSTANT
8210                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
8211                gfc_error ("Imageset argument at %L must between 1 and "
8212                           "num_images()", &cons->expr->where);
8213         }
8214     }
8215
8216   /* Check STAT.  */
8217   if (code->expr2
8218       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8219           || code->expr2->expr_type != EXPR_VARIABLE))
8220     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8221                &code->expr2->where);
8222
8223   /* Check ERRMSG.  */
8224   if (code->expr3
8225       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8226           || code->expr3->expr_type != EXPR_VARIABLE))
8227     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8228                &code->expr3->where);
8229 }
8230
8231
8232 /* Given a branch to a label, see if the branch is conforming.
8233    The code node describes where the branch is located.  */
8234
8235 static void
8236 resolve_branch (gfc_st_label *label, gfc_code *code)
8237 {
8238   code_stack *stack;
8239
8240   if (label == NULL)
8241     return;
8242
8243   /* Step one: is this a valid branching target?  */
8244
8245   if (label->defined == ST_LABEL_UNKNOWN)
8246     {
8247       gfc_error ("Label %d referenced at %L is never defined", label->value,
8248                  &label->where);
8249       return;
8250     }
8251
8252   if (label->defined != ST_LABEL_TARGET)
8253     {
8254       gfc_error ("Statement at %L is not a valid branch target statement "
8255                  "for the branch statement at %L", &label->where, &code->loc);
8256       return;
8257     }
8258
8259   /* Step two: make sure this branch is not a branch to itself ;-)  */
8260
8261   if (code->here == label)
8262     {
8263       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
8264       return;
8265     }
8266
8267   /* Step three:  See if the label is in the same block as the
8268      branching statement.  The hard work has been done by setting up
8269      the bitmap reachable_labels.  */
8270
8271   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8272     {
8273       /* Check now whether there is a CRITICAL construct; if so, check
8274          whether the label is still visible outside of the CRITICAL block,
8275          which is invalid.  */
8276       for (stack = cs_base; stack; stack = stack->prev)
8277         if (stack->current->op == EXEC_CRITICAL
8278             && bitmap_bit_p (stack->reachable_labels, label->value))
8279           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8280                       " at %L", &code->loc, &label->where);
8281
8282       return;
8283     }
8284
8285   /* Step four:  If we haven't found the label in the bitmap, it may
8286     still be the label of the END of the enclosing block, in which
8287     case we find it by going up the code_stack.  */
8288
8289   for (stack = cs_base; stack; stack = stack->prev)
8290     {
8291       if (stack->current->next && stack->current->next->here == label)
8292         break;
8293       if (stack->current->op == EXEC_CRITICAL)
8294         {
8295           /* Note: A label at END CRITICAL does not leave the CRITICAL
8296              construct as END CRITICAL is still part of it.  */
8297           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8298                       " at %L", &code->loc, &label->where);
8299           return;
8300         }
8301     }
8302
8303   if (stack)
8304     {
8305       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
8306       return;
8307     }
8308
8309   /* The label is not in an enclosing block, so illegal.  This was
8310      allowed in Fortran 66, so we allow it as extension.  No
8311      further checks are necessary in this case.  */
8312   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
8313                   "as the GOTO statement at %L", &label->where,
8314                   &code->loc);
8315   return;
8316 }
8317
8318
8319 /* Check whether EXPR1 has the same shape as EXPR2.  */
8320
8321 static gfc_try
8322 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8323 {
8324   mpz_t shape[GFC_MAX_DIMENSIONS];
8325   mpz_t shape2[GFC_MAX_DIMENSIONS];
8326   gfc_try result = FAILURE;
8327   int i;
8328
8329   /* Compare the rank.  */
8330   if (expr1->rank != expr2->rank)
8331     return result;
8332
8333   /* Compare the size of each dimension.  */
8334   for (i=0; i<expr1->rank; i++)
8335     {
8336       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
8337         goto ignore;
8338
8339       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
8340         goto ignore;
8341
8342       if (mpz_cmp (shape[i], shape2[i]))
8343         goto over;
8344     }
8345
8346   /* When either of the two expression is an assumed size array, we
8347      ignore the comparison of dimension sizes.  */
8348 ignore:
8349   result = SUCCESS;
8350
8351 over:
8352   for (i--; i >= 0; i--)
8353     {
8354       mpz_clear (shape[i]);
8355       mpz_clear (shape2[i]);
8356     }
8357   return result;
8358 }
8359
8360
8361 /* Check whether a WHERE assignment target or a WHERE mask expression
8362    has the same shape as the outmost WHERE mask expression.  */
8363
8364 static void
8365 resolve_where (gfc_code *code, gfc_expr *mask)
8366 {
8367   gfc_code *cblock;
8368   gfc_code *cnext;
8369   gfc_expr *e = NULL;
8370
8371   cblock = code->block;
8372
8373   /* Store the first WHERE mask-expr of the WHERE statement or construct.
8374      In case of nested WHERE, only the outmost one is stored.  */
8375   if (mask == NULL) /* outmost WHERE */
8376     e = cblock->expr1;
8377   else /* inner WHERE */
8378     e = mask;
8379
8380   while (cblock)
8381     {
8382       if (cblock->expr1)
8383         {
8384           /* Check if the mask-expr has a consistent shape with the
8385              outmost WHERE mask-expr.  */
8386           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
8387             gfc_error ("WHERE mask at %L has inconsistent shape",
8388                        &cblock->expr1->where);
8389          }
8390
8391       /* the assignment statement of a WHERE statement, or the first
8392          statement in where-body-construct of a WHERE construct */
8393       cnext = cblock->next;
8394       while (cnext)
8395         {
8396           switch (cnext->op)
8397             {
8398             /* WHERE assignment statement */
8399             case EXEC_ASSIGN:
8400
8401               /* Check shape consistent for WHERE assignment target.  */
8402               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
8403                gfc_error ("WHERE assignment target at %L has "
8404                           "inconsistent shape", &cnext->expr1->where);
8405               break;
8406
8407   
8408             case EXEC_ASSIGN_CALL:
8409               resolve_call (cnext);
8410               if (!cnext->resolved_sym->attr.elemental)
8411                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8412                           &cnext->ext.actual->expr->where);
8413               break;
8414
8415             /* WHERE or WHERE construct is part of a where-body-construct */
8416             case EXEC_WHERE:
8417               resolve_where (cnext, e);
8418               break;
8419
8420             default:
8421               gfc_error ("Unsupported statement inside WHERE at %L",
8422                          &cnext->loc);
8423             }
8424          /* the next statement within the same where-body-construct */
8425          cnext = cnext->next;
8426        }
8427     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8428     cblock = cblock->block;
8429   }
8430 }
8431
8432
8433 /* Resolve assignment in FORALL construct.
8434    NVAR is the number of FORALL index variables, and VAR_EXPR records the
8435    FORALL index variables.  */
8436
8437 static void
8438 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8439 {
8440   int n;
8441
8442   for (n = 0; n < nvar; n++)
8443     {
8444       gfc_symbol *forall_index;
8445
8446       forall_index = var_expr[n]->symtree->n.sym;
8447
8448       /* Check whether the assignment target is one of the FORALL index
8449          variable.  */
8450       if ((code->expr1->expr_type == EXPR_VARIABLE)
8451           && (code->expr1->symtree->n.sym == forall_index))
8452         gfc_error ("Assignment to a FORALL index variable at %L",
8453                    &code->expr1->where);
8454       else
8455         {
8456           /* If one of the FORALL index variables doesn't appear in the
8457              assignment variable, then there could be a many-to-one
8458              assignment.  Emit a warning rather than an error because the
8459              mask could be resolving this problem.  */
8460           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
8461             gfc_warning ("The FORALL with index '%s' is not used on the "
8462                          "left side of the assignment at %L and so might "
8463                          "cause multiple assignment to this object",
8464                          var_expr[n]->symtree->name, &code->expr1->where);
8465         }
8466     }
8467 }
8468
8469
8470 /* Resolve WHERE statement in FORALL construct.  */
8471
8472 static void
8473 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
8474                                   gfc_expr **var_expr)
8475 {
8476   gfc_code *cblock;
8477   gfc_code *cnext;
8478
8479   cblock = code->block;
8480   while (cblock)
8481     {
8482       /* the assignment statement of a WHERE statement, or the first
8483          statement in where-body-construct of a WHERE construct */
8484       cnext = cblock->next;
8485       while (cnext)
8486         {
8487           switch (cnext->op)
8488             {
8489             /* WHERE assignment statement */
8490             case EXEC_ASSIGN:
8491               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
8492               break;
8493   
8494             /* WHERE operator assignment statement */
8495             case EXEC_ASSIGN_CALL:
8496               resolve_call (cnext);
8497               if (!cnext->resolved_sym->attr.elemental)
8498                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8499                           &cnext->ext.actual->expr->where);
8500               break;
8501
8502             /* WHERE or WHERE construct is part of a where-body-construct */
8503             case EXEC_WHERE:
8504               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
8505               break;
8506
8507             default:
8508               gfc_error ("Unsupported statement inside WHERE at %L",
8509                          &cnext->loc);
8510             }
8511           /* the next statement within the same where-body-construct */
8512           cnext = cnext->next;
8513         }
8514       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8515       cblock = cblock->block;
8516     }
8517 }
8518
8519
8520 /* Traverse the FORALL body to check whether the following errors exist:
8521    1. For assignment, check if a many-to-one assignment happens.
8522    2. For WHERE statement, check the WHERE body to see if there is any
8523       many-to-one assignment.  */
8524
8525 static void
8526 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
8527 {
8528   gfc_code *c;
8529
8530   c = code->block->next;
8531   while (c)
8532     {
8533       switch (c->op)
8534         {
8535         case EXEC_ASSIGN:
8536         case EXEC_POINTER_ASSIGN:
8537           gfc_resolve_assign_in_forall (c, nvar, var_expr);
8538           break;
8539
8540         case EXEC_ASSIGN_CALL:
8541           resolve_call (c);
8542           break;
8543
8544         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
8545            there is no need to handle it here.  */
8546         case EXEC_FORALL:
8547           break;
8548         case EXEC_WHERE:
8549           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
8550           break;
8551         default:
8552           break;
8553         }
8554       /* The next statement in the FORALL body.  */
8555       c = c->next;
8556     }
8557 }
8558
8559
8560 /* Counts the number of iterators needed inside a forall construct, including
8561    nested forall constructs. This is used to allocate the needed memory 
8562    in gfc_resolve_forall.  */
8563
8564 static int 
8565 gfc_count_forall_iterators (gfc_code *code)
8566 {
8567   int max_iters, sub_iters, current_iters;
8568   gfc_forall_iterator *fa;
8569
8570   gcc_assert(code->op == EXEC_FORALL);
8571   max_iters = 0;
8572   current_iters = 0;
8573
8574   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8575     current_iters ++;
8576   
8577   code = code->block->next;
8578
8579   while (code)
8580     {          
8581       if (code->op == EXEC_FORALL)
8582         {
8583           sub_iters = gfc_count_forall_iterators (code);
8584           if (sub_iters > max_iters)
8585             max_iters = sub_iters;
8586         }
8587       code = code->next;
8588     }
8589
8590   return current_iters + max_iters;
8591 }
8592
8593
8594 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8595    gfc_resolve_forall_body to resolve the FORALL body.  */
8596
8597 static void
8598 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8599 {
8600   static gfc_expr **var_expr;
8601   static int total_var = 0;
8602   static int nvar = 0;
8603   int old_nvar, tmp;
8604   gfc_forall_iterator *fa;
8605   int i;
8606
8607   old_nvar = nvar;
8608
8609   /* Start to resolve a FORALL construct   */
8610   if (forall_save == 0)
8611     {
8612       /* Count the total number of FORALL index in the nested FORALL
8613          construct in order to allocate the VAR_EXPR with proper size.  */
8614       total_var = gfc_count_forall_iterators (code);
8615
8616       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8617       var_expr = XCNEWVEC (gfc_expr *, total_var);
8618     }
8619
8620   /* The information about FORALL iterator, including FORALL index start, end
8621      and stride. The FORALL index can not appear in start, end or stride.  */
8622   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8623     {
8624       /* Check if any outer FORALL index name is the same as the current
8625          one.  */
8626       for (i = 0; i < nvar; i++)
8627         {
8628           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8629             {
8630               gfc_error ("An outer FORALL construct already has an index "
8631                          "with this name %L", &fa->var->where);
8632             }
8633         }
8634
8635       /* Record the current FORALL index.  */
8636       var_expr[nvar] = gfc_copy_expr (fa->var);
8637
8638       nvar++;
8639
8640       /* No memory leak.  */
8641       gcc_assert (nvar <= total_var);
8642     }
8643
8644   /* Resolve the FORALL body.  */
8645   gfc_resolve_forall_body (code, nvar, var_expr);
8646
8647   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8648   gfc_resolve_blocks (code->block, ns);
8649
8650   tmp = nvar;
8651   nvar = old_nvar;
8652   /* Free only the VAR_EXPRs allocated in this frame.  */
8653   for (i = nvar; i < tmp; i++)
8654      gfc_free_expr (var_expr[i]);
8655
8656   if (nvar == 0)
8657     {
8658       /* We are in the outermost FORALL construct.  */
8659       gcc_assert (forall_save == 0);
8660
8661       /* VAR_EXPR is not needed any more.  */
8662       free (var_expr);
8663       total_var = 0;
8664     }
8665 }
8666
8667
8668 /* Resolve a BLOCK construct statement.  */
8669
8670 static void
8671 resolve_block_construct (gfc_code* code)
8672 {
8673   /* Resolve the BLOCK's namespace.  */
8674   gfc_resolve (code->ext.block.ns);
8675
8676   /* For an ASSOCIATE block, the associations (and their targets) are already
8677      resolved during resolve_symbol.  */
8678 }
8679
8680
8681 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
8682    DO code nodes.  */
8683
8684 static void resolve_code (gfc_code *, gfc_namespace *);
8685
8686 void
8687 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8688 {
8689   gfc_try t;
8690
8691   for (; b; b = b->block)
8692     {
8693       t = gfc_resolve_expr (b->expr1);
8694       if (gfc_resolve_expr (b->expr2) == FAILURE)
8695         t = FAILURE;
8696
8697       switch (b->op)
8698         {
8699         case EXEC_IF:
8700           if (t == SUCCESS && b->expr1 != NULL
8701               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8702             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8703                        &b->expr1->where);
8704           break;
8705
8706         case EXEC_WHERE:
8707           if (t == SUCCESS
8708               && b->expr1 != NULL
8709               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8710             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8711                        &b->expr1->where);
8712           break;
8713
8714         case EXEC_GOTO:
8715           resolve_branch (b->label1, b);
8716           break;
8717
8718         case EXEC_BLOCK:
8719           resolve_block_construct (b);
8720           break;
8721
8722         case EXEC_SELECT:
8723         case EXEC_SELECT_TYPE:
8724         case EXEC_FORALL:
8725         case EXEC_DO:
8726         case EXEC_DO_WHILE:
8727         case EXEC_CRITICAL:
8728         case EXEC_READ:
8729         case EXEC_WRITE:
8730         case EXEC_IOLENGTH:
8731         case EXEC_WAIT:
8732           break;
8733
8734         case EXEC_OMP_ATOMIC:
8735         case EXEC_OMP_CRITICAL:
8736         case EXEC_OMP_DO:
8737         case EXEC_OMP_MASTER:
8738         case EXEC_OMP_ORDERED:
8739         case EXEC_OMP_PARALLEL:
8740         case EXEC_OMP_PARALLEL_DO:
8741         case EXEC_OMP_PARALLEL_SECTIONS:
8742         case EXEC_OMP_PARALLEL_WORKSHARE:
8743         case EXEC_OMP_SECTIONS:
8744         case EXEC_OMP_SINGLE:
8745         case EXEC_OMP_TASK:
8746         case EXEC_OMP_TASKWAIT:
8747         case EXEC_OMP_WORKSHARE:
8748           break;
8749
8750         default:
8751           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
8752         }
8753
8754       resolve_code (b->next, ns);
8755     }
8756 }
8757
8758
8759 /* Does everything to resolve an ordinary assignment.  Returns true
8760    if this is an interface assignment.  */
8761 static bool
8762 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
8763 {
8764   bool rval = false;
8765   gfc_expr *lhs;
8766   gfc_expr *rhs;
8767   int llen = 0;
8768   int rlen = 0;
8769   int n;
8770   gfc_ref *ref;
8771
8772   if (gfc_extend_assign (code, ns) == SUCCESS)
8773     {
8774       gfc_expr** rhsptr;
8775
8776       if (code->op == EXEC_ASSIGN_CALL)
8777         {
8778           lhs = code->ext.actual->expr;
8779           rhsptr = &code->ext.actual->next->expr;
8780         }
8781       else
8782         {
8783           gfc_actual_arglist* args;
8784           gfc_typebound_proc* tbp;
8785
8786           gcc_assert (code->op == EXEC_COMPCALL);
8787
8788           args = code->expr1->value.compcall.actual;
8789           lhs = args->expr;
8790           rhsptr = &args->next->expr;
8791
8792           tbp = code->expr1->value.compcall.tbp;
8793           gcc_assert (!tbp->is_generic);
8794         }
8795
8796       /* Make a temporary rhs when there is a default initializer
8797          and rhs is the same symbol as the lhs.  */
8798       if ((*rhsptr)->expr_type == EXPR_VARIABLE
8799             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
8800             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
8801             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
8802         *rhsptr = gfc_get_parentheses (*rhsptr);
8803
8804       return true;
8805     }
8806
8807   lhs = code->expr1;
8808   rhs = code->expr2;
8809
8810   if (rhs->is_boz
8811       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
8812                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
8813                          &code->loc) == FAILURE)
8814     return false;
8815
8816   /* Handle the case of a BOZ literal on the RHS.  */
8817   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
8818     {
8819       int rc;
8820       if (gfc_option.warn_surprising)
8821         gfc_warning ("BOZ literal at %L is bitwise transferred "
8822                      "non-integer symbol '%s'", &code->loc,
8823                      lhs->symtree->n.sym->name);
8824
8825       if (!gfc_convert_boz (rhs, &lhs->ts))
8826         return false;
8827       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
8828         {
8829           if (rc == ARITH_UNDERFLOW)
8830             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
8831                        ". This check can be disabled with the option "
8832                        "-fno-range-check", &rhs->where);
8833           else if (rc == ARITH_OVERFLOW)
8834             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
8835                        ". This check can be disabled with the option "
8836                        "-fno-range-check", &rhs->where);
8837           else if (rc == ARITH_NAN)
8838             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
8839                        ". This check can be disabled with the option "
8840                        "-fno-range-check", &rhs->where);
8841           return false;
8842         }
8843     }
8844
8845   if (lhs->ts.type == BT_CHARACTER
8846         && gfc_option.warn_character_truncation)
8847     {
8848       if (lhs->ts.u.cl != NULL
8849             && lhs->ts.u.cl->length != NULL
8850             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8851         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
8852
8853       if (rhs->expr_type == EXPR_CONSTANT)
8854         rlen = rhs->value.character.length;
8855
8856       else if (rhs->ts.u.cl != NULL
8857                  && rhs->ts.u.cl->length != NULL
8858                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8859         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
8860
8861       if (rlen && llen && rlen > llen)
8862         gfc_warning_now ("CHARACTER expression will be truncated "
8863                          "in assignment (%d/%d) at %L",
8864                          llen, rlen, &code->loc);
8865     }
8866
8867   /* Ensure that a vector index expression for the lvalue is evaluated
8868      to a temporary if the lvalue symbol is referenced in it.  */
8869   if (lhs->rank)
8870     {
8871       for (ref = lhs->ref; ref; ref= ref->next)
8872         if (ref->type == REF_ARRAY)
8873           {
8874             for (n = 0; n < ref->u.ar.dimen; n++)
8875               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
8876                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
8877                                            ref->u.ar.start[n]))
8878                 ref->u.ar.start[n]
8879                         = gfc_get_parentheses (ref->u.ar.start[n]);
8880           }
8881     }
8882
8883   if (gfc_pure (NULL))
8884     {
8885       if (lhs->ts.type == BT_DERIVED
8886             && lhs->expr_type == EXPR_VARIABLE
8887             && lhs->ts.u.derived->attr.pointer_comp
8888             && rhs->expr_type == EXPR_VARIABLE
8889             && (gfc_impure_variable (rhs->symtree->n.sym)
8890                 || gfc_is_coindexed (rhs)))
8891         {
8892           /* F2008, C1283.  */
8893           if (gfc_is_coindexed (rhs))
8894             gfc_error ("Coindexed expression at %L is assigned to "
8895                         "a derived type variable with a POINTER "
8896                         "component in a PURE procedure",
8897                         &rhs->where);
8898           else
8899             gfc_error ("The impure variable at %L is assigned to "
8900                         "a derived type variable with a POINTER "
8901                         "component in a PURE procedure (12.6)",
8902                         &rhs->where);
8903           return rval;
8904         }
8905
8906       /* Fortran 2008, C1283.  */
8907       if (gfc_is_coindexed (lhs))
8908         {
8909           gfc_error ("Assignment to coindexed variable at %L in a PURE "
8910                      "procedure", &rhs->where);
8911           return rval;
8912         }
8913     }
8914
8915   if (gfc_implicit_pure (NULL))
8916     {
8917       if (lhs->expr_type == EXPR_VARIABLE
8918             && lhs->symtree->n.sym != gfc_current_ns->proc_name
8919             && lhs->symtree->n.sym->ns != gfc_current_ns)
8920         gfc_current_ns->proc_name->attr.implicit_pure = 0;
8921
8922       if (lhs->ts.type == BT_DERIVED
8923             && lhs->expr_type == EXPR_VARIABLE
8924             && lhs->ts.u.derived->attr.pointer_comp
8925             && rhs->expr_type == EXPR_VARIABLE
8926             && (gfc_impure_variable (rhs->symtree->n.sym)
8927                 || gfc_is_coindexed (rhs)))
8928         gfc_current_ns->proc_name->attr.implicit_pure = 0;
8929
8930       /* Fortran 2008, C1283.  */
8931       if (gfc_is_coindexed (lhs))
8932         gfc_current_ns->proc_name->attr.implicit_pure = 0;
8933     }
8934
8935   /* F03:7.4.1.2.  */
8936   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
8937      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
8938   if (lhs->ts.type == BT_CLASS)
8939     {
8940       gfc_error ("Variable must not be polymorphic in assignment at %L",
8941                  &lhs->where);
8942       return false;
8943     }
8944
8945   /* F2008, Section 7.2.1.2.  */
8946   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
8947     {
8948       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
8949                  "component in assignment at %L", &lhs->where);
8950       return false;
8951     }
8952
8953   gfc_check_assign (lhs, rhs, 1);
8954   return false;
8955 }
8956
8957
8958 /* Given a block of code, recursively resolve everything pointed to by this
8959    code block.  */
8960
8961 static void
8962 resolve_code (gfc_code *code, gfc_namespace *ns)
8963 {
8964   int omp_workshare_save;
8965   int forall_save;
8966   code_stack frame;
8967   gfc_try t;
8968
8969   frame.prev = cs_base;
8970   frame.head = code;
8971   cs_base = &frame;
8972
8973   find_reachable_labels (code);
8974
8975   for (; code; code = code->next)
8976     {
8977       frame.current = code;
8978       forall_save = forall_flag;
8979
8980       if (code->op == EXEC_FORALL)
8981         {
8982           forall_flag = 1;
8983           gfc_resolve_forall (code, ns, forall_save);
8984           forall_flag = 2;
8985         }
8986       else if (code->block)
8987         {
8988           omp_workshare_save = -1;
8989           switch (code->op)
8990             {
8991             case EXEC_OMP_PARALLEL_WORKSHARE:
8992               omp_workshare_save = omp_workshare_flag;
8993               omp_workshare_flag = 1;
8994               gfc_resolve_omp_parallel_blocks (code, ns);
8995               break;
8996             case EXEC_OMP_PARALLEL:
8997             case EXEC_OMP_PARALLEL_DO:
8998             case EXEC_OMP_PARALLEL_SECTIONS:
8999             case EXEC_OMP_TASK:
9000               omp_workshare_save = omp_workshare_flag;
9001               omp_workshare_flag = 0;
9002               gfc_resolve_omp_parallel_blocks (code, ns);
9003               break;
9004             case EXEC_OMP_DO:
9005               gfc_resolve_omp_do_blocks (code, ns);
9006               break;
9007             case EXEC_SELECT_TYPE:
9008               /* Blocks are handled in resolve_select_type because we have
9009                  to transform the SELECT TYPE into ASSOCIATE first.  */
9010               break;
9011             case EXEC_OMP_WORKSHARE:
9012               omp_workshare_save = omp_workshare_flag;
9013               omp_workshare_flag = 1;
9014               /* FALLTHROUGH */
9015             default:
9016               gfc_resolve_blocks (code->block, ns);
9017               break;
9018             }
9019
9020           if (omp_workshare_save != -1)
9021             omp_workshare_flag = omp_workshare_save;
9022         }
9023
9024       t = SUCCESS;
9025       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
9026         t = gfc_resolve_expr (code->expr1);
9027       forall_flag = forall_save;
9028
9029       if (gfc_resolve_expr (code->expr2) == FAILURE)
9030         t = FAILURE;
9031
9032       if (code->op == EXEC_ALLOCATE
9033           && gfc_resolve_expr (code->expr3) == FAILURE)
9034         t = FAILURE;
9035
9036       switch (code->op)
9037         {
9038         case EXEC_NOP:
9039         case EXEC_END_BLOCK:
9040         case EXEC_CYCLE:
9041         case EXEC_PAUSE:
9042         case EXEC_STOP:
9043         case EXEC_ERROR_STOP:
9044         case EXEC_EXIT:
9045         case EXEC_CONTINUE:
9046         case EXEC_DT_END:
9047         case EXEC_ASSIGN_CALL:
9048         case EXEC_CRITICAL:
9049           break;
9050
9051         case EXEC_SYNC_ALL:
9052         case EXEC_SYNC_IMAGES:
9053         case EXEC_SYNC_MEMORY:
9054           resolve_sync (code);
9055           break;
9056
9057         case EXEC_ENTRY:
9058           /* Keep track of which entry we are up to.  */
9059           current_entry_id = code->ext.entry->id;
9060           break;
9061
9062         case EXEC_WHERE:
9063           resolve_where (code, NULL);
9064           break;
9065
9066         case EXEC_GOTO:
9067           if (code->expr1 != NULL)
9068             {
9069               if (code->expr1->ts.type != BT_INTEGER)
9070                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
9071                            "INTEGER variable", &code->expr1->where);
9072               else if (code->expr1->symtree->n.sym->attr.assign != 1)
9073                 gfc_error ("Variable '%s' has not been assigned a target "
9074                            "label at %L", code->expr1->symtree->n.sym->name,
9075                            &code->expr1->where);
9076             }
9077           else
9078             resolve_branch (code->label1, code);
9079           break;
9080
9081         case EXEC_RETURN:
9082           if (code->expr1 != NULL
9083                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
9084             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
9085                        "INTEGER return specifier", &code->expr1->where);
9086           break;
9087
9088         case EXEC_INIT_ASSIGN:
9089         case EXEC_END_PROCEDURE:
9090           break;
9091
9092         case EXEC_ASSIGN:
9093           if (t == FAILURE)
9094             break;
9095
9096           if (gfc_check_vardef_context (code->expr1, false, _("assignment"))
9097                 == FAILURE)
9098             break;
9099
9100           if (resolve_ordinary_assign (code, ns))
9101             {
9102               if (code->op == EXEC_COMPCALL)
9103                 goto compcall;
9104               else
9105                 goto call;
9106             }
9107           break;
9108
9109         case EXEC_LABEL_ASSIGN:
9110           if (code->label1->defined == ST_LABEL_UNKNOWN)
9111             gfc_error ("Label %d referenced at %L is never defined",
9112                        code->label1->value, &code->label1->where);
9113           if (t == SUCCESS
9114               && (code->expr1->expr_type != EXPR_VARIABLE
9115                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
9116                   || code->expr1->symtree->n.sym->ts.kind
9117                      != gfc_default_integer_kind
9118                   || code->expr1->symtree->n.sym->as != NULL))
9119             gfc_error ("ASSIGN statement at %L requires a scalar "
9120                        "default INTEGER variable", &code->expr1->where);
9121           break;
9122
9123         case EXEC_POINTER_ASSIGN:
9124           {
9125             gfc_expr* e;
9126
9127             if (t == FAILURE)
9128               break;
9129
9130             /* This is both a variable definition and pointer assignment
9131                context, so check both of them.  For rank remapping, a final
9132                array ref may be present on the LHS and fool gfc_expr_attr
9133                used in gfc_check_vardef_context.  Remove it.  */
9134             e = remove_last_array_ref (code->expr1);
9135             t = gfc_check_vardef_context (e, true, _("pointer assignment"));
9136             if (t == SUCCESS)
9137               t = gfc_check_vardef_context (e, false, _("pointer assignment"));
9138             gfc_free_expr (e);
9139             if (t == FAILURE)
9140               break;
9141
9142             gfc_check_pointer_assign (code->expr1, code->expr2);
9143             break;
9144           }
9145
9146         case EXEC_ARITHMETIC_IF:
9147           if (t == SUCCESS
9148               && code->expr1->ts.type != BT_INTEGER
9149               && code->expr1->ts.type != BT_REAL)
9150             gfc_error ("Arithmetic IF statement at %L requires a numeric "
9151                        "expression", &code->expr1->where);
9152
9153           resolve_branch (code->label1, code);
9154           resolve_branch (code->label2, code);
9155           resolve_branch (code->label3, code);
9156           break;
9157
9158         case EXEC_IF:
9159           if (t == SUCCESS && code->expr1 != NULL
9160               && (code->expr1->ts.type != BT_LOGICAL
9161                   || code->expr1->rank != 0))
9162             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9163                        &code->expr1->where);
9164           break;
9165
9166         case EXEC_CALL:
9167         call:
9168           resolve_call (code);
9169           break;
9170
9171         case EXEC_COMPCALL:
9172         compcall:
9173           resolve_typebound_subroutine (code);
9174           break;
9175
9176         case EXEC_CALL_PPC:
9177           resolve_ppc_call (code);
9178           break;
9179
9180         case EXEC_SELECT:
9181           /* Select is complicated. Also, a SELECT construct could be
9182              a transformed computed GOTO.  */
9183           resolve_select (code);
9184           break;
9185
9186         case EXEC_SELECT_TYPE:
9187           resolve_select_type (code, ns);
9188           break;
9189
9190         case EXEC_BLOCK:
9191           resolve_block_construct (code);
9192           break;
9193
9194         case EXEC_DO:
9195           if (code->ext.iterator != NULL)
9196             {
9197               gfc_iterator *iter = code->ext.iterator;
9198               if (gfc_resolve_iterator (iter, true) != FAILURE)
9199                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
9200             }
9201           break;
9202
9203         case EXEC_DO_WHILE:
9204           if (code->expr1 == NULL)
9205             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
9206           if (t == SUCCESS
9207               && (code->expr1->rank != 0
9208                   || code->expr1->ts.type != BT_LOGICAL))
9209             gfc_error ("Exit condition of DO WHILE loop at %L must be "
9210                        "a scalar LOGICAL expression", &code->expr1->where);
9211           break;
9212
9213         case EXEC_ALLOCATE:
9214           if (t == SUCCESS)
9215             resolve_allocate_deallocate (code, "ALLOCATE");
9216
9217           break;
9218
9219         case EXEC_DEALLOCATE:
9220           if (t == SUCCESS)
9221             resolve_allocate_deallocate (code, "DEALLOCATE");
9222
9223           break;
9224
9225         case EXEC_OPEN:
9226           if (gfc_resolve_open (code->ext.open) == FAILURE)
9227             break;
9228
9229           resolve_branch (code->ext.open->err, code);
9230           break;
9231
9232         case EXEC_CLOSE:
9233           if (gfc_resolve_close (code->ext.close) == FAILURE)
9234             break;
9235
9236           resolve_branch (code->ext.close->err, code);
9237           break;
9238
9239         case EXEC_BACKSPACE:
9240         case EXEC_ENDFILE:
9241         case EXEC_REWIND:
9242         case EXEC_FLUSH:
9243           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
9244             break;
9245
9246           resolve_branch (code->ext.filepos->err, code);
9247           break;
9248
9249         case EXEC_INQUIRE:
9250           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9251               break;
9252
9253           resolve_branch (code->ext.inquire->err, code);
9254           break;
9255
9256         case EXEC_IOLENGTH:
9257           gcc_assert (code->ext.inquire != NULL);
9258           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9259             break;
9260
9261           resolve_branch (code->ext.inquire->err, code);
9262           break;
9263
9264         case EXEC_WAIT:
9265           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
9266             break;
9267
9268           resolve_branch (code->ext.wait->err, code);
9269           resolve_branch (code->ext.wait->end, code);
9270           resolve_branch (code->ext.wait->eor, code);
9271           break;
9272
9273         case EXEC_READ:
9274         case EXEC_WRITE:
9275           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
9276             break;
9277
9278           resolve_branch (code->ext.dt->err, code);
9279           resolve_branch (code->ext.dt->end, code);
9280           resolve_branch (code->ext.dt->eor, code);
9281           break;
9282
9283         case EXEC_TRANSFER:
9284           resolve_transfer (code);
9285           break;
9286
9287         case EXEC_FORALL:
9288           resolve_forall_iterators (code->ext.forall_iterator);
9289
9290           if (code->expr1 != NULL
9291               && (code->expr1->ts.type != BT_LOGICAL || code->expr1->rank))
9292             gfc_error ("FORALL mask clause at %L requires a scalar LOGICAL "
9293                        "expression", &code->expr1->where);
9294           break;
9295
9296         case EXEC_OMP_ATOMIC:
9297         case EXEC_OMP_BARRIER:
9298         case EXEC_OMP_CRITICAL:
9299         case EXEC_OMP_FLUSH:
9300         case EXEC_OMP_DO:
9301         case EXEC_OMP_MASTER:
9302         case EXEC_OMP_ORDERED:
9303         case EXEC_OMP_SECTIONS:
9304         case EXEC_OMP_SINGLE:
9305         case EXEC_OMP_TASKWAIT:
9306         case EXEC_OMP_WORKSHARE:
9307           gfc_resolve_omp_directive (code, ns);
9308           break;
9309
9310         case EXEC_OMP_PARALLEL:
9311         case EXEC_OMP_PARALLEL_DO:
9312         case EXEC_OMP_PARALLEL_SECTIONS:
9313         case EXEC_OMP_PARALLEL_WORKSHARE:
9314         case EXEC_OMP_TASK:
9315           omp_workshare_save = omp_workshare_flag;
9316           omp_workshare_flag = 0;
9317           gfc_resolve_omp_directive (code, ns);
9318           omp_workshare_flag = omp_workshare_save;
9319           break;
9320
9321         default:
9322           gfc_internal_error ("resolve_code(): Bad statement code");
9323         }
9324     }
9325
9326   cs_base = frame.prev;
9327 }
9328
9329
9330 /* Resolve initial values and make sure they are compatible with
9331    the variable.  */
9332
9333 static void
9334 resolve_values (gfc_symbol *sym)
9335 {
9336   gfc_try t;
9337
9338   if (sym->value == NULL)
9339     return;
9340
9341   if (sym->value->expr_type == EXPR_STRUCTURE)
9342     t= resolve_structure_cons (sym->value, 1);
9343   else 
9344     t = gfc_resolve_expr (sym->value);
9345
9346   if (t == FAILURE)
9347     return;
9348
9349   gfc_check_assign_symbol (sym, sym->value);
9350 }
9351
9352
9353 /* Verify the binding labels for common blocks that are BIND(C).  The label
9354    for a BIND(C) common block must be identical in all scoping units in which
9355    the common block is declared.  Further, the binding label can not collide
9356    with any other global entity in the program.  */
9357
9358 static void
9359 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
9360 {
9361   if (comm_block_tree->n.common->is_bind_c == 1)
9362     {
9363       gfc_gsymbol *binding_label_gsym;
9364       gfc_gsymbol *comm_name_gsym;
9365
9366       /* See if a global symbol exists by the common block's name.  It may
9367          be NULL if the common block is use-associated.  */
9368       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
9369                                          comm_block_tree->n.common->name);
9370       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
9371         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
9372                    "with the global entity '%s' at %L",
9373                    comm_block_tree->n.common->binding_label,
9374                    comm_block_tree->n.common->name,
9375                    &(comm_block_tree->n.common->where),
9376                    comm_name_gsym->name, &(comm_name_gsym->where));
9377       else if (comm_name_gsym != NULL
9378                && strcmp (comm_name_gsym->name,
9379                           comm_block_tree->n.common->name) == 0)
9380         {
9381           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
9382              as expected.  */
9383           if (comm_name_gsym->binding_label == NULL)
9384             /* No binding label for common block stored yet; save this one.  */
9385             comm_name_gsym->binding_label =
9386               comm_block_tree->n.common->binding_label;
9387           else
9388             if (strcmp (comm_name_gsym->binding_label,
9389                         comm_block_tree->n.common->binding_label) != 0)
9390               {
9391                 /* Common block names match but binding labels do not.  */
9392                 gfc_error ("Binding label '%s' for common block '%s' at %L "
9393                            "does not match the binding label '%s' for common "
9394                            "block '%s' at %L",
9395                            comm_block_tree->n.common->binding_label,
9396                            comm_block_tree->n.common->name,
9397                            &(comm_block_tree->n.common->where),
9398                            comm_name_gsym->binding_label,
9399                            comm_name_gsym->name,
9400                            &(comm_name_gsym->where));
9401                 return;
9402               }
9403         }
9404
9405       /* There is no binding label (NAME="") so we have nothing further to
9406          check and nothing to add as a global symbol for the label.  */
9407       if (comm_block_tree->n.common->binding_label[0] == '\0' )
9408         return;
9409       
9410       binding_label_gsym =
9411         gfc_find_gsymbol (gfc_gsym_root,
9412                           comm_block_tree->n.common->binding_label);
9413       if (binding_label_gsym == NULL)
9414         {
9415           /* Need to make a global symbol for the binding label to prevent
9416              it from colliding with another.  */
9417           binding_label_gsym =
9418             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
9419           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
9420           binding_label_gsym->type = GSYM_COMMON;
9421         }
9422       else
9423         {
9424           /* If comm_name_gsym is NULL, the name common block is use
9425              associated and the name could be colliding.  */
9426           if (binding_label_gsym->type != GSYM_COMMON)
9427             gfc_error ("Binding label '%s' for common block '%s' at %L "
9428                        "collides with the global entity '%s' at %L",
9429                        comm_block_tree->n.common->binding_label,
9430                        comm_block_tree->n.common->name,
9431                        &(comm_block_tree->n.common->where),
9432                        binding_label_gsym->name,
9433                        &(binding_label_gsym->where));
9434           else if (comm_name_gsym != NULL
9435                    && (strcmp (binding_label_gsym->name,
9436                                comm_name_gsym->binding_label) != 0)
9437                    && (strcmp (binding_label_gsym->sym_name,
9438                                comm_name_gsym->name) != 0))
9439             gfc_error ("Binding label '%s' for common block '%s' at %L "
9440                        "collides with global entity '%s' at %L",
9441                        binding_label_gsym->name, binding_label_gsym->sym_name,
9442                        &(comm_block_tree->n.common->where),
9443                        comm_name_gsym->name, &(comm_name_gsym->where));
9444         }
9445     }
9446   
9447   return;
9448 }
9449
9450
9451 /* Verify any BIND(C) derived types in the namespace so we can report errors
9452    for them once, rather than for each variable declared of that type.  */
9453
9454 static void
9455 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
9456 {
9457   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
9458       && derived_sym->attr.is_bind_c == 1)
9459     verify_bind_c_derived_type (derived_sym);
9460   
9461   return;
9462 }
9463
9464
9465 /* Verify that any binding labels used in a given namespace do not collide 
9466    with the names or binding labels of any global symbols.  */
9467
9468 static void
9469 gfc_verify_binding_labels (gfc_symbol *sym)
9470 {
9471   int has_error = 0;
9472   
9473   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
9474       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
9475     {
9476       gfc_gsymbol *bind_c_sym;
9477
9478       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
9479       if (bind_c_sym != NULL 
9480           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
9481         {
9482           if (sym->attr.if_source == IFSRC_DECL 
9483               && (bind_c_sym->type != GSYM_SUBROUTINE 
9484                   && bind_c_sym->type != GSYM_FUNCTION) 
9485               && ((sym->attr.contained == 1 
9486                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
9487                   || (sym->attr.use_assoc == 1 
9488                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
9489             {
9490               /* Make sure global procedures don't collide with anything.  */
9491               gfc_error ("Binding label '%s' at %L collides with the global "
9492                          "entity '%s' at %L", sym->binding_label,
9493                          &(sym->declared_at), bind_c_sym->name,
9494                          &(bind_c_sym->where));
9495               has_error = 1;
9496             }
9497           else if (sym->attr.contained == 0 
9498                    && (sym->attr.if_source == IFSRC_IFBODY 
9499                        && sym->attr.flavor == FL_PROCEDURE) 
9500                    && (bind_c_sym->sym_name != NULL 
9501                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
9502             {
9503               /* Make sure procedures in interface bodies don't collide.  */
9504               gfc_error ("Binding label '%s' in interface body at %L collides "
9505                          "with the global entity '%s' at %L",
9506                          sym->binding_label,
9507                          &(sym->declared_at), bind_c_sym->name,
9508                          &(bind_c_sym->where));
9509               has_error = 1;
9510             }
9511           else if (sym->attr.contained == 0 
9512                    && sym->attr.if_source == IFSRC_UNKNOWN)
9513             if ((sym->attr.use_assoc && bind_c_sym->mod_name
9514                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
9515                 || sym->attr.use_assoc == 0)
9516               {
9517                 gfc_error ("Binding label '%s' at %L collides with global "
9518                            "entity '%s' at %L", sym->binding_label,
9519                            &(sym->declared_at), bind_c_sym->name,
9520                            &(bind_c_sym->where));
9521                 has_error = 1;
9522               }
9523
9524           if (has_error != 0)
9525             /* Clear the binding label to prevent checking multiple times.  */
9526             sym->binding_label[0] = '\0';
9527         }
9528       else if (bind_c_sym == NULL)
9529         {
9530           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
9531           bind_c_sym->where = sym->declared_at;
9532           bind_c_sym->sym_name = sym->name;
9533
9534           if (sym->attr.use_assoc == 1)
9535             bind_c_sym->mod_name = sym->module;
9536           else
9537             if (sym->ns->proc_name != NULL)
9538               bind_c_sym->mod_name = sym->ns->proc_name->name;
9539
9540           if (sym->attr.contained == 0)
9541             {
9542               if (sym->attr.subroutine)
9543                 bind_c_sym->type = GSYM_SUBROUTINE;
9544               else if (sym->attr.function)
9545                 bind_c_sym->type = GSYM_FUNCTION;
9546             }
9547         }
9548     }
9549   return;
9550 }
9551
9552
9553 /* Resolve an index expression.  */
9554
9555 static gfc_try
9556 resolve_index_expr (gfc_expr *e)
9557 {
9558   if (gfc_resolve_expr (e) == FAILURE)
9559     return FAILURE;
9560
9561   if (gfc_simplify_expr (e, 0) == FAILURE)
9562     return FAILURE;
9563
9564   if (gfc_specification_expr (e) == FAILURE)
9565     return FAILURE;
9566
9567   return SUCCESS;
9568 }
9569
9570
9571 /* Resolve a charlen structure.  */
9572
9573 static gfc_try
9574 resolve_charlen (gfc_charlen *cl)
9575 {
9576   int i, k;
9577
9578   if (cl->resolved)
9579     return SUCCESS;
9580
9581   cl->resolved = 1;
9582
9583   specification_expr = 1;
9584
9585   if (resolve_index_expr (cl->length) == FAILURE)
9586     {
9587       specification_expr = 0;
9588       return FAILURE;
9589     }
9590
9591   /* "If the character length parameter value evaluates to a negative
9592      value, the length of character entities declared is zero."  */
9593   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
9594     {
9595       if (gfc_option.warn_surprising)
9596         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
9597                          " the length has been set to zero",
9598                          &cl->length->where, i);
9599       gfc_replace_expr (cl->length,
9600                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
9601     }
9602
9603   /* Check that the character length is not too large.  */
9604   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
9605   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
9606       && cl->length->ts.type == BT_INTEGER
9607       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
9608     {
9609       gfc_error ("String length at %L is too large", &cl->length->where);
9610       return FAILURE;
9611     }
9612
9613   return SUCCESS;
9614 }
9615
9616
9617 /* Test for non-constant shape arrays.  */
9618
9619 static bool
9620 is_non_constant_shape_array (gfc_symbol *sym)
9621 {
9622   gfc_expr *e;
9623   int i;
9624   bool not_constant;
9625
9626   not_constant = false;
9627   if (sym->as != NULL)
9628     {
9629       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
9630          has not been simplified; parameter array references.  Do the
9631          simplification now.  */
9632       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
9633         {
9634           e = sym->as->lower[i];
9635           if (e && (resolve_index_expr (e) == FAILURE
9636                     || !gfc_is_constant_expr (e)))
9637             not_constant = true;
9638           e = sym->as->upper[i];
9639           if (e && (resolve_index_expr (e) == FAILURE
9640                     || !gfc_is_constant_expr (e)))
9641             not_constant = true;
9642         }
9643     }
9644   return not_constant;
9645 }
9646
9647 /* Given a symbol and an initialization expression, add code to initialize
9648    the symbol to the function entry.  */
9649 static void
9650 build_init_assign (gfc_symbol *sym, gfc_expr *init)
9651 {
9652   gfc_expr *lval;
9653   gfc_code *init_st;
9654   gfc_namespace *ns = sym->ns;
9655
9656   /* Search for the function namespace if this is a contained
9657      function without an explicit result.  */
9658   if (sym->attr.function && sym == sym->result
9659       && sym->name != sym->ns->proc_name->name)
9660     {
9661       ns = ns->contained;
9662       for (;ns; ns = ns->sibling)
9663         if (strcmp (ns->proc_name->name, sym->name) == 0)
9664           break;
9665     }
9666
9667   if (ns == NULL)
9668     {
9669       gfc_free_expr (init);
9670       return;
9671     }
9672
9673   /* Build an l-value expression for the result.  */
9674   lval = gfc_lval_expr_from_sym (sym);
9675
9676   /* Add the code at scope entry.  */
9677   init_st = gfc_get_code ();
9678   init_st->next = ns->code;
9679   ns->code = init_st;
9680
9681   /* Assign the default initializer to the l-value.  */
9682   init_st->loc = sym->declared_at;
9683   init_st->op = EXEC_INIT_ASSIGN;
9684   init_st->expr1 = lval;
9685   init_st->expr2 = init;
9686 }
9687
9688 /* Assign the default initializer to a derived type variable or result.  */
9689
9690 static void
9691 apply_default_init (gfc_symbol *sym)
9692 {
9693   gfc_expr *init = NULL;
9694
9695   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9696     return;
9697
9698   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
9699     init = gfc_default_initializer (&sym->ts);
9700
9701   if (init == NULL && sym->ts.type != BT_CLASS)
9702     return;
9703
9704   build_init_assign (sym, init);
9705   sym->attr.referenced = 1;
9706 }
9707
9708 /* Build an initializer for a local integer, real, complex, logical, or
9709    character variable, based on the command line flags finit-local-zero,
9710    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
9711    null if the symbol should not have a default initialization.  */
9712 static gfc_expr *
9713 build_default_init_expr (gfc_symbol *sym)
9714 {
9715   int char_len;
9716   gfc_expr *init_expr;
9717   int i;
9718
9719   /* These symbols should never have a default initialization.  */
9720   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
9721       || sym->attr.external
9722       || sym->attr.dummy
9723       || sym->attr.pointer
9724       || sym->attr.in_equivalence
9725       || sym->attr.in_common
9726       || sym->attr.data
9727       || sym->module
9728       || sym->attr.cray_pointee
9729       || sym->attr.cray_pointer)
9730     return NULL;
9731
9732   /* Now we'll try to build an initializer expression.  */
9733   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
9734                                      &sym->declared_at);
9735
9736   /* We will only initialize integers, reals, complex, logicals, and
9737      characters, and only if the corresponding command-line flags
9738      were set.  Otherwise, we free init_expr and return null.  */
9739   switch (sym->ts.type)
9740     {    
9741     case BT_INTEGER:
9742       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
9743         mpz_set_si (init_expr->value.integer, 
9744                          gfc_option.flag_init_integer_value);
9745       else
9746         {
9747           gfc_free_expr (init_expr);
9748           init_expr = NULL;
9749         }
9750       break;
9751
9752     case BT_REAL:
9753       switch (gfc_option.flag_init_real)
9754         {
9755         case GFC_INIT_REAL_SNAN:
9756           init_expr->is_snan = 1;
9757           /* Fall through.  */
9758         case GFC_INIT_REAL_NAN:
9759           mpfr_set_nan (init_expr->value.real);
9760           break;
9761
9762         case GFC_INIT_REAL_INF:
9763           mpfr_set_inf (init_expr->value.real, 1);
9764           break;
9765
9766         case GFC_INIT_REAL_NEG_INF:
9767           mpfr_set_inf (init_expr->value.real, -1);
9768           break;
9769
9770         case GFC_INIT_REAL_ZERO:
9771           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
9772           break;
9773
9774         default:
9775           gfc_free_expr (init_expr);
9776           init_expr = NULL;
9777           break;
9778         }
9779       break;
9780           
9781     case BT_COMPLEX:
9782       switch (gfc_option.flag_init_real)
9783         {
9784         case GFC_INIT_REAL_SNAN:
9785           init_expr->is_snan = 1;
9786           /* Fall through.  */
9787         case GFC_INIT_REAL_NAN:
9788           mpfr_set_nan (mpc_realref (init_expr->value.complex));
9789           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
9790           break;
9791
9792         case GFC_INIT_REAL_INF:
9793           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
9794           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
9795           break;
9796
9797         case GFC_INIT_REAL_NEG_INF:
9798           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
9799           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
9800           break;
9801
9802         case GFC_INIT_REAL_ZERO:
9803           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
9804           break;
9805
9806         default:
9807           gfc_free_expr (init_expr);
9808           init_expr = NULL;
9809           break;
9810         }
9811       break;
9812           
9813     case BT_LOGICAL:
9814       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
9815         init_expr->value.logical = 0;
9816       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
9817         init_expr->value.logical = 1;
9818       else
9819         {
9820           gfc_free_expr (init_expr);
9821           init_expr = NULL;
9822         }
9823       break;
9824           
9825     case BT_CHARACTER:
9826       /* For characters, the length must be constant in order to 
9827          create a default initializer.  */
9828       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
9829           && sym->ts.u.cl->length
9830           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9831         {
9832           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
9833           init_expr->value.character.length = char_len;
9834           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
9835           for (i = 0; i < char_len; i++)
9836             init_expr->value.character.string[i]
9837               = (unsigned char) gfc_option.flag_init_character_value;
9838         }
9839       else
9840         {
9841           gfc_free_expr (init_expr);
9842           init_expr = NULL;
9843         }
9844       break;
9845           
9846     default:
9847      gfc_free_expr (init_expr);
9848      init_expr = NULL;
9849     }
9850   return init_expr;
9851 }
9852
9853 /* Add an initialization expression to a local variable.  */
9854 static void
9855 apply_default_init_local (gfc_symbol *sym)
9856 {
9857   gfc_expr *init = NULL;
9858
9859   /* The symbol should be a variable or a function return value.  */
9860   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9861       || (sym->attr.function && sym->result != sym))
9862     return;
9863
9864   /* Try to build the initializer expression.  If we can't initialize
9865      this symbol, then init will be NULL.  */
9866   init = build_default_init_expr (sym);
9867   if (init == NULL)
9868     return;
9869
9870   /* For saved variables, we don't want to add an initializer at 
9871      function entry, so we just add a static initializer.  */
9872   if (sym->attr.save || sym->ns->save_all 
9873       || gfc_option.flag_max_stack_var_size == 0)
9874     {
9875       /* Don't clobber an existing initializer!  */
9876       gcc_assert (sym->value == NULL);
9877       sym->value = init;
9878       return;
9879     }
9880
9881   build_init_assign (sym, init);
9882 }
9883
9884
9885 /* Resolution of common features of flavors variable and procedure.  */
9886
9887 static gfc_try
9888 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
9889 {
9890   /* Avoid double diagnostics for function result symbols.  */
9891   if ((sym->result || sym->attr.result) && !sym->attr.dummy
9892       && (sym->ns != gfc_current_ns))
9893     return SUCCESS;
9894
9895   /* Constraints on deferred shape variable.  */
9896   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
9897     {
9898       if (sym->attr.allocatable)
9899         {
9900           if (sym->attr.dimension)
9901             {
9902               gfc_error ("Allocatable array '%s' at %L must have "
9903                          "a deferred shape", sym->name, &sym->declared_at);
9904               return FAILURE;
9905             }
9906           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
9907                                    "may not be ALLOCATABLE", sym->name,
9908                                    &sym->declared_at) == FAILURE)
9909             return FAILURE;
9910         }
9911
9912       if (sym->attr.pointer && sym->attr.dimension)
9913         {
9914           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
9915                      sym->name, &sym->declared_at);
9916           return FAILURE;
9917         }
9918     }
9919   else
9920     {
9921       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
9922           && sym->ts.type != BT_CLASS && !sym->assoc)
9923         {
9924           gfc_error ("Array '%s' at %L cannot have a deferred shape",
9925                      sym->name, &sym->declared_at);
9926           return FAILURE;
9927          }
9928     }
9929
9930   /* Constraints on polymorphic variables.  */
9931   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
9932     {
9933       /* F03:C502.  */
9934       if (sym->attr.class_ok
9935           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
9936         {
9937           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
9938                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
9939                      &sym->declared_at);
9940           return FAILURE;
9941         }
9942
9943       /* F03:C509.  */
9944       /* Assume that use associated symbols were checked in the module ns.
9945          Class-variables that are associate-names are also something special
9946          and excepted from the test.  */
9947       if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
9948         {
9949           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
9950                      "or pointer", sym->name, &sym->declared_at);
9951           return FAILURE;
9952         }
9953     }
9954     
9955   return SUCCESS;
9956 }
9957
9958
9959 /* Additional checks for symbols with flavor variable and derived
9960    type.  To be called from resolve_fl_variable.  */
9961
9962 static gfc_try
9963 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
9964 {
9965   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
9966
9967   /* Check to see if a derived type is blocked from being host
9968      associated by the presence of another class I symbol in the same
9969      namespace.  14.6.1.3 of the standard and the discussion on
9970      comp.lang.fortran.  */
9971   if (sym->ns != sym->ts.u.derived->ns
9972       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
9973     {
9974       gfc_symbol *s;
9975       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
9976       if (s && s->attr.flavor != FL_DERIVED)
9977         {
9978           gfc_error ("The type '%s' cannot be host associated at %L "
9979                      "because it is blocked by an incompatible object "
9980                      "of the same name declared at %L",
9981                      sym->ts.u.derived->name, &sym->declared_at,
9982                      &s->declared_at);
9983           return FAILURE;
9984         }
9985     }
9986
9987   /* 4th constraint in section 11.3: "If an object of a type for which
9988      component-initialization is specified (R429) appears in the
9989      specification-part of a module and does not have the ALLOCATABLE
9990      or POINTER attribute, the object shall have the SAVE attribute."
9991
9992      The check for initializers is performed with
9993      gfc_has_default_initializer because gfc_default_initializer generates
9994      a hidden default for allocatable components.  */
9995   if (!(sym->value || no_init_flag) && sym->ns->proc_name
9996       && sym->ns->proc_name->attr.flavor == FL_MODULE
9997       && !sym->ns->save_all && !sym->attr.save
9998       && !sym->attr.pointer && !sym->attr.allocatable
9999       && gfc_has_default_initializer (sym->ts.u.derived)
10000       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
10001                          "module variable '%s' at %L, needed due to "
10002                          "the default initialization", sym->name,
10003                          &sym->declared_at) == FAILURE)
10004     return FAILURE;
10005
10006   /* Assign default initializer.  */
10007   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
10008       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
10009     {
10010       sym->value = gfc_default_initializer (&sym->ts);
10011     }
10012
10013   return SUCCESS;
10014 }
10015
10016
10017 /* Resolve symbols with flavor variable.  */
10018
10019 static gfc_try
10020 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
10021 {
10022   int no_init_flag, automatic_flag;
10023   gfc_expr *e;
10024   const char *auto_save_msg;
10025
10026   auto_save_msg = "Automatic object '%s' at %L cannot have the "
10027                   "SAVE attribute";
10028
10029   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10030     return FAILURE;
10031
10032   /* Set this flag to check that variables are parameters of all entries.
10033      This check is effected by the call to gfc_resolve_expr through
10034      is_non_constant_shape_array.  */
10035   specification_expr = 1;
10036
10037   if (sym->ns->proc_name
10038       && (sym->ns->proc_name->attr.flavor == FL_MODULE
10039           || sym->ns->proc_name->attr.is_main_program)
10040       && !sym->attr.use_assoc
10041       && !sym->attr.allocatable
10042       && !sym->attr.pointer
10043       && is_non_constant_shape_array (sym))
10044     {
10045       /* The shape of a main program or module array needs to be
10046          constant.  */
10047       gfc_error ("The module or main program array '%s' at %L must "
10048                  "have constant shape", sym->name, &sym->declared_at);
10049       specification_expr = 0;
10050       return FAILURE;
10051     }
10052
10053   /* Constraints on deferred type parameter.  */
10054   if (sym->ts.deferred && !(sym->attr.pointer || sym->attr.allocatable))
10055     {
10056       gfc_error ("Entity '%s' at %L has a deferred type parameter and "
10057                  "requires either the pointer or allocatable attribute",
10058                      sym->name, &sym->declared_at);
10059       return FAILURE;
10060     }
10061
10062   if (sym->ts.type == BT_CHARACTER)
10063     {
10064       /* Make sure that character string variables with assumed length are
10065          dummy arguments.  */
10066       e = sym->ts.u.cl->length;
10067       if (e == NULL && !sym->attr.dummy && !sym->attr.result
10068           && !sym->ts.deferred)
10069         {
10070           gfc_error ("Entity with assumed character length at %L must be a "
10071                      "dummy argument or a PARAMETER", &sym->declared_at);
10072           return FAILURE;
10073         }
10074
10075       if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
10076         {
10077           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10078           return FAILURE;
10079         }
10080
10081       if (!gfc_is_constant_expr (e)
10082           && !(e->expr_type == EXPR_VARIABLE
10083                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
10084           && sym->ns->proc_name
10085           && (sym->ns->proc_name->attr.flavor == FL_MODULE
10086               || sym->ns->proc_name->attr.is_main_program)
10087           && !sym->attr.use_assoc)
10088         {
10089           gfc_error ("'%s' at %L must have constant character length "
10090                      "in this context", sym->name, &sym->declared_at);
10091           return FAILURE;
10092         }
10093     }
10094
10095   if (sym->value == NULL && sym->attr.referenced)
10096     apply_default_init_local (sym); /* Try to apply a default initialization.  */
10097
10098   /* Determine if the symbol may not have an initializer.  */
10099   no_init_flag = automatic_flag = 0;
10100   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
10101       || sym->attr.intrinsic || sym->attr.result)
10102     no_init_flag = 1;
10103   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
10104            && is_non_constant_shape_array (sym))
10105     {
10106       no_init_flag = automatic_flag = 1;
10107
10108       /* Also, they must not have the SAVE attribute.
10109          SAVE_IMPLICIT is checked below.  */
10110       if (sym->attr.save == SAVE_EXPLICIT)
10111         {
10112           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10113           return FAILURE;
10114         }
10115     }
10116
10117   /* Ensure that any initializer is simplified.  */
10118   if (sym->value)
10119     gfc_simplify_expr (sym->value, 1);
10120
10121   /* Reject illegal initializers.  */
10122   if (!sym->mark && sym->value)
10123     {
10124       if (sym->attr.allocatable || (sym->ts.type == BT_CLASS
10125                                     && CLASS_DATA (sym)->attr.allocatable))
10126         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
10127                    sym->name, &sym->declared_at);
10128       else if (sym->attr.external)
10129         gfc_error ("External '%s' at %L cannot have an initializer",
10130                    sym->name, &sym->declared_at);
10131       else if (sym->attr.dummy
10132         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
10133         gfc_error ("Dummy '%s' at %L cannot have an initializer",
10134                    sym->name, &sym->declared_at);
10135       else if (sym->attr.intrinsic)
10136         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
10137                    sym->name, &sym->declared_at);
10138       else if (sym->attr.result)
10139         gfc_error ("Function result '%s' at %L cannot have an initializer",
10140                    sym->name, &sym->declared_at);
10141       else if (automatic_flag)
10142         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
10143                    sym->name, &sym->declared_at);
10144       else
10145         goto no_init_error;
10146       return FAILURE;
10147     }
10148
10149 no_init_error:
10150   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
10151     return resolve_fl_variable_derived (sym, no_init_flag);
10152
10153   return SUCCESS;
10154 }
10155
10156
10157 /* Resolve a procedure.  */
10158
10159 static gfc_try
10160 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
10161 {
10162   gfc_formal_arglist *arg;
10163
10164   if (sym->attr.function
10165       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10166     return FAILURE;
10167
10168   if (sym->ts.type == BT_CHARACTER)
10169     {
10170       gfc_charlen *cl = sym->ts.u.cl;
10171
10172       if (cl && cl->length && gfc_is_constant_expr (cl->length)
10173              && resolve_charlen (cl) == FAILURE)
10174         return FAILURE;
10175
10176       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
10177           && sym->attr.proc == PROC_ST_FUNCTION)
10178         {
10179           gfc_error ("Character-valued statement function '%s' at %L must "
10180                      "have constant length", sym->name, &sym->declared_at);
10181           return FAILURE;
10182         }
10183     }
10184
10185   /* Ensure that derived type for are not of a private type.  Internal
10186      module procedures are excluded by 2.2.3.3 - i.e., they are not
10187      externally accessible and can access all the objects accessible in
10188      the host.  */
10189   if (!(sym->ns->parent
10190         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
10191       && gfc_check_symbol_access (sym))
10192     {
10193       gfc_interface *iface;
10194
10195       for (arg = sym->formal; arg; arg = arg->next)
10196         {
10197           if (arg->sym
10198               && arg->sym->ts.type == BT_DERIVED
10199               && !arg->sym->ts.u.derived->attr.use_assoc
10200               && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10201               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
10202                                  "PRIVATE type and cannot be a dummy argument"
10203                                  " of '%s', which is PUBLIC at %L",
10204                                  arg->sym->name, sym->name, &sym->declared_at)
10205                  == FAILURE)
10206             {
10207               /* Stop this message from recurring.  */
10208               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10209               return FAILURE;
10210             }
10211         }
10212
10213       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10214          PRIVATE to the containing module.  */
10215       for (iface = sym->generic; iface; iface = iface->next)
10216         {
10217           for (arg = iface->sym->formal; arg; arg = arg->next)
10218             {
10219               if (arg->sym
10220                   && arg->sym->ts.type == BT_DERIVED
10221                   && !arg->sym->ts.u.derived->attr.use_assoc
10222                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10223                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10224                                      "'%s' in PUBLIC interface '%s' at %L "
10225                                      "takes dummy arguments of '%s' which is "
10226                                      "PRIVATE", iface->sym->name, sym->name,
10227                                      &iface->sym->declared_at,
10228                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10229                 {
10230                   /* Stop this message from recurring.  */
10231                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10232                   return FAILURE;
10233                 }
10234              }
10235         }
10236
10237       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10238          PRIVATE to the containing module.  */
10239       for (iface = sym->generic; iface; iface = iface->next)
10240         {
10241           for (arg = iface->sym->formal; arg; arg = arg->next)
10242             {
10243               if (arg->sym
10244                   && arg->sym->ts.type == BT_DERIVED
10245                   && !arg->sym->ts.u.derived->attr.use_assoc
10246                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10247                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10248                                      "'%s' in PUBLIC interface '%s' at %L "
10249                                      "takes dummy arguments of '%s' which is "
10250                                      "PRIVATE", iface->sym->name, sym->name,
10251                                      &iface->sym->declared_at,
10252                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10253                 {
10254                   /* Stop this message from recurring.  */
10255                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10256                   return FAILURE;
10257                 }
10258              }
10259         }
10260     }
10261
10262   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
10263       && !sym->attr.proc_pointer)
10264     {
10265       gfc_error ("Function '%s' at %L cannot have an initializer",
10266                  sym->name, &sym->declared_at);
10267       return FAILURE;
10268     }
10269
10270   /* An external symbol may not have an initializer because it is taken to be
10271      a procedure. Exception: Procedure Pointers.  */
10272   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
10273     {
10274       gfc_error ("External object '%s' at %L may not have an initializer",
10275                  sym->name, &sym->declared_at);
10276       return FAILURE;
10277     }
10278
10279   /* An elemental function is required to return a scalar 12.7.1  */
10280   if (sym->attr.elemental && sym->attr.function && sym->as)
10281     {
10282       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
10283                  "result", sym->name, &sym->declared_at);
10284       /* Reset so that the error only occurs once.  */
10285       sym->attr.elemental = 0;
10286       return FAILURE;
10287     }
10288
10289   if (sym->attr.proc == PROC_ST_FUNCTION
10290       && (sym->attr.allocatable || sym->attr.pointer))
10291     {
10292       gfc_error ("Statement function '%s' at %L may not have pointer or "
10293                  "allocatable attribute", sym->name, &sym->declared_at);
10294       return FAILURE;
10295     }
10296
10297   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
10298      char-len-param shall not be array-valued, pointer-valued, recursive
10299      or pure.  ....snip... A character value of * may only be used in the
10300      following ways: (i) Dummy arg of procedure - dummy associates with
10301      actual length; (ii) To declare a named constant; or (iii) External
10302      function - but length must be declared in calling scoping unit.  */
10303   if (sym->attr.function
10304       && sym->ts.type == BT_CHARACTER
10305       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
10306     {
10307       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
10308           || (sym->attr.recursive) || (sym->attr.pure))
10309         {
10310           if (sym->as && sym->as->rank)
10311             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10312                        "array-valued", sym->name, &sym->declared_at);
10313
10314           if (sym->attr.pointer)
10315             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10316                        "pointer-valued", sym->name, &sym->declared_at);
10317
10318           if (sym->attr.pure)
10319             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10320                        "pure", sym->name, &sym->declared_at);
10321
10322           if (sym->attr.recursive)
10323             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10324                        "recursive", sym->name, &sym->declared_at);
10325
10326           return FAILURE;
10327         }
10328
10329       /* Appendix B.2 of the standard.  Contained functions give an
10330          error anyway.  Fixed-form is likely to be F77/legacy. Deferred
10331          character length is an F2003 feature.  */
10332       if (!sym->attr.contained
10333             && gfc_current_form != FORM_FIXED
10334             && !sym->ts.deferred)
10335         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
10336                         "CHARACTER(*) function '%s' at %L",
10337                         sym->name, &sym->declared_at);
10338     }
10339
10340   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
10341     {
10342       gfc_formal_arglist *curr_arg;
10343       int has_non_interop_arg = 0;
10344
10345       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10346                              sym->common_block) == FAILURE)
10347         {
10348           /* Clear these to prevent looking at them again if there was an
10349              error.  */
10350           sym->attr.is_bind_c = 0;
10351           sym->attr.is_c_interop = 0;
10352           sym->ts.is_c_interop = 0;
10353         }
10354       else
10355         {
10356           /* So far, no errors have been found.  */
10357           sym->attr.is_c_interop = 1;
10358           sym->ts.is_c_interop = 1;
10359         }
10360       
10361       curr_arg = sym->formal;
10362       while (curr_arg != NULL)
10363         {
10364           /* Skip implicitly typed dummy args here.  */
10365           if (curr_arg->sym->attr.implicit_type == 0)
10366             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
10367               /* If something is found to fail, record the fact so we
10368                  can mark the symbol for the procedure as not being
10369                  BIND(C) to try and prevent multiple errors being
10370                  reported.  */
10371               has_non_interop_arg = 1;
10372           
10373           curr_arg = curr_arg->next;
10374         }
10375
10376       /* See if any of the arguments were not interoperable and if so, clear
10377          the procedure symbol to prevent duplicate error messages.  */
10378       if (has_non_interop_arg != 0)
10379         {
10380           sym->attr.is_c_interop = 0;
10381           sym->ts.is_c_interop = 0;
10382           sym->attr.is_bind_c = 0;
10383         }
10384     }
10385   
10386   if (!sym->attr.proc_pointer)
10387     {
10388       if (sym->attr.save == SAVE_EXPLICIT)
10389         {
10390           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
10391                      "in '%s' at %L", sym->name, &sym->declared_at);
10392           return FAILURE;
10393         }
10394       if (sym->attr.intent)
10395         {
10396           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
10397                      "in '%s' at %L", sym->name, &sym->declared_at);
10398           return FAILURE;
10399         }
10400       if (sym->attr.subroutine && sym->attr.result)
10401         {
10402           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
10403                      "in '%s' at %L", sym->name, &sym->declared_at);
10404           return FAILURE;
10405         }
10406       if (sym->attr.external && sym->attr.function
10407           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
10408               || sym->attr.contained))
10409         {
10410           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
10411                      "in '%s' at %L", sym->name, &sym->declared_at);
10412           return FAILURE;
10413         }
10414       if (strcmp ("ppr@", sym->name) == 0)
10415         {
10416           gfc_error ("Procedure pointer result '%s' at %L "
10417                      "is missing the pointer attribute",
10418                      sym->ns->proc_name->name, &sym->declared_at);
10419           return FAILURE;
10420         }
10421     }
10422
10423   return SUCCESS;
10424 }
10425
10426
10427 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
10428    been defined and we now know their defined arguments, check that they fulfill
10429    the requirements of the standard for procedures used as finalizers.  */
10430
10431 static gfc_try
10432 gfc_resolve_finalizers (gfc_symbol* derived)
10433 {
10434   gfc_finalizer* list;
10435   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
10436   gfc_try result = SUCCESS;
10437   bool seen_scalar = false;
10438
10439   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
10440     return SUCCESS;
10441
10442   /* Walk over the list of finalizer-procedures, check them, and if any one
10443      does not fit in with the standard's definition, print an error and remove
10444      it from the list.  */
10445   prev_link = &derived->f2k_derived->finalizers;
10446   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
10447     {
10448       gfc_symbol* arg;
10449       gfc_finalizer* i;
10450       int my_rank;
10451
10452       /* Skip this finalizer if we already resolved it.  */
10453       if (list->proc_tree)
10454         {
10455           prev_link = &(list->next);
10456           continue;
10457         }
10458
10459       /* Check this exists and is a SUBROUTINE.  */
10460       if (!list->proc_sym->attr.subroutine)
10461         {
10462           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
10463                      list->proc_sym->name, &list->where);
10464           goto error;
10465         }
10466
10467       /* We should have exactly one argument.  */
10468       if (!list->proc_sym->formal || list->proc_sym->formal->next)
10469         {
10470           gfc_error ("FINAL procedure at %L must have exactly one argument",
10471                      &list->where);
10472           goto error;
10473         }
10474       arg = list->proc_sym->formal->sym;
10475
10476       /* This argument must be of our type.  */
10477       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
10478         {
10479           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
10480                      &arg->declared_at, derived->name);
10481           goto error;
10482         }
10483
10484       /* It must neither be a pointer nor allocatable nor optional.  */
10485       if (arg->attr.pointer)
10486         {
10487           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
10488                      &arg->declared_at);
10489           goto error;
10490         }
10491       if (arg->attr.allocatable)
10492         {
10493           gfc_error ("Argument of FINAL procedure at %L must not be"
10494                      " ALLOCATABLE", &arg->declared_at);
10495           goto error;
10496         }
10497       if (arg->attr.optional)
10498         {
10499           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
10500                      &arg->declared_at);
10501           goto error;
10502         }
10503
10504       /* It must not be INTENT(OUT).  */
10505       if (arg->attr.intent == INTENT_OUT)
10506         {
10507           gfc_error ("Argument of FINAL procedure at %L must not be"
10508                      " INTENT(OUT)", &arg->declared_at);
10509           goto error;
10510         }
10511
10512       /* Warn if the procedure is non-scalar and not assumed shape.  */
10513       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
10514           && arg->as->type != AS_ASSUMED_SHAPE)
10515         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
10516                      " shape argument", &arg->declared_at);
10517
10518       /* Check that it does not match in kind and rank with a FINAL procedure
10519          defined earlier.  To really loop over the *earlier* declarations,
10520          we need to walk the tail of the list as new ones were pushed at the
10521          front.  */
10522       /* TODO: Handle kind parameters once they are implemented.  */
10523       my_rank = (arg->as ? arg->as->rank : 0);
10524       for (i = list->next; i; i = i->next)
10525         {
10526           /* Argument list might be empty; that is an error signalled earlier,
10527              but we nevertheless continued resolving.  */
10528           if (i->proc_sym->formal)
10529             {
10530               gfc_symbol* i_arg = i->proc_sym->formal->sym;
10531               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
10532               if (i_rank == my_rank)
10533                 {
10534                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
10535                              " rank (%d) as '%s'",
10536                              list->proc_sym->name, &list->where, my_rank, 
10537                              i->proc_sym->name);
10538                   goto error;
10539                 }
10540             }
10541         }
10542
10543         /* Is this the/a scalar finalizer procedure?  */
10544         if (!arg->as || arg->as->rank == 0)
10545           seen_scalar = true;
10546
10547         /* Find the symtree for this procedure.  */
10548         gcc_assert (!list->proc_tree);
10549         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
10550
10551         prev_link = &list->next;
10552         continue;
10553
10554         /* Remove wrong nodes immediately from the list so we don't risk any
10555            troubles in the future when they might fail later expectations.  */
10556 error:
10557         result = FAILURE;
10558         i = list;
10559         *prev_link = list->next;
10560         gfc_free_finalizer (i);
10561     }
10562
10563   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
10564      were nodes in the list, must have been for arrays.  It is surely a good
10565      idea to have a scalar version there if there's something to finalize.  */
10566   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
10567     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
10568                  " defined at %L, suggest also scalar one",
10569                  derived->name, &derived->declared_at);
10570
10571   /* TODO:  Remove this error when finalization is finished.  */
10572   gfc_error ("Finalization at %L is not yet implemented",
10573              &derived->declared_at);
10574
10575   return result;
10576 }
10577
10578
10579 /* Check that it is ok for the typebound procedure proc to override the
10580    procedure old.  */
10581
10582 static gfc_try
10583 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
10584 {
10585   locus where;
10586   const gfc_symbol* proc_target;
10587   const gfc_symbol* old_target;
10588   unsigned proc_pass_arg, old_pass_arg, argpos;
10589   gfc_formal_arglist* proc_formal;
10590   gfc_formal_arglist* old_formal;
10591
10592   /* This procedure should only be called for non-GENERIC proc.  */
10593   gcc_assert (!proc->n.tb->is_generic);
10594
10595   /* If the overwritten procedure is GENERIC, this is an error.  */
10596   if (old->n.tb->is_generic)
10597     {
10598       gfc_error ("Can't overwrite GENERIC '%s' at %L",
10599                  old->name, &proc->n.tb->where);
10600       return FAILURE;
10601     }
10602
10603   where = proc->n.tb->where;
10604   proc_target = proc->n.tb->u.specific->n.sym;
10605   old_target = old->n.tb->u.specific->n.sym;
10606
10607   /* Check that overridden binding is not NON_OVERRIDABLE.  */
10608   if (old->n.tb->non_overridable)
10609     {
10610       gfc_error ("'%s' at %L overrides a procedure binding declared"
10611                  " NON_OVERRIDABLE", proc->name, &where);
10612       return FAILURE;
10613     }
10614
10615   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
10616   if (!old->n.tb->deferred && proc->n.tb->deferred)
10617     {
10618       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
10619                  " non-DEFERRED binding", proc->name, &where);
10620       return FAILURE;
10621     }
10622
10623   /* If the overridden binding is PURE, the overriding must be, too.  */
10624   if (old_target->attr.pure && !proc_target->attr.pure)
10625     {
10626       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
10627                  proc->name, &where);
10628       return FAILURE;
10629     }
10630
10631   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
10632      is not, the overriding must not be either.  */
10633   if (old_target->attr.elemental && !proc_target->attr.elemental)
10634     {
10635       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
10636                  " ELEMENTAL", proc->name, &where);
10637       return FAILURE;
10638     }
10639   if (!old_target->attr.elemental && proc_target->attr.elemental)
10640     {
10641       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
10642                  " be ELEMENTAL, either", proc->name, &where);
10643       return FAILURE;
10644     }
10645
10646   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
10647      SUBROUTINE.  */
10648   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
10649     {
10650       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
10651                  " SUBROUTINE", proc->name, &where);
10652       return FAILURE;
10653     }
10654
10655   /* If the overridden binding is a FUNCTION, the overriding must also be a
10656      FUNCTION and have the same characteristics.  */
10657   if (old_target->attr.function)
10658     {
10659       if (!proc_target->attr.function)
10660         {
10661           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
10662                      " FUNCTION", proc->name, &where);
10663           return FAILURE;
10664         }
10665
10666       /* FIXME:  Do more comprehensive checking (including, for instance, the
10667          rank and array-shape).  */
10668       gcc_assert (proc_target->result && old_target->result);
10669       if (!gfc_compare_types (&proc_target->result->ts,
10670                               &old_target->result->ts))
10671         {
10672           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
10673                      " matching result types", proc->name, &where);
10674           return FAILURE;
10675         }
10676     }
10677
10678   /* If the overridden binding is PUBLIC, the overriding one must not be
10679      PRIVATE.  */
10680   if (old->n.tb->access == ACCESS_PUBLIC
10681       && proc->n.tb->access == ACCESS_PRIVATE)
10682     {
10683       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
10684                  " PRIVATE", proc->name, &where);
10685       return FAILURE;
10686     }
10687
10688   /* Compare the formal argument lists of both procedures.  This is also abused
10689      to find the position of the passed-object dummy arguments of both
10690      bindings as at least the overridden one might not yet be resolved and we
10691      need those positions in the check below.  */
10692   proc_pass_arg = old_pass_arg = 0;
10693   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
10694     proc_pass_arg = 1;
10695   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
10696     old_pass_arg = 1;
10697   argpos = 1;
10698   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
10699        proc_formal && old_formal;
10700        proc_formal = proc_formal->next, old_formal = old_formal->next)
10701     {
10702       if (proc->n.tb->pass_arg
10703           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
10704         proc_pass_arg = argpos;
10705       if (old->n.tb->pass_arg
10706           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
10707         old_pass_arg = argpos;
10708
10709       /* Check that the names correspond.  */
10710       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
10711         {
10712           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
10713                      " to match the corresponding argument of the overridden"
10714                      " procedure", proc_formal->sym->name, proc->name, &where,
10715                      old_formal->sym->name);
10716           return FAILURE;
10717         }
10718
10719       /* Check that the types correspond if neither is the passed-object
10720          argument.  */
10721       /* FIXME:  Do more comprehensive testing here.  */
10722       if (proc_pass_arg != argpos && old_pass_arg != argpos
10723           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
10724         {
10725           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L "
10726                      "in respect to the overridden procedure",
10727                      proc_formal->sym->name, proc->name, &where);
10728           return FAILURE;
10729         }
10730
10731       ++argpos;
10732     }
10733   if (proc_formal || old_formal)
10734     {
10735       gfc_error ("'%s' at %L must have the same number of formal arguments as"
10736                  " the overridden procedure", proc->name, &where);
10737       return FAILURE;
10738     }
10739
10740   /* If the overridden binding is NOPASS, the overriding one must also be
10741      NOPASS.  */
10742   if (old->n.tb->nopass && !proc->n.tb->nopass)
10743     {
10744       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
10745                  " NOPASS", proc->name, &where);
10746       return FAILURE;
10747     }
10748
10749   /* If the overridden binding is PASS(x), the overriding one must also be
10750      PASS and the passed-object dummy arguments must correspond.  */
10751   if (!old->n.tb->nopass)
10752     {
10753       if (proc->n.tb->nopass)
10754         {
10755           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
10756                      " PASS", proc->name, &where);
10757           return FAILURE;
10758         }
10759
10760       if (proc_pass_arg != old_pass_arg)
10761         {
10762           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
10763                      " the same position as the passed-object dummy argument of"
10764                      " the overridden procedure", proc->name, &where);
10765           return FAILURE;
10766         }
10767     }
10768
10769   return SUCCESS;
10770 }
10771
10772
10773 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10774
10775 static gfc_try
10776 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10777                              const char* generic_name, locus where)
10778 {
10779   gfc_symbol* sym1;
10780   gfc_symbol* sym2;
10781
10782   gcc_assert (t1->specific && t2->specific);
10783   gcc_assert (!t1->specific->is_generic);
10784   gcc_assert (!t2->specific->is_generic);
10785
10786   sym1 = t1->specific->u.specific->n.sym;
10787   sym2 = t2->specific->u.specific->n.sym;
10788
10789   if (sym1 == sym2)
10790     return SUCCESS;
10791
10792   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10793   if (sym1->attr.subroutine != sym2->attr.subroutine
10794       || sym1->attr.function != sym2->attr.function)
10795     {
10796       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10797                  " GENERIC '%s' at %L",
10798                  sym1->name, sym2->name, generic_name, &where);
10799       return FAILURE;
10800     }
10801
10802   /* Compare the interfaces.  */
10803   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10804     {
10805       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10806                  sym1->name, sym2->name, generic_name, &where);
10807       return FAILURE;
10808     }
10809
10810   return SUCCESS;
10811 }
10812
10813
10814 /* Worker function for resolving a generic procedure binding; this is used to
10815    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10816
10817    The difference between those cases is finding possible inherited bindings
10818    that are overridden, as one has to look for them in tb_sym_root,
10819    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10820    the super-type and set p->overridden correctly.  */
10821
10822 static gfc_try
10823 resolve_tb_generic_targets (gfc_symbol* super_type,
10824                             gfc_typebound_proc* p, const char* name)
10825 {
10826   gfc_tbp_generic* target;
10827   gfc_symtree* first_target;
10828   gfc_symtree* inherited;
10829
10830   gcc_assert (p && p->is_generic);
10831
10832   /* Try to find the specific bindings for the symtrees in our target-list.  */
10833   gcc_assert (p->u.generic);
10834   for (target = p->u.generic; target; target = target->next)
10835     if (!target->specific)
10836       {
10837         gfc_typebound_proc* overridden_tbp;
10838         gfc_tbp_generic* g;
10839         const char* target_name;
10840
10841         target_name = target->specific_st->name;
10842
10843         /* Defined for this type directly.  */
10844         if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
10845           {
10846             target->specific = target->specific_st->n.tb;
10847             goto specific_found;
10848           }
10849
10850         /* Look for an inherited specific binding.  */
10851         if (super_type)
10852           {
10853             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10854                                                  true, NULL);
10855
10856             if (inherited)
10857               {
10858                 gcc_assert (inherited->n.tb);
10859                 target->specific = inherited->n.tb;
10860                 goto specific_found;
10861               }
10862           }
10863
10864         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10865                    " at %L", target_name, name, &p->where);
10866         return FAILURE;
10867
10868         /* Once we've found the specific binding, check it is not ambiguous with
10869            other specifics already found or inherited for the same GENERIC.  */
10870 specific_found:
10871         gcc_assert (target->specific);
10872
10873         /* This must really be a specific binding!  */
10874         if (target->specific->is_generic)
10875           {
10876             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
10877                        " '%s' is GENERIC, too", name, &p->where, target_name);
10878             return FAILURE;
10879           }
10880
10881         /* Check those already resolved on this type directly.  */
10882         for (g = p->u.generic; g; g = g->next)
10883           if (g != target && g->specific
10884               && check_generic_tbp_ambiguity (target, g, name, p->where)
10885                   == FAILURE)
10886             return FAILURE;
10887
10888         /* Check for ambiguity with inherited specific targets.  */
10889         for (overridden_tbp = p->overridden; overridden_tbp;
10890              overridden_tbp = overridden_tbp->overridden)
10891           if (overridden_tbp->is_generic)
10892             {
10893               for (g = overridden_tbp->u.generic; g; g = g->next)
10894                 {
10895                   gcc_assert (g->specific);
10896                   if (check_generic_tbp_ambiguity (target, g,
10897                                                    name, p->where) == FAILURE)
10898                     return FAILURE;
10899                 }
10900             }
10901       }
10902
10903   /* If we attempt to "overwrite" a specific binding, this is an error.  */
10904   if (p->overridden && !p->overridden->is_generic)
10905     {
10906       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
10907                  " the same name", name, &p->where);
10908       return FAILURE;
10909     }
10910
10911   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
10912      all must have the same attributes here.  */
10913   first_target = p->u.generic->specific->u.specific;
10914   gcc_assert (first_target);
10915   p->subroutine = first_target->n.sym->attr.subroutine;
10916   p->function = first_target->n.sym->attr.function;
10917
10918   return SUCCESS;
10919 }
10920
10921
10922 /* Resolve a GENERIC procedure binding for a derived type.  */
10923
10924 static gfc_try
10925 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
10926 {
10927   gfc_symbol* super_type;
10928
10929   /* Find the overridden binding if any.  */
10930   st->n.tb->overridden = NULL;
10931   super_type = gfc_get_derived_super_type (derived);
10932   if (super_type)
10933     {
10934       gfc_symtree* overridden;
10935       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
10936                                             true, NULL);
10937
10938       if (overridden && overridden->n.tb)
10939         st->n.tb->overridden = overridden->n.tb;
10940     }
10941
10942   /* Resolve using worker function.  */
10943   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
10944 }
10945
10946
10947 /* Retrieve the target-procedure of an operator binding and do some checks in
10948    common for intrinsic and user-defined type-bound operators.  */
10949
10950 static gfc_symbol*
10951 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
10952 {
10953   gfc_symbol* target_proc;
10954
10955   gcc_assert (target->specific && !target->specific->is_generic);
10956   target_proc = target->specific->u.specific->n.sym;
10957   gcc_assert (target_proc);
10958
10959   /* All operator bindings must have a passed-object dummy argument.  */
10960   if (target->specific->nopass)
10961     {
10962       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
10963       return NULL;
10964     }
10965
10966   return target_proc;
10967 }
10968
10969
10970 /* Resolve a type-bound intrinsic operator.  */
10971
10972 static gfc_try
10973 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
10974                                 gfc_typebound_proc* p)
10975 {
10976   gfc_symbol* super_type;
10977   gfc_tbp_generic* target;
10978   
10979   /* If there's already an error here, do nothing (but don't fail again).  */
10980   if (p->error)
10981     return SUCCESS;
10982
10983   /* Operators should always be GENERIC bindings.  */
10984   gcc_assert (p->is_generic);
10985
10986   /* Look for an overridden binding.  */
10987   super_type = gfc_get_derived_super_type (derived);
10988   if (super_type && super_type->f2k_derived)
10989     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
10990                                                      op, true, NULL);
10991   else
10992     p->overridden = NULL;
10993
10994   /* Resolve general GENERIC properties using worker function.  */
10995   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
10996     goto error;
10997
10998   /* Check the targets to be procedures of correct interface.  */
10999   for (target = p->u.generic; target; target = target->next)
11000     {
11001       gfc_symbol* target_proc;
11002
11003       target_proc = get_checked_tb_operator_target (target, p->where);
11004       if (!target_proc)
11005         goto error;
11006
11007       if (!gfc_check_operator_interface (target_proc, op, p->where))
11008         goto error;
11009     }
11010
11011   return SUCCESS;
11012
11013 error:
11014   p->error = 1;
11015   return FAILURE;
11016 }
11017
11018
11019 /* Resolve a type-bound user operator (tree-walker callback).  */
11020
11021 static gfc_symbol* resolve_bindings_derived;
11022 static gfc_try resolve_bindings_result;
11023
11024 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
11025
11026 static void
11027 resolve_typebound_user_op (gfc_symtree* stree)
11028 {
11029   gfc_symbol* super_type;
11030   gfc_tbp_generic* target;
11031
11032   gcc_assert (stree && stree->n.tb);
11033
11034   if (stree->n.tb->error)
11035     return;
11036
11037   /* Operators should always be GENERIC bindings.  */
11038   gcc_assert (stree->n.tb->is_generic);
11039
11040   /* Find overridden procedure, if any.  */
11041   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11042   if (super_type && super_type->f2k_derived)
11043     {
11044       gfc_symtree* overridden;
11045       overridden = gfc_find_typebound_user_op (super_type, NULL,
11046                                                stree->name, true, NULL);
11047
11048       if (overridden && overridden->n.tb)
11049         stree->n.tb->overridden = overridden->n.tb;
11050     }
11051   else
11052     stree->n.tb->overridden = NULL;
11053
11054   /* Resolve basically using worker function.  */
11055   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
11056         == FAILURE)
11057     goto error;
11058
11059   /* Check the targets to be functions of correct interface.  */
11060   for (target = stree->n.tb->u.generic; target; target = target->next)
11061     {
11062       gfc_symbol* target_proc;
11063
11064       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
11065       if (!target_proc)
11066         goto error;
11067
11068       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
11069         goto error;
11070     }
11071
11072   return;
11073
11074 error:
11075   resolve_bindings_result = FAILURE;
11076   stree->n.tb->error = 1;
11077 }
11078
11079
11080 /* Resolve the type-bound procedures for a derived type.  */
11081
11082 static void
11083 resolve_typebound_procedure (gfc_symtree* stree)
11084 {
11085   gfc_symbol* proc;
11086   locus where;
11087   gfc_symbol* me_arg;
11088   gfc_symbol* super_type;
11089   gfc_component* comp;
11090
11091   gcc_assert (stree);
11092
11093   /* Undefined specific symbol from GENERIC target definition.  */
11094   if (!stree->n.tb)
11095     return;
11096
11097   if (stree->n.tb->error)
11098     return;
11099
11100   /* If this is a GENERIC binding, use that routine.  */
11101   if (stree->n.tb->is_generic)
11102     {
11103       if (resolve_typebound_generic (resolve_bindings_derived, stree)
11104             == FAILURE)
11105         goto error;
11106       return;
11107     }
11108
11109   /* Get the target-procedure to check it.  */
11110   gcc_assert (!stree->n.tb->is_generic);
11111   gcc_assert (stree->n.tb->u.specific);
11112   proc = stree->n.tb->u.specific->n.sym;
11113   where = stree->n.tb->where;
11114
11115   /* Default access should already be resolved from the parser.  */
11116   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
11117
11118   /* It should be a module procedure or an external procedure with explicit
11119      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
11120   if ((!proc->attr.subroutine && !proc->attr.function)
11121       || (proc->attr.proc != PROC_MODULE
11122           && proc->attr.if_source != IFSRC_IFBODY)
11123       || (proc->attr.abstract && !stree->n.tb->deferred))
11124     {
11125       gfc_error ("'%s' must be a module procedure or an external procedure with"
11126                  " an explicit interface at %L", proc->name, &where);
11127       goto error;
11128     }
11129   stree->n.tb->subroutine = proc->attr.subroutine;
11130   stree->n.tb->function = proc->attr.function;
11131
11132   /* Find the super-type of the current derived type.  We could do this once and
11133      store in a global if speed is needed, but as long as not I believe this is
11134      more readable and clearer.  */
11135   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11136
11137   /* If PASS, resolve and check arguments if not already resolved / loaded
11138      from a .mod file.  */
11139   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
11140     {
11141       if (stree->n.tb->pass_arg)
11142         {
11143           gfc_formal_arglist* i;
11144
11145           /* If an explicit passing argument name is given, walk the arg-list
11146              and look for it.  */
11147
11148           me_arg = NULL;
11149           stree->n.tb->pass_arg_num = 1;
11150           for (i = proc->formal; i; i = i->next)
11151             {
11152               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
11153                 {
11154                   me_arg = i->sym;
11155                   break;
11156                 }
11157               ++stree->n.tb->pass_arg_num;
11158             }
11159
11160           if (!me_arg)
11161             {
11162               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
11163                          " argument '%s'",
11164                          proc->name, stree->n.tb->pass_arg, &where,
11165                          stree->n.tb->pass_arg);
11166               goto error;
11167             }
11168         }
11169       else
11170         {
11171           /* Otherwise, take the first one; there should in fact be at least
11172              one.  */
11173           stree->n.tb->pass_arg_num = 1;
11174           if (!proc->formal)
11175             {
11176               gfc_error ("Procedure '%s' with PASS at %L must have at"
11177                          " least one argument", proc->name, &where);
11178               goto error;
11179             }
11180           me_arg = proc->formal->sym;
11181         }
11182
11183       /* Now check that the argument-type matches and the passed-object
11184          dummy argument is generally fine.  */
11185
11186       gcc_assert (me_arg);
11187
11188       if (me_arg->ts.type != BT_CLASS)
11189         {
11190           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11191                      " at %L", proc->name, &where);
11192           goto error;
11193         }
11194
11195       if (CLASS_DATA (me_arg)->ts.u.derived
11196           != resolve_bindings_derived)
11197         {
11198           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11199                      " the derived-type '%s'", me_arg->name, proc->name,
11200                      me_arg->name, &where, resolve_bindings_derived->name);
11201           goto error;
11202         }
11203   
11204       gcc_assert (me_arg->ts.type == BT_CLASS);
11205       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
11206         {
11207           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
11208                      " scalar", proc->name, &where);
11209           goto error;
11210         }
11211       if (CLASS_DATA (me_arg)->attr.allocatable)
11212         {
11213           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11214                      " be ALLOCATABLE", proc->name, &where);
11215           goto error;
11216         }
11217       if (CLASS_DATA (me_arg)->attr.class_pointer)
11218         {
11219           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11220                      " be POINTER", proc->name, &where);
11221           goto error;
11222         }
11223     }
11224
11225   /* If we are extending some type, check that we don't override a procedure
11226      flagged NON_OVERRIDABLE.  */
11227   stree->n.tb->overridden = NULL;
11228   if (super_type)
11229     {
11230       gfc_symtree* overridden;
11231       overridden = gfc_find_typebound_proc (super_type, NULL,
11232                                             stree->name, true, NULL);
11233
11234       if (overridden && overridden->n.tb)
11235         stree->n.tb->overridden = overridden->n.tb;
11236
11237       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
11238         goto error;
11239     }
11240
11241   /* See if there's a name collision with a component directly in this type.  */
11242   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
11243     if (!strcmp (comp->name, stree->name))
11244       {
11245         gfc_error ("Procedure '%s' at %L has the same name as a component of"
11246                    " '%s'",
11247                    stree->name, &where, resolve_bindings_derived->name);
11248         goto error;
11249       }
11250
11251   /* Try to find a name collision with an inherited component.  */
11252   if (super_type && gfc_find_component (super_type, stree->name, true, true))
11253     {
11254       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
11255                  " component of '%s'",
11256                  stree->name, &where, resolve_bindings_derived->name);
11257       goto error;
11258     }
11259
11260   stree->n.tb->error = 0;
11261   return;
11262
11263 error:
11264   resolve_bindings_result = FAILURE;
11265   stree->n.tb->error = 1;
11266 }
11267
11268
11269 static gfc_try
11270 resolve_typebound_procedures (gfc_symbol* derived)
11271 {
11272   int op;
11273
11274   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
11275     return SUCCESS;
11276
11277   resolve_bindings_derived = derived;
11278   resolve_bindings_result = SUCCESS;
11279
11280   /* Make sure the vtab has been generated.  */
11281   gfc_find_derived_vtab (derived);
11282
11283   if (derived->f2k_derived->tb_sym_root)
11284     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
11285                           &resolve_typebound_procedure);
11286
11287   if (derived->f2k_derived->tb_uop_root)
11288     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
11289                           &resolve_typebound_user_op);
11290
11291   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
11292     {
11293       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
11294       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
11295                                                p) == FAILURE)
11296         resolve_bindings_result = FAILURE;
11297     }
11298
11299   return resolve_bindings_result;
11300 }
11301
11302
11303 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
11304    to give all identical derived types the same backend_decl.  */
11305 static void
11306 add_dt_to_dt_list (gfc_symbol *derived)
11307 {
11308   gfc_dt_list *dt_list;
11309
11310   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
11311     if (derived == dt_list->derived)
11312       return;
11313
11314   dt_list = gfc_get_dt_list ();
11315   dt_list->next = gfc_derived_types;
11316   dt_list->derived = derived;
11317   gfc_derived_types = dt_list;
11318 }
11319
11320
11321 /* Ensure that a derived-type is really not abstract, meaning that every
11322    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
11323
11324 static gfc_try
11325 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
11326 {
11327   if (!st)
11328     return SUCCESS;
11329
11330   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
11331     return FAILURE;
11332   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
11333     return FAILURE;
11334
11335   if (st->n.tb && st->n.tb->deferred)
11336     {
11337       gfc_symtree* overriding;
11338       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
11339       if (!overriding)
11340         return FAILURE;
11341       gcc_assert (overriding->n.tb);
11342       if (overriding->n.tb->deferred)
11343         {
11344           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
11345                      " '%s' is DEFERRED and not overridden",
11346                      sub->name, &sub->declared_at, st->name);
11347           return FAILURE;
11348         }
11349     }
11350
11351   return SUCCESS;
11352 }
11353
11354 static gfc_try
11355 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
11356 {
11357   /* The algorithm used here is to recursively travel up the ancestry of sub
11358      and for each ancestor-type, check all bindings.  If any of them is
11359      DEFERRED, look it up starting from sub and see if the found (overriding)
11360      binding is not DEFERRED.
11361      This is not the most efficient way to do this, but it should be ok and is
11362      clearer than something sophisticated.  */
11363
11364   gcc_assert (ancestor && !sub->attr.abstract);
11365   
11366   if (!ancestor->attr.abstract)
11367     return SUCCESS;
11368
11369   /* Walk bindings of this ancestor.  */
11370   if (ancestor->f2k_derived)
11371     {
11372       gfc_try t;
11373       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
11374       if (t == FAILURE)
11375         return FAILURE;
11376     }
11377
11378   /* Find next ancestor type and recurse on it.  */
11379   ancestor = gfc_get_derived_super_type (ancestor);
11380   if (ancestor)
11381     return ensure_not_abstract (sub, ancestor);
11382
11383   return SUCCESS;
11384 }
11385
11386
11387 /* Resolve the components of a derived type.  */
11388
11389 static gfc_try
11390 resolve_fl_derived (gfc_symbol *sym)
11391 {
11392   gfc_symbol* super_type;
11393   gfc_component *c;
11394
11395   super_type = gfc_get_derived_super_type (sym);
11396   
11397   if (sym->attr.is_class && sym->ts.u.derived == NULL)
11398     {
11399       /* Fix up incomplete CLASS symbols.  */
11400       gfc_component *data = gfc_find_component (sym, "_data", true, true);
11401       gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true);
11402       if (vptr->ts.u.derived == NULL)
11403         {
11404           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
11405           gcc_assert (vtab);
11406           vptr->ts.u.derived = vtab->ts.u.derived;
11407         }
11408     }
11409
11410   /* F2008, C432. */
11411   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
11412     {
11413       gfc_error ("As extending type '%s' at %L has a coarray component, "
11414                  "parent type '%s' shall also have one", sym->name,
11415                  &sym->declared_at, super_type->name);
11416       return FAILURE;
11417     }
11418
11419   /* Ensure the extended type gets resolved before we do.  */
11420   if (super_type && resolve_fl_derived (super_type) == FAILURE)
11421     return FAILURE;
11422
11423   /* An ABSTRACT type must be extensible.  */
11424   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
11425     {
11426       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
11427                  sym->name, &sym->declared_at);
11428       return FAILURE;
11429     }
11430
11431   for (c = sym->components; c != NULL; c = c->next)
11432     {
11433       /* F2008, C442.  */
11434       if (c->attr.codimension /* FIXME: c->as check due to PR 43412.  */
11435           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
11436         {
11437           gfc_error ("Coarray component '%s' at %L must be allocatable with "
11438                      "deferred shape", c->name, &c->loc);
11439           return FAILURE;
11440         }
11441
11442       /* F2008, C443.  */
11443       if (c->attr.codimension && c->ts.type == BT_DERIVED
11444           && c->ts.u.derived->ts.is_iso_c)
11445         {
11446           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11447                      "shall not be a coarray", c->name, &c->loc);
11448           return FAILURE;
11449         }
11450
11451       /* F2008, C444.  */
11452       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
11453           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
11454               || c->attr.allocatable))
11455         {
11456           gfc_error ("Component '%s' at %L with coarray component "
11457                      "shall be a nonpointer, nonallocatable scalar",
11458                      c->name, &c->loc);
11459           return FAILURE;
11460         }
11461
11462       /* F2008, C448.  */
11463       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
11464         {
11465           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
11466                      "is not an array pointer", c->name, &c->loc);
11467           return FAILURE;
11468         }
11469
11470       if (c->attr.proc_pointer && c->ts.interface)
11471         {
11472           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
11473             gfc_error ("Interface '%s', used by procedure pointer component "
11474                        "'%s' at %L, is declared in a later PROCEDURE statement",
11475                        c->ts.interface->name, c->name, &c->loc);
11476
11477           /* Get the attributes from the interface (now resolved).  */
11478           if (c->ts.interface->attr.if_source
11479               || c->ts.interface->attr.intrinsic)
11480             {
11481               gfc_symbol *ifc = c->ts.interface;
11482
11483               if (ifc->formal && !ifc->formal_ns)
11484                 resolve_symbol (ifc);
11485
11486               if (ifc->attr.intrinsic)
11487                 resolve_intrinsic (ifc, &ifc->declared_at);
11488
11489               if (ifc->result)
11490                 {
11491                   c->ts = ifc->result->ts;
11492                   c->attr.allocatable = ifc->result->attr.allocatable;
11493                   c->attr.pointer = ifc->result->attr.pointer;
11494                   c->attr.dimension = ifc->result->attr.dimension;
11495                   c->as = gfc_copy_array_spec (ifc->result->as);
11496                 }
11497               else
11498                 {   
11499                   c->ts = ifc->ts;
11500                   c->attr.allocatable = ifc->attr.allocatable;
11501                   c->attr.pointer = ifc->attr.pointer;
11502                   c->attr.dimension = ifc->attr.dimension;
11503                   c->as = gfc_copy_array_spec (ifc->as);
11504                 }
11505               c->ts.interface = ifc;
11506               c->attr.function = ifc->attr.function;
11507               c->attr.subroutine = ifc->attr.subroutine;
11508               gfc_copy_formal_args_ppc (c, ifc);
11509
11510               c->attr.pure = ifc->attr.pure;
11511               c->attr.elemental = ifc->attr.elemental;
11512               c->attr.recursive = ifc->attr.recursive;
11513               c->attr.always_explicit = ifc->attr.always_explicit;
11514               c->attr.ext_attr |= ifc->attr.ext_attr;
11515               /* Replace symbols in array spec.  */
11516               if (c->as)
11517                 {
11518                   int i;
11519                   for (i = 0; i < c->as->rank; i++)
11520                     {
11521                       gfc_expr_replace_comp (c->as->lower[i], c);
11522                       gfc_expr_replace_comp (c->as->upper[i], c);
11523                     }
11524                 }
11525               /* Copy char length.  */
11526               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11527                 {
11528                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11529                   gfc_expr_replace_comp (cl->length, c);
11530                   if (cl->length && !cl->resolved
11531                         && gfc_resolve_expr (cl->length) == FAILURE)
11532                     return FAILURE;
11533                   c->ts.u.cl = cl;
11534                 }
11535             }
11536           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
11537             {
11538               gfc_error ("Interface '%s' of procedure pointer component "
11539                          "'%s' at %L must be explicit", c->ts.interface->name,
11540                          c->name, &c->loc);
11541               return FAILURE;
11542             }
11543         }
11544       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
11545         {
11546           /* Since PPCs are not implicitly typed, a PPC without an explicit
11547              interface must be a subroutine.  */
11548           gfc_add_subroutine (&c->attr, c->name, &c->loc);
11549         }
11550
11551       /* Procedure pointer components: Check PASS arg.  */
11552       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
11553           && !sym->attr.vtype)
11554         {
11555           gfc_symbol* me_arg;
11556
11557           if (c->tb->pass_arg)
11558             {
11559               gfc_formal_arglist* i;
11560
11561               /* If an explicit passing argument name is given, walk the arg-list
11562                 and look for it.  */
11563
11564               me_arg = NULL;
11565               c->tb->pass_arg_num = 1;
11566               for (i = c->formal; i; i = i->next)
11567                 {
11568                   if (!strcmp (i->sym->name, c->tb->pass_arg))
11569                     {
11570                       me_arg = i->sym;
11571                       break;
11572                     }
11573                   c->tb->pass_arg_num++;
11574                 }
11575
11576               if (!me_arg)
11577                 {
11578                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
11579                              "at %L has no argument '%s'", c->name,
11580                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
11581                   c->tb->error = 1;
11582                   return FAILURE;
11583                 }
11584             }
11585           else
11586             {
11587               /* Otherwise, take the first one; there should in fact be at least
11588                 one.  */
11589               c->tb->pass_arg_num = 1;
11590               if (!c->formal)
11591                 {
11592                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
11593                              "must have at least one argument",
11594                              c->name, &c->loc);
11595                   c->tb->error = 1;
11596                   return FAILURE;
11597                 }
11598               me_arg = c->formal->sym;
11599             }
11600
11601           /* Now check that the argument-type matches.  */
11602           gcc_assert (me_arg);
11603           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
11604               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
11605               || (me_arg->ts.type == BT_CLASS
11606                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
11607             {
11608               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11609                          " the derived type '%s'", me_arg->name, c->name,
11610                          me_arg->name, &c->loc, sym->name);
11611               c->tb->error = 1;
11612               return FAILURE;
11613             }
11614
11615           /* Check for C453.  */
11616           if (me_arg->attr.dimension)
11617             {
11618               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11619                          "must be scalar", me_arg->name, c->name, me_arg->name,
11620                          &c->loc);
11621               c->tb->error = 1;
11622               return FAILURE;
11623             }
11624
11625           if (me_arg->attr.pointer)
11626             {
11627               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11628                          "may not have the POINTER attribute", me_arg->name,
11629                          c->name, me_arg->name, &c->loc);
11630               c->tb->error = 1;
11631               return FAILURE;
11632             }
11633
11634           if (me_arg->attr.allocatable)
11635             {
11636               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11637                          "may not be ALLOCATABLE", me_arg->name, c->name,
11638                          me_arg->name, &c->loc);
11639               c->tb->error = 1;
11640               return FAILURE;
11641             }
11642
11643           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11644             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11645                        " at %L", c->name, &c->loc);
11646
11647         }
11648
11649       /* Check type-spec if this is not the parent-type component.  */
11650       if ((!sym->attr.extension || c != sym->components) && !sym->attr.vtype
11651           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11652         return FAILURE;
11653
11654       /* If this type is an extension, set the accessibility of the parent
11655          component.  */
11656       if (super_type && c == sym->components
11657           && strcmp (super_type->name, c->name) == 0)
11658         c->attr.access = super_type->attr.access;
11659       
11660       /* If this type is an extension, see if this component has the same name
11661          as an inherited type-bound procedure.  */
11662       if (super_type && !sym->attr.is_class
11663           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11664         {
11665           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11666                      " inherited type-bound procedure",
11667                      c->name, sym->name, &c->loc);
11668           return FAILURE;
11669         }
11670
11671       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer
11672             && !c->ts.deferred)
11673         {
11674          if (c->ts.u.cl->length == NULL
11675              || (resolve_charlen (c->ts.u.cl) == FAILURE)
11676              || !gfc_is_constant_expr (c->ts.u.cl->length))
11677            {
11678              gfc_error ("Character length of component '%s' needs to "
11679                         "be a constant specification expression at %L",
11680                         c->name,
11681                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
11682              return FAILURE;
11683            }
11684         }
11685
11686       if (c->ts.type == BT_CHARACTER && c->ts.deferred
11687           && !c->attr.pointer && !c->attr.allocatable)
11688         {
11689           gfc_error ("Character component '%s' of '%s' at %L with deferred "
11690                      "length must be a POINTER or ALLOCATABLE",
11691                      c->name, sym->name, &c->loc);
11692           return FAILURE;
11693         }
11694
11695       if (c->ts.type == BT_DERIVED
11696           && sym->component_access != ACCESS_PRIVATE
11697           && gfc_check_symbol_access (sym)
11698           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11699           && !c->ts.u.derived->attr.use_assoc
11700           && !gfc_check_symbol_access (c->ts.u.derived)
11701           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11702                              "is a PRIVATE type and cannot be a component of "
11703                              "'%s', which is PUBLIC at %L", c->name,
11704                              sym->name, &sym->declared_at) == FAILURE)
11705         return FAILURE;
11706
11707       if ((sym->attr.sequence || sym->attr.is_bind_c) && c->ts.type == BT_CLASS)
11708         {
11709           gfc_error ("Polymorphic component %s at %L in SEQUENCE or BIND(C) "
11710                      "type %s", c->name, &c->loc, sym->name);
11711           return FAILURE;
11712         }
11713
11714       if (sym->attr.sequence)
11715         {
11716           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
11717             {
11718               gfc_error ("Component %s of SEQUENCE type declared at %L does "
11719                          "not have the SEQUENCE attribute",
11720                          c->ts.u.derived->name, &sym->declared_at);
11721               return FAILURE;
11722             }
11723         }
11724
11725       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && !sym->attr.vtype
11726           && c->attr.pointer && c->ts.u.derived->components == NULL
11727           && !c->ts.u.derived->attr.zero_comp)
11728         {
11729           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11730                      "that has not been declared", c->name, sym->name,
11731                      &c->loc);
11732           return FAILURE;
11733         }
11734
11735       if (c->ts.type == BT_CLASS && CLASS_DATA (c)->attr.class_pointer
11736           && CLASS_DATA (c)->ts.u.derived->components == NULL
11737           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
11738         {
11739           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11740                      "that has not been declared", c->name, sym->name,
11741                      &c->loc);
11742           return FAILURE;
11743         }
11744
11745       /* C437.  */
11746       if (c->ts.type == BT_CLASS
11747           && !(CLASS_DATA (c)->attr.class_pointer
11748                || CLASS_DATA (c)->attr.allocatable))
11749         {
11750           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
11751                      "or pointer", c->name, &c->loc);
11752           return FAILURE;
11753         }
11754
11755       /* Ensure that all the derived type components are put on the
11756          derived type list; even in formal namespaces, where derived type
11757          pointer components might not have been declared.  */
11758       if (c->ts.type == BT_DERIVED
11759             && c->ts.u.derived
11760             && c->ts.u.derived->components
11761             && c->attr.pointer
11762             && sym != c->ts.u.derived)
11763         add_dt_to_dt_list (c->ts.u.derived);
11764
11765       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
11766                                            || c->attr.proc_pointer
11767                                            || c->attr.allocatable)) == FAILURE)
11768         return FAILURE;
11769     }
11770
11771   /* Resolve the type-bound procedures.  */
11772   if (resolve_typebound_procedures (sym) == FAILURE)
11773     return FAILURE;
11774
11775   /* Resolve the finalizer procedures.  */
11776   if (gfc_resolve_finalizers (sym) == FAILURE)
11777     return FAILURE;
11778
11779   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11780      all DEFERRED bindings are overridden.  */
11781   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11782       && !sym->attr.is_class
11783       && ensure_not_abstract (sym, super_type) == FAILURE)
11784     return FAILURE;
11785
11786   /* Add derived type to the derived type list.  */
11787   add_dt_to_dt_list (sym);
11788
11789   return SUCCESS;
11790 }
11791
11792
11793 static gfc_try
11794 resolve_fl_namelist (gfc_symbol *sym)
11795 {
11796   gfc_namelist *nl;
11797   gfc_symbol *nlsym;
11798
11799   for (nl = sym->namelist; nl; nl = nl->next)
11800     {
11801       /* Check again, the check in match only works if NAMELIST comes
11802          after the decl.  */
11803       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SIZE)
11804         {
11805           gfc_error ("Assumed size array '%s' in namelist '%s' at %L is not "
11806                      "allowed", nl->sym->name, sym->name, &sym->declared_at);
11807           return FAILURE;
11808         }
11809
11810       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
11811           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: NAMELIST array "
11812                              "object '%s' with assumed shape in namelist "
11813                              "'%s' at %L", nl->sym->name, sym->name,
11814                              &sym->declared_at) == FAILURE)
11815         return FAILURE;
11816
11817       if (is_non_constant_shape_array (nl->sym)
11818           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST array "
11819                              "object '%s' with nonconstant shape in namelist "
11820                              "'%s' at %L", nl->sym->name, sym->name,
11821                              &sym->declared_at) == FAILURE)
11822         return FAILURE;
11823
11824       if (nl->sym->ts.type == BT_CHARACTER
11825           && (nl->sym->ts.u.cl->length == NULL
11826               || !gfc_is_constant_expr (nl->sym->ts.u.cl->length))
11827           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
11828                              "'%s' with nonconstant character length in "
11829                              "namelist '%s' at %L", nl->sym->name, sym->name,
11830                              &sym->declared_at) == FAILURE)
11831         return FAILURE;
11832
11833       /* FIXME: Once UDDTIO is implemented, the following can be
11834          removed.  */
11835       if (nl->sym->ts.type == BT_CLASS)
11836         {
11837           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L is "
11838                      "polymorphic and requires a defined input/output "
11839                      "procedure", nl->sym->name, sym->name, &sym->declared_at);
11840           return FAILURE;
11841         }
11842
11843       if (nl->sym->ts.type == BT_DERIVED
11844           && (nl->sym->ts.u.derived->attr.alloc_comp
11845               || nl->sym->ts.u.derived->attr.pointer_comp))
11846         {
11847           if (gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
11848                               "'%s' in namelist '%s' at %L with ALLOCATABLE "
11849                               "or POINTER components", nl->sym->name,
11850                               sym->name, &sym->declared_at) == FAILURE)
11851             return FAILURE;
11852
11853          /* FIXME: Once UDDTIO is implemented, the following can be
11854             removed.  */
11855           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L has "
11856                      "ALLOCATABLE or POINTER components and thus requires "
11857                      "a defined input/output procedure", nl->sym->name,
11858                      sym->name, &sym->declared_at);
11859           return FAILURE;
11860         }
11861     }
11862
11863   /* Reject PRIVATE objects in a PUBLIC namelist.  */
11864   if (gfc_check_symbol_access (sym))
11865     {
11866       for (nl = sym->namelist; nl; nl = nl->next)
11867         {
11868           if (!nl->sym->attr.use_assoc
11869               && !is_sym_host_assoc (nl->sym, sym->ns)
11870               && !gfc_check_symbol_access (nl->sym))
11871             {
11872               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
11873                          "cannot be member of PUBLIC namelist '%s' at %L",
11874                          nl->sym->name, sym->name, &sym->declared_at);
11875               return FAILURE;
11876             }
11877
11878           /* Types with private components that came here by USE-association.  */
11879           if (nl->sym->ts.type == BT_DERIVED
11880               && derived_inaccessible (nl->sym->ts.u.derived))
11881             {
11882               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
11883                          "components and cannot be member of namelist '%s' at %L",
11884                          nl->sym->name, sym->name, &sym->declared_at);
11885               return FAILURE;
11886             }
11887
11888           /* Types with private components that are defined in the same module.  */
11889           if (nl->sym->ts.type == BT_DERIVED
11890               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
11891               && nl->sym->ts.u.derived->attr.private_comp)
11892             {
11893               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
11894                          "cannot be a member of PUBLIC namelist '%s' at %L",
11895                          nl->sym->name, sym->name, &sym->declared_at);
11896               return FAILURE;
11897             }
11898         }
11899     }
11900
11901
11902   /* 14.1.2 A module or internal procedure represent local entities
11903      of the same type as a namelist member and so are not allowed.  */
11904   for (nl = sym->namelist; nl; nl = nl->next)
11905     {
11906       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
11907         continue;
11908
11909       if (nl->sym->attr.function && nl->sym == nl->sym->result)
11910         if ((nl->sym == sym->ns->proc_name)
11911                ||
11912             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
11913           continue;
11914
11915       nlsym = NULL;
11916       if (nl->sym && nl->sym->name)
11917         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
11918       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
11919         {
11920           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
11921                      "attribute in '%s' at %L", nlsym->name,
11922                      &sym->declared_at);
11923           return FAILURE;
11924         }
11925     }
11926
11927   return SUCCESS;
11928 }
11929
11930
11931 static gfc_try
11932 resolve_fl_parameter (gfc_symbol *sym)
11933 {
11934   /* A parameter array's shape needs to be constant.  */
11935   if (sym->as != NULL 
11936       && (sym->as->type == AS_DEFERRED
11937           || is_non_constant_shape_array (sym)))
11938     {
11939       gfc_error ("Parameter array '%s' at %L cannot be automatic "
11940                  "or of deferred shape", sym->name, &sym->declared_at);
11941       return FAILURE;
11942     }
11943
11944   /* Make sure a parameter that has been implicitly typed still
11945      matches the implicit type, since PARAMETER statements can precede
11946      IMPLICIT statements.  */
11947   if (sym->attr.implicit_type
11948       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
11949                                                              sym->ns)))
11950     {
11951       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
11952                  "later IMPLICIT type", sym->name, &sym->declared_at);
11953       return FAILURE;
11954     }
11955
11956   /* Make sure the types of derived parameters are consistent.  This
11957      type checking is deferred until resolution because the type may
11958      refer to a derived type from the host.  */
11959   if (sym->ts.type == BT_DERIVED
11960       && !gfc_compare_types (&sym->ts, &sym->value->ts))
11961     {
11962       gfc_error ("Incompatible derived type in PARAMETER at %L",
11963                  &sym->value->where);
11964       return FAILURE;
11965     }
11966   return SUCCESS;
11967 }
11968
11969
11970 /* Do anything necessary to resolve a symbol.  Right now, we just
11971    assume that an otherwise unknown symbol is a variable.  This sort
11972    of thing commonly happens for symbols in module.  */
11973
11974 static void
11975 resolve_symbol (gfc_symbol *sym)
11976 {
11977   int check_constant, mp_flag;
11978   gfc_symtree *symtree;
11979   gfc_symtree *this_symtree;
11980   gfc_namespace *ns;
11981   gfc_component *c;
11982
11983   if (sym->attr.flavor == FL_UNKNOWN)
11984     {
11985
11986     /* If we find that a flavorless symbol is an interface in one of the
11987        parent namespaces, find its symtree in this namespace, free the
11988        symbol and set the symtree to point to the interface symbol.  */
11989       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
11990         {
11991           symtree = gfc_find_symtree (ns->sym_root, sym->name);
11992           if (symtree && (symtree->n.sym->generic ||
11993                           (symtree->n.sym->attr.flavor == FL_PROCEDURE
11994                            && sym->ns->construct_entities)))
11995             {
11996               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
11997                                                sym->name);
11998               gfc_release_symbol (sym);
11999               symtree->n.sym->refs++;
12000               this_symtree->n.sym = symtree->n.sym;
12001               return;
12002             }
12003         }
12004
12005       /* Otherwise give it a flavor according to such attributes as
12006          it has.  */
12007       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
12008         sym->attr.flavor = FL_VARIABLE;
12009       else
12010         {
12011           sym->attr.flavor = FL_PROCEDURE;
12012           if (sym->attr.dimension)
12013             sym->attr.function = 1;
12014         }
12015     }
12016
12017   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
12018     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
12019
12020   if (sym->attr.procedure && sym->ts.interface
12021       && sym->attr.if_source != IFSRC_DECL
12022       && resolve_procedure_interface (sym) == FAILURE)
12023     return;
12024
12025   if (sym->attr.is_protected && !sym->attr.proc_pointer
12026       && (sym->attr.procedure || sym->attr.external))
12027     {
12028       if (sym->attr.external)
12029         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
12030                    "at %L", &sym->declared_at);
12031       else
12032         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
12033                    "at %L", &sym->declared_at);
12034
12035       return;
12036     }
12037
12038
12039   /* F2008, C530. */
12040   if (sym->attr.contiguous
12041       && (!sym->attr.dimension || (sym->as->type != AS_ASSUMED_SHAPE
12042                                    && !sym->attr.pointer)))
12043     {
12044       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
12045                   "array pointer or an assumed-shape array", sym->name,
12046                   &sym->declared_at);
12047       return;
12048     }
12049
12050   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
12051     return;
12052
12053   /* Symbols that are module procedures with results (functions) have
12054      the types and array specification copied for type checking in
12055      procedures that call them, as well as for saving to a module
12056      file.  These symbols can't stand the scrutiny that their results
12057      can.  */
12058   mp_flag = (sym->result != NULL && sym->result != sym);
12059
12060   /* Make sure that the intrinsic is consistent with its internal 
12061      representation. This needs to be done before assigning a default 
12062      type to avoid spurious warnings.  */
12063   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
12064       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
12065     return;
12066
12067   /* Resolve associate names.  */
12068   if (sym->assoc)
12069     resolve_assoc_var (sym, true);
12070
12071   /* Assign default type to symbols that need one and don't have one.  */
12072   if (sym->ts.type == BT_UNKNOWN)
12073     {
12074       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
12075         gfc_set_default_type (sym, 1, NULL);
12076
12077       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
12078           && !sym->attr.function && !sym->attr.subroutine
12079           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
12080         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
12081
12082       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12083         {
12084           /* The specific case of an external procedure should emit an error
12085              in the case that there is no implicit type.  */
12086           if (!mp_flag)
12087             gfc_set_default_type (sym, sym->attr.external, NULL);
12088           else
12089             {
12090               /* Result may be in another namespace.  */
12091               resolve_symbol (sym->result);
12092
12093               if (!sym->result->attr.proc_pointer)
12094                 {
12095                   sym->ts = sym->result->ts;
12096                   sym->as = gfc_copy_array_spec (sym->result->as);
12097                   sym->attr.dimension = sym->result->attr.dimension;
12098                   sym->attr.pointer = sym->result->attr.pointer;
12099                   sym->attr.allocatable = sym->result->attr.allocatable;
12100                   sym->attr.contiguous = sym->result->attr.contiguous;
12101                 }
12102             }
12103         }
12104     }
12105
12106   /* Assumed size arrays and assumed shape arrays must be dummy
12107      arguments.  Array-spec's of implied-shape should have been resolved to
12108      AS_EXPLICIT already.  */
12109
12110   if (sym->as)
12111     {
12112       gcc_assert (sym->as->type != AS_IMPLIED_SHAPE);
12113       if (((sym->as->type == AS_ASSUMED_SIZE && !sym->as->cp_was_assumed)
12114            || sym->as->type == AS_ASSUMED_SHAPE)
12115           && sym->attr.dummy == 0)
12116         {
12117           if (sym->as->type == AS_ASSUMED_SIZE)
12118             gfc_error ("Assumed size array at %L must be a dummy argument",
12119                        &sym->declared_at);
12120           else
12121             gfc_error ("Assumed shape array at %L must be a dummy argument",
12122                        &sym->declared_at);
12123           return;
12124         }
12125     }
12126
12127   /* Make sure symbols with known intent or optional are really dummy
12128      variable.  Because of ENTRY statement, this has to be deferred
12129      until resolution time.  */
12130
12131   if (!sym->attr.dummy
12132       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
12133     {
12134       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
12135       return;
12136     }
12137
12138   if (sym->attr.value && !sym->attr.dummy)
12139     {
12140       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
12141                  "it is not a dummy argument", sym->name, &sym->declared_at);
12142       return;
12143     }
12144
12145   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
12146     {
12147       gfc_charlen *cl = sym->ts.u.cl;
12148       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
12149         {
12150           gfc_error ("Character dummy variable '%s' at %L with VALUE "
12151                      "attribute must have constant length",
12152                      sym->name, &sym->declared_at);
12153           return;
12154         }
12155
12156       if (sym->ts.is_c_interop
12157           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
12158         {
12159           gfc_error ("C interoperable character dummy variable '%s' at %L "
12160                      "with VALUE attribute must have length one",
12161                      sym->name, &sym->declared_at);
12162           return;
12163         }
12164     }
12165
12166   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
12167      do this for something that was implicitly typed because that is handled
12168      in gfc_set_default_type.  Handle dummy arguments and procedure
12169      definitions separately.  Also, anything that is use associated is not
12170      handled here but instead is handled in the module it is declared in.
12171      Finally, derived type definitions are allowed to be BIND(C) since that
12172      only implies that they're interoperable, and they are checked fully for
12173      interoperability when a variable is declared of that type.  */
12174   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
12175       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
12176       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
12177     {
12178       gfc_try t = SUCCESS;
12179       
12180       /* First, make sure the variable is declared at the
12181          module-level scope (J3/04-007, Section 15.3).  */
12182       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
12183           sym->attr.in_common == 0)
12184         {
12185           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
12186                      "is neither a COMMON block nor declared at the "
12187                      "module level scope", sym->name, &(sym->declared_at));
12188           t = FAILURE;
12189         }
12190       else if (sym->common_head != NULL)
12191         {
12192           t = verify_com_block_vars_c_interop (sym->common_head);
12193         }
12194       else
12195         {
12196           /* If type() declaration, we need to verify that the components
12197              of the given type are all C interoperable, etc.  */
12198           if (sym->ts.type == BT_DERIVED &&
12199               sym->ts.u.derived->attr.is_c_interop != 1)
12200             {
12201               /* Make sure the user marked the derived type as BIND(C).  If
12202                  not, call the verify routine.  This could print an error
12203                  for the derived type more than once if multiple variables
12204                  of that type are declared.  */
12205               if (sym->ts.u.derived->attr.is_bind_c != 1)
12206                 verify_bind_c_derived_type (sym->ts.u.derived);
12207               t = FAILURE;
12208             }
12209           
12210           /* Verify the variable itself as C interoperable if it
12211              is BIND(C).  It is not possible for this to succeed if
12212              the verify_bind_c_derived_type failed, so don't have to handle
12213              any error returned by verify_bind_c_derived_type.  */
12214           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
12215                                  sym->common_block);
12216         }
12217
12218       if (t == FAILURE)
12219         {
12220           /* clear the is_bind_c flag to prevent reporting errors more than
12221              once if something failed.  */
12222           sym->attr.is_bind_c = 0;
12223           return;
12224         }
12225     }
12226
12227   /* If a derived type symbol has reached this point, without its
12228      type being declared, we have an error.  Notice that most
12229      conditions that produce undefined derived types have already
12230      been dealt with.  However, the likes of:
12231      implicit type(t) (t) ..... call foo (t) will get us here if
12232      the type is not declared in the scope of the implicit
12233      statement. Change the type to BT_UNKNOWN, both because it is so
12234      and to prevent an ICE.  */
12235   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
12236       && !sym->ts.u.derived->attr.zero_comp)
12237     {
12238       gfc_error ("The derived type '%s' at %L is of type '%s', "
12239                  "which has not been defined", sym->name,
12240                   &sym->declared_at, sym->ts.u.derived->name);
12241       sym->ts.type = BT_UNKNOWN;
12242       return;
12243     }
12244
12245   /* Make sure that the derived type has been resolved and that the
12246      derived type is visible in the symbol's namespace, if it is a
12247      module function and is not PRIVATE.  */
12248   if (sym->ts.type == BT_DERIVED
12249         && sym->ts.u.derived->attr.use_assoc
12250         && sym->ns->proc_name
12251         && sym->ns->proc_name->attr.flavor == FL_MODULE)
12252     {
12253       gfc_symbol *ds;
12254
12255       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
12256         return;
12257
12258       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
12259       if (!ds && sym->attr.function && gfc_check_symbol_access (sym))
12260         {
12261           symtree = gfc_new_symtree (&sym->ns->sym_root,
12262                                      sym->ts.u.derived->name);
12263           symtree->n.sym = sym->ts.u.derived;
12264           sym->ts.u.derived->refs++;
12265         }
12266     }
12267
12268   /* Unless the derived-type declaration is use associated, Fortran 95
12269      does not allow public entries of private derived types.
12270      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
12271      161 in 95-006r3.  */
12272   if (sym->ts.type == BT_DERIVED
12273       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
12274       && !sym->ts.u.derived->attr.use_assoc
12275       && gfc_check_symbol_access (sym)
12276       && !gfc_check_symbol_access (sym->ts.u.derived)
12277       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
12278                          "of PRIVATE derived type '%s'",
12279                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
12280                          : "variable", sym->name, &sym->declared_at,
12281                          sym->ts.u.derived->name) == FAILURE)
12282     return;
12283
12284   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
12285      default initialization is defined (5.1.2.4.4).  */
12286   if (sym->ts.type == BT_DERIVED
12287       && sym->attr.dummy
12288       && sym->attr.intent == INTENT_OUT
12289       && sym->as
12290       && sym->as->type == AS_ASSUMED_SIZE)
12291     {
12292       for (c = sym->ts.u.derived->components; c; c = c->next)
12293         {
12294           if (c->initializer)
12295             {
12296               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
12297                          "ASSUMED SIZE and so cannot have a default initializer",
12298                          sym->name, &sym->declared_at);
12299               return;
12300             }
12301         }
12302     }
12303
12304   /* F2008, C526.  */
12305   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12306        || sym->attr.codimension)
12307       && sym->attr.result)
12308     gfc_error ("Function result '%s' at %L shall not be a coarray or have "
12309                "a coarray component", sym->name, &sym->declared_at);
12310
12311   /* F2008, C524.  */
12312   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
12313       && sym->ts.u.derived->ts.is_iso_c)
12314     gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12315                "shall not be a coarray", sym->name, &sym->declared_at);
12316
12317   /* F2008, C525.  */
12318   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp
12319       && (sym->attr.codimension || sym->attr.pointer || sym->attr.dimension
12320           || sym->attr.allocatable))
12321     gfc_error ("Variable '%s' at %L with coarray component "
12322                "shall be a nonpointer, nonallocatable scalar",
12323                sym->name, &sym->declared_at);
12324
12325   /* F2008, C526.  The function-result case was handled above.  */
12326   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12327        || sym->attr.codimension)
12328       && !(sym->attr.allocatable || sym->attr.dummy || sym->attr.save
12329            || sym->ns->proc_name->attr.flavor == FL_MODULE
12330            || sym->ns->proc_name->attr.is_main_program
12331            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
12332     gfc_error ("Variable '%s' at %L is a coarray or has a coarray "
12333                "component and is not ALLOCATABLE, SAVE nor a "
12334                "dummy argument", sym->name, &sym->declared_at);
12335   /* F2008, C528.  */  /* FIXME: sym->as check due to PR 43412.  */
12336   else if (sym->attr.codimension && !sym->attr.allocatable
12337       && sym->as && sym->as->cotype == AS_DEFERRED)
12338     gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
12339                 "deferred shape", sym->name, &sym->declared_at);
12340   else if (sym->attr.codimension && sym->attr.allocatable
12341       && (sym->as->type != AS_DEFERRED || sym->as->cotype != AS_DEFERRED))
12342     gfc_error ("Allocatable coarray variable '%s' at %L must have "
12343                "deferred shape", sym->name, &sym->declared_at);
12344
12345
12346   /* F2008, C541.  */
12347   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12348        || (sym->attr.codimension && sym->attr.allocatable))
12349       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
12350     gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
12351                "allocatable coarray or have coarray components",
12352                sym->name, &sym->declared_at);
12353
12354   if (sym->attr.codimension && sym->attr.dummy
12355       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
12356     gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
12357                "procedure '%s'", sym->name, &sym->declared_at,
12358                sym->ns->proc_name->name);
12359
12360   switch (sym->attr.flavor)
12361     {
12362     case FL_VARIABLE:
12363       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
12364         return;
12365       break;
12366
12367     case FL_PROCEDURE:
12368       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
12369         return;
12370       break;
12371
12372     case FL_NAMELIST:
12373       if (resolve_fl_namelist (sym) == FAILURE)
12374         return;
12375       break;
12376
12377     case FL_PARAMETER:
12378       if (resolve_fl_parameter (sym) == FAILURE)
12379         return;
12380       break;
12381
12382     default:
12383       break;
12384     }
12385
12386   /* Resolve array specifier. Check as well some constraints
12387      on COMMON blocks.  */
12388
12389   check_constant = sym->attr.in_common && !sym->attr.pointer;
12390
12391   /* Set the formal_arg_flag so that check_conflict will not throw
12392      an error for host associated variables in the specification
12393      expression for an array_valued function.  */
12394   if (sym->attr.function && sym->as)
12395     formal_arg_flag = 1;
12396
12397   gfc_resolve_array_spec (sym->as, check_constant);
12398
12399   formal_arg_flag = 0;
12400
12401   /* Resolve formal namespaces.  */
12402   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
12403       && !sym->attr.contained && !sym->attr.intrinsic)
12404     gfc_resolve (sym->formal_ns);
12405
12406   /* Make sure the formal namespace is present.  */
12407   if (sym->formal && !sym->formal_ns)
12408     {
12409       gfc_formal_arglist *formal = sym->formal;
12410       while (formal && !formal->sym)
12411         formal = formal->next;
12412
12413       if (formal)
12414         {
12415           sym->formal_ns = formal->sym->ns;
12416           sym->formal_ns->refs++;
12417         }
12418     }
12419
12420   /* Check threadprivate restrictions.  */
12421   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
12422       && (!sym->attr.in_common
12423           && sym->module == NULL
12424           && (sym->ns->proc_name == NULL
12425               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
12426     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
12427
12428   /* If we have come this far we can apply default-initializers, as
12429      described in 14.7.5, to those variables that have not already
12430      been assigned one.  */
12431   if (sym->ts.type == BT_DERIVED
12432       && sym->ns == gfc_current_ns
12433       && !sym->value
12434       && !sym->attr.allocatable
12435       && !sym->attr.alloc_comp)
12436     {
12437       symbol_attribute *a = &sym->attr;
12438
12439       if ((!a->save && !a->dummy && !a->pointer
12440            && !a->in_common && !a->use_assoc
12441            && (a->referenced || a->result)
12442            && !(a->function && sym != sym->result))
12443           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
12444         apply_default_init (sym);
12445     }
12446
12447   if (sym->ts.type == BT_CLASS && sym->ns == gfc_current_ns
12448       && sym->attr.dummy && sym->attr.intent == INTENT_OUT
12449       && !CLASS_DATA (sym)->attr.class_pointer
12450       && !CLASS_DATA (sym)->attr.allocatable)
12451     apply_default_init (sym);
12452
12453   /* If this symbol has a type-spec, check it.  */
12454   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
12455       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
12456     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
12457           == FAILURE)
12458       return;
12459 }
12460
12461
12462 /************* Resolve DATA statements *************/
12463
12464 static struct
12465 {
12466   gfc_data_value *vnode;
12467   mpz_t left;
12468 }
12469 values;
12470
12471
12472 /* Advance the values structure to point to the next value in the data list.  */
12473
12474 static gfc_try
12475 next_data_value (void)
12476 {
12477   while (mpz_cmp_ui (values.left, 0) == 0)
12478     {
12479
12480       if (values.vnode->next == NULL)
12481         return FAILURE;
12482
12483       values.vnode = values.vnode->next;
12484       mpz_set (values.left, values.vnode->repeat);
12485     }
12486
12487   return SUCCESS;
12488 }
12489
12490
12491 static gfc_try
12492 check_data_variable (gfc_data_variable *var, locus *where)
12493 {
12494   gfc_expr *e;
12495   mpz_t size;
12496   mpz_t offset;
12497   gfc_try t;
12498   ar_type mark = AR_UNKNOWN;
12499   int i;
12500   mpz_t section_index[GFC_MAX_DIMENSIONS];
12501   gfc_ref *ref;
12502   gfc_array_ref *ar;
12503   gfc_symbol *sym;
12504   int has_pointer;
12505
12506   if (gfc_resolve_expr (var->expr) == FAILURE)
12507     return FAILURE;
12508
12509   ar = NULL;
12510   mpz_init_set_si (offset, 0);
12511   e = var->expr;
12512
12513   if (e->expr_type != EXPR_VARIABLE)
12514     gfc_internal_error ("check_data_variable(): Bad expression");
12515
12516   sym = e->symtree->n.sym;
12517
12518   if (sym->ns->is_block_data && !sym->attr.in_common)
12519     {
12520       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
12521                  sym->name, &sym->declared_at);
12522     }
12523
12524   if (e->ref == NULL && sym->as)
12525     {
12526       gfc_error ("DATA array '%s' at %L must be specified in a previous"
12527                  " declaration", sym->name, where);
12528       return FAILURE;
12529     }
12530
12531   has_pointer = sym->attr.pointer;
12532
12533   if (gfc_is_coindexed (e))
12534     {
12535       gfc_error ("DATA element '%s' at %L cannot have a coindex", sym->name,
12536                  where);
12537       return FAILURE;
12538     }
12539
12540   for (ref = e->ref; ref; ref = ref->next)
12541     {
12542       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
12543         has_pointer = 1;
12544
12545       if (has_pointer
12546             && ref->type == REF_ARRAY
12547             && ref->u.ar.type != AR_FULL)
12548           {
12549             gfc_error ("DATA element '%s' at %L is a pointer and so must "
12550                         "be a full array", sym->name, where);
12551             return FAILURE;
12552           }
12553     }
12554
12555   if (e->rank == 0 || has_pointer)
12556     {
12557       mpz_init_set_ui (size, 1);
12558       ref = NULL;
12559     }
12560   else
12561     {
12562       ref = e->ref;
12563
12564       /* Find the array section reference.  */
12565       for (ref = e->ref; ref; ref = ref->next)
12566         {
12567           if (ref->type != REF_ARRAY)
12568             continue;
12569           if (ref->u.ar.type == AR_ELEMENT)
12570             continue;
12571           break;
12572         }
12573       gcc_assert (ref);
12574
12575       /* Set marks according to the reference pattern.  */
12576       switch (ref->u.ar.type)
12577         {
12578         case AR_FULL:
12579           mark = AR_FULL;
12580           break;
12581
12582         case AR_SECTION:
12583           ar = &ref->u.ar;
12584           /* Get the start position of array section.  */
12585           gfc_get_section_index (ar, section_index, &offset);
12586           mark = AR_SECTION;
12587           break;
12588
12589         default:
12590           gcc_unreachable ();
12591         }
12592
12593       if (gfc_array_size (e, &size) == FAILURE)
12594         {
12595           gfc_error ("Nonconstant array section at %L in DATA statement",
12596                      &e->where);
12597           mpz_clear (offset);
12598           return FAILURE;
12599         }
12600     }
12601
12602   t = SUCCESS;
12603
12604   while (mpz_cmp_ui (size, 0) > 0)
12605     {
12606       if (next_data_value () == FAILURE)
12607         {
12608           gfc_error ("DATA statement at %L has more variables than values",
12609                      where);
12610           t = FAILURE;
12611           break;
12612         }
12613
12614       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
12615       if (t == FAILURE)
12616         break;
12617
12618       /* If we have more than one element left in the repeat count,
12619          and we have more than one element left in the target variable,
12620          then create a range assignment.  */
12621       /* FIXME: Only done for full arrays for now, since array sections
12622          seem tricky.  */
12623       if (mark == AR_FULL && ref && ref->next == NULL
12624           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
12625         {
12626           mpz_t range;
12627
12628           if (mpz_cmp (size, values.left) >= 0)
12629             {
12630               mpz_init_set (range, values.left);
12631               mpz_sub (size, size, values.left);
12632               mpz_set_ui (values.left, 0);
12633             }
12634           else
12635             {
12636               mpz_init_set (range, size);
12637               mpz_sub (values.left, values.left, size);
12638               mpz_set_ui (size, 0);
12639             }
12640
12641           t = gfc_assign_data_value_range (var->expr, values.vnode->expr,
12642                                            offset, range);
12643
12644           mpz_add (offset, offset, range);
12645           mpz_clear (range);
12646
12647           if (t == FAILURE)
12648             break;
12649         }
12650
12651       /* Assign initial value to symbol.  */
12652       else
12653         {
12654           mpz_sub_ui (values.left, values.left, 1);
12655           mpz_sub_ui (size, size, 1);
12656
12657           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
12658           if (t == FAILURE)
12659             break;
12660
12661           if (mark == AR_FULL)
12662             mpz_add_ui (offset, offset, 1);
12663
12664           /* Modify the array section indexes and recalculate the offset
12665              for next element.  */
12666           else if (mark == AR_SECTION)
12667             gfc_advance_section (section_index, ar, &offset);
12668         }
12669     }
12670
12671   if (mark == AR_SECTION)
12672     {
12673       for (i = 0; i < ar->dimen; i++)
12674         mpz_clear (section_index[i]);
12675     }
12676
12677   mpz_clear (size);
12678   mpz_clear (offset);
12679
12680   return t;
12681 }
12682
12683
12684 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
12685
12686 /* Iterate over a list of elements in a DATA statement.  */
12687
12688 static gfc_try
12689 traverse_data_list (gfc_data_variable *var, locus *where)
12690 {
12691   mpz_t trip;
12692   iterator_stack frame;
12693   gfc_expr *e, *start, *end, *step;
12694   gfc_try retval = SUCCESS;
12695
12696   mpz_init (frame.value);
12697   mpz_init (trip);
12698
12699   start = gfc_copy_expr (var->iter.start);
12700   end = gfc_copy_expr (var->iter.end);
12701   step = gfc_copy_expr (var->iter.step);
12702
12703   if (gfc_simplify_expr (start, 1) == FAILURE
12704       || start->expr_type != EXPR_CONSTANT)
12705     {
12706       gfc_error ("start 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   if (gfc_simplify_expr (end, 1) == FAILURE
12712       || end->expr_type != EXPR_CONSTANT)
12713     {
12714       gfc_error ("end of implied-do loop at %L could not be "
12715                  "simplified to a constant value", &start->where);
12716       retval = FAILURE;
12717       goto cleanup;
12718     }
12719   if (gfc_simplify_expr (step, 1) == FAILURE
12720       || step->expr_type != EXPR_CONSTANT)
12721     {
12722       gfc_error ("step of implied-do loop at %L could not be "
12723                  "simplified to a constant value", &start->where);
12724       retval = FAILURE;
12725       goto cleanup;
12726     }
12727
12728   mpz_set (trip, end->value.integer);
12729   mpz_sub (trip, trip, start->value.integer);
12730   mpz_add (trip, trip, step->value.integer);
12731
12732   mpz_div (trip, trip, step->value.integer);
12733
12734   mpz_set (frame.value, start->value.integer);
12735
12736   frame.prev = iter_stack;
12737   frame.variable = var->iter.var->symtree;
12738   iter_stack = &frame;
12739
12740   while (mpz_cmp_ui (trip, 0) > 0)
12741     {
12742       if (traverse_data_var (var->list, where) == FAILURE)
12743         {
12744           retval = FAILURE;
12745           goto cleanup;
12746         }
12747
12748       e = gfc_copy_expr (var->expr);
12749       if (gfc_simplify_expr (e, 1) == FAILURE)
12750         {
12751           gfc_free_expr (e);
12752           retval = FAILURE;
12753           goto cleanup;
12754         }
12755
12756       mpz_add (frame.value, frame.value, step->value.integer);
12757
12758       mpz_sub_ui (trip, trip, 1);
12759     }
12760
12761 cleanup:
12762   mpz_clear (frame.value);
12763   mpz_clear (trip);
12764
12765   gfc_free_expr (start);
12766   gfc_free_expr (end);
12767   gfc_free_expr (step);
12768
12769   iter_stack = frame.prev;
12770   return retval;
12771 }
12772
12773
12774 /* Type resolve variables in the variable list of a DATA statement.  */
12775
12776 static gfc_try
12777 traverse_data_var (gfc_data_variable *var, locus *where)
12778 {
12779   gfc_try t;
12780
12781   for (; var; var = var->next)
12782     {
12783       if (var->expr == NULL)
12784         t = traverse_data_list (var, where);
12785       else
12786         t = check_data_variable (var, where);
12787
12788       if (t == FAILURE)
12789         return FAILURE;
12790     }
12791
12792   return SUCCESS;
12793 }
12794
12795
12796 /* Resolve the expressions and iterators associated with a data statement.
12797    This is separate from the assignment checking because data lists should
12798    only be resolved once.  */
12799
12800 static gfc_try
12801 resolve_data_variables (gfc_data_variable *d)
12802 {
12803   for (; d; d = d->next)
12804     {
12805       if (d->list == NULL)
12806         {
12807           if (gfc_resolve_expr (d->expr) == FAILURE)
12808             return FAILURE;
12809         }
12810       else
12811         {
12812           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
12813             return FAILURE;
12814
12815           if (resolve_data_variables (d->list) == FAILURE)
12816             return FAILURE;
12817         }
12818     }
12819
12820   return SUCCESS;
12821 }
12822
12823
12824 /* Resolve a single DATA statement.  We implement this by storing a pointer to
12825    the value list into static variables, and then recursively traversing the
12826    variables list, expanding iterators and such.  */
12827
12828 static void
12829 resolve_data (gfc_data *d)
12830 {
12831
12832   if (resolve_data_variables (d->var) == FAILURE)
12833     return;
12834
12835   values.vnode = d->value;
12836   if (d->value == NULL)
12837     mpz_set_ui (values.left, 0);
12838   else
12839     mpz_set (values.left, d->value->repeat);
12840
12841   if (traverse_data_var (d->var, &d->where) == FAILURE)
12842     return;
12843
12844   /* At this point, we better not have any values left.  */
12845
12846   if (next_data_value () == SUCCESS)
12847     gfc_error ("DATA statement at %L has more values than variables",
12848                &d->where);
12849 }
12850
12851
12852 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
12853    accessed by host or use association, is a dummy argument to a pure function,
12854    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
12855    is storage associated with any such variable, shall not be used in the
12856    following contexts: (clients of this function).  */
12857
12858 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
12859    procedure.  Returns zero if assignment is OK, nonzero if there is a
12860    problem.  */
12861 int
12862 gfc_impure_variable (gfc_symbol *sym)
12863 {
12864   gfc_symbol *proc;
12865   gfc_namespace *ns;
12866
12867   if (sym->attr.use_assoc || sym->attr.in_common)
12868     return 1;
12869
12870   /* Check if the symbol's ns is inside the pure procedure.  */
12871   for (ns = gfc_current_ns; ns; ns = ns->parent)
12872     {
12873       if (ns == sym->ns)
12874         break;
12875       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
12876         return 1;
12877     }
12878
12879   proc = sym->ns->proc_name;
12880   if (sym->attr.dummy && gfc_pure (proc)
12881         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
12882                 ||
12883              proc->attr.function))
12884     return 1;
12885
12886   /* TODO: Sort out what can be storage associated, if anything, and include
12887      it here.  In principle equivalences should be scanned but it does not
12888      seem to be possible to storage associate an impure variable this way.  */
12889   return 0;
12890 }
12891
12892
12893 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
12894    current namespace is inside a pure procedure.  */
12895
12896 int
12897 gfc_pure (gfc_symbol *sym)
12898 {
12899   symbol_attribute attr;
12900   gfc_namespace *ns;
12901
12902   if (sym == NULL)
12903     {
12904       /* Check if the current namespace or one of its parents
12905         belongs to a pure procedure.  */
12906       for (ns = gfc_current_ns; ns; ns = ns->parent)
12907         {
12908           sym = ns->proc_name;
12909           if (sym == NULL)
12910             return 0;
12911           attr = sym->attr;
12912           if (attr.flavor == FL_PROCEDURE && attr.pure)
12913             return 1;
12914         }
12915       return 0;
12916     }
12917
12918   attr = sym->attr;
12919
12920   return attr.flavor == FL_PROCEDURE && attr.pure;
12921 }
12922
12923
12924 /* Test whether a symbol is implicitly pure or not.  For a NULL pointer,
12925    checks if the current namespace is implicitly pure.  Note that this
12926    function returns false for a PURE procedure.  */
12927
12928 int
12929 gfc_implicit_pure (gfc_symbol *sym)
12930 {
12931   symbol_attribute attr;
12932
12933   if (sym == NULL)
12934     {
12935       /* Check if the current namespace is implicit_pure.  */
12936       sym = gfc_current_ns->proc_name;
12937       if (sym == NULL)
12938         return 0;
12939       attr = sym->attr;
12940       if (attr.flavor == FL_PROCEDURE
12941             && attr.implicit_pure && !attr.pure)
12942         return 1;
12943       return 0;
12944     }
12945
12946   attr = sym->attr;
12947
12948   return attr.flavor == FL_PROCEDURE && attr.implicit_pure && !attr.pure;
12949 }
12950
12951
12952 /* Test whether the current procedure is elemental or not.  */
12953
12954 int
12955 gfc_elemental (gfc_symbol *sym)
12956 {
12957   symbol_attribute attr;
12958
12959   if (sym == NULL)
12960     sym = gfc_current_ns->proc_name;
12961   if (sym == NULL)
12962     return 0;
12963   attr = sym->attr;
12964
12965   return attr.flavor == FL_PROCEDURE && attr.elemental;
12966 }
12967
12968
12969 /* Warn about unused labels.  */
12970
12971 static void
12972 warn_unused_fortran_label (gfc_st_label *label)
12973 {
12974   if (label == NULL)
12975     return;
12976
12977   warn_unused_fortran_label (label->left);
12978
12979   if (label->defined == ST_LABEL_UNKNOWN)
12980     return;
12981
12982   switch (label->referenced)
12983     {
12984     case ST_LABEL_UNKNOWN:
12985       gfc_warning ("Label %d at %L defined but not used", label->value,
12986                    &label->where);
12987       break;
12988
12989     case ST_LABEL_BAD_TARGET:
12990       gfc_warning ("Label %d at %L defined but cannot be used",
12991                    label->value, &label->where);
12992       break;
12993
12994     default:
12995       break;
12996     }
12997
12998   warn_unused_fortran_label (label->right);
12999 }
13000
13001
13002 /* Returns the sequence type of a symbol or sequence.  */
13003
13004 static seq_type
13005 sequence_type (gfc_typespec ts)
13006 {
13007   seq_type result;
13008   gfc_component *c;
13009
13010   switch (ts.type)
13011   {
13012     case BT_DERIVED:
13013
13014       if (ts.u.derived->components == NULL)
13015         return SEQ_NONDEFAULT;
13016
13017       result = sequence_type (ts.u.derived->components->ts);
13018       for (c = ts.u.derived->components->next; c; c = c->next)
13019         if (sequence_type (c->ts) != result)
13020           return SEQ_MIXED;
13021
13022       return result;
13023
13024     case BT_CHARACTER:
13025       if (ts.kind != gfc_default_character_kind)
13026           return SEQ_NONDEFAULT;
13027
13028       return SEQ_CHARACTER;
13029
13030     case BT_INTEGER:
13031       if (ts.kind != gfc_default_integer_kind)
13032           return SEQ_NONDEFAULT;
13033
13034       return SEQ_NUMERIC;
13035
13036     case BT_REAL:
13037       if (!(ts.kind == gfc_default_real_kind
13038             || ts.kind == gfc_default_double_kind))
13039           return SEQ_NONDEFAULT;
13040
13041       return SEQ_NUMERIC;
13042
13043     case BT_COMPLEX:
13044       if (ts.kind != gfc_default_complex_kind)
13045           return SEQ_NONDEFAULT;
13046
13047       return SEQ_NUMERIC;
13048
13049     case BT_LOGICAL:
13050       if (ts.kind != gfc_default_logical_kind)
13051           return SEQ_NONDEFAULT;
13052
13053       return SEQ_NUMERIC;
13054
13055     default:
13056       return SEQ_NONDEFAULT;
13057   }
13058 }
13059
13060
13061 /* Resolve derived type EQUIVALENCE object.  */
13062
13063 static gfc_try
13064 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
13065 {
13066   gfc_component *c = derived->components;
13067
13068   if (!derived)
13069     return SUCCESS;
13070
13071   /* Shall not be an object of nonsequence derived type.  */
13072   if (!derived->attr.sequence)
13073     {
13074       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
13075                  "attribute to be an EQUIVALENCE object", sym->name,
13076                  &e->where);
13077       return FAILURE;
13078     }
13079
13080   /* Shall not have allocatable components.  */
13081   if (derived->attr.alloc_comp)
13082     {
13083       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
13084                  "components to be an EQUIVALENCE object",sym->name,
13085                  &e->where);
13086       return FAILURE;
13087     }
13088
13089   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
13090     {
13091       gfc_error ("Derived type variable '%s' at %L with default "
13092                  "initialization cannot be in EQUIVALENCE with a variable "
13093                  "in COMMON", sym->name, &e->where);
13094       return FAILURE;
13095     }
13096
13097   for (; c ; c = c->next)
13098     {
13099       if (c->ts.type == BT_DERIVED
13100           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
13101         return FAILURE;
13102
13103       /* Shall not be an object of sequence derived type containing a pointer
13104          in the structure.  */
13105       if (c->attr.pointer)
13106         {
13107           gfc_error ("Derived type variable '%s' at %L with pointer "
13108                      "component(s) cannot be an EQUIVALENCE object",
13109                      sym->name, &e->where);
13110           return FAILURE;
13111         }
13112     }
13113   return SUCCESS;
13114 }
13115
13116
13117 /* Resolve equivalence object. 
13118    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
13119    an allocatable array, an object of nonsequence derived type, an object of
13120    sequence derived type containing a pointer at any level of component
13121    selection, an automatic object, a function name, an entry name, a result
13122    name, a named constant, a structure component, or a subobject of any of
13123    the preceding objects.  A substring shall not have length zero.  A
13124    derived type shall not have components with default initialization nor
13125    shall two objects of an equivalence group be initialized.
13126    Either all or none of the objects shall have an protected attribute.
13127    The simple constraints are done in symbol.c(check_conflict) and the rest
13128    are implemented here.  */
13129
13130 static void
13131 resolve_equivalence (gfc_equiv *eq)
13132 {
13133   gfc_symbol *sym;
13134   gfc_symbol *first_sym;
13135   gfc_expr *e;
13136   gfc_ref *r;
13137   locus *last_where = NULL;
13138   seq_type eq_type, last_eq_type;
13139   gfc_typespec *last_ts;
13140   int object, cnt_protected;
13141   const char *msg;
13142
13143   last_ts = &eq->expr->symtree->n.sym->ts;
13144
13145   first_sym = eq->expr->symtree->n.sym;
13146
13147   cnt_protected = 0;
13148
13149   for (object = 1; eq; eq = eq->eq, object++)
13150     {
13151       e = eq->expr;
13152
13153       e->ts = e->symtree->n.sym->ts;
13154       /* match_varspec might not know yet if it is seeing
13155          array reference or substring reference, as it doesn't
13156          know the types.  */
13157       if (e->ref && e->ref->type == REF_ARRAY)
13158         {
13159           gfc_ref *ref = e->ref;
13160           sym = e->symtree->n.sym;
13161
13162           if (sym->attr.dimension)
13163             {
13164               ref->u.ar.as = sym->as;
13165               ref = ref->next;
13166             }
13167
13168           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
13169           if (e->ts.type == BT_CHARACTER
13170               && ref
13171               && ref->type == REF_ARRAY
13172               && ref->u.ar.dimen == 1
13173               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
13174               && ref->u.ar.stride[0] == NULL)
13175             {
13176               gfc_expr *start = ref->u.ar.start[0];
13177               gfc_expr *end = ref->u.ar.end[0];
13178               void *mem = NULL;
13179
13180               /* Optimize away the (:) reference.  */
13181               if (start == NULL && end == NULL)
13182                 {
13183                   if (e->ref == ref)
13184                     e->ref = ref->next;
13185                   else
13186                     e->ref->next = ref->next;
13187                   mem = ref;
13188                 }
13189               else
13190                 {
13191                   ref->type = REF_SUBSTRING;
13192                   if (start == NULL)
13193                     start = gfc_get_int_expr (gfc_default_integer_kind,
13194                                               NULL, 1);
13195                   ref->u.ss.start = start;
13196                   if (end == NULL && e->ts.u.cl)
13197                     end = gfc_copy_expr (e->ts.u.cl->length);
13198                   ref->u.ss.end = end;
13199                   ref->u.ss.length = e->ts.u.cl;
13200                   e->ts.u.cl = NULL;
13201                 }
13202               ref = ref->next;
13203               free (mem);
13204             }
13205
13206           /* Any further ref is an error.  */
13207           if (ref)
13208             {
13209               gcc_assert (ref->type == REF_ARRAY);
13210               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
13211                          &ref->u.ar.where);
13212               continue;
13213             }
13214         }
13215
13216       if (gfc_resolve_expr (e) == FAILURE)
13217         continue;
13218
13219       sym = e->symtree->n.sym;
13220
13221       if (sym->attr.is_protected)
13222         cnt_protected++;
13223       if (cnt_protected > 0 && cnt_protected != object)
13224         {
13225               gfc_error ("Either all or none of the objects in the "
13226                          "EQUIVALENCE set at %L shall have the "
13227                          "PROTECTED attribute",
13228                          &e->where);
13229               break;
13230         }
13231
13232       /* Shall not equivalence common block variables in a PURE procedure.  */
13233       if (sym->ns->proc_name
13234           && sym->ns->proc_name->attr.pure
13235           && sym->attr.in_common)
13236         {
13237           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
13238                      "object in the pure procedure '%s'",
13239                      sym->name, &e->where, sym->ns->proc_name->name);
13240           break;
13241         }
13242
13243       /* Shall not be a named constant.  */
13244       if (e->expr_type == EXPR_CONSTANT)
13245         {
13246           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
13247                      "object", sym->name, &e->where);
13248           continue;
13249         }
13250
13251       if (e->ts.type == BT_DERIVED
13252           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
13253         continue;
13254
13255       /* Check that the types correspond correctly:
13256          Note 5.28:
13257          A numeric sequence structure may be equivalenced to another sequence
13258          structure, an object of default integer type, default real type, double
13259          precision real type, default logical type such that components of the
13260          structure ultimately only become associated to objects of the same
13261          kind. A character sequence structure may be equivalenced to an object
13262          of default character kind or another character sequence structure.
13263          Other objects may be equivalenced only to objects of the same type and
13264          kind parameters.  */
13265
13266       /* Identical types are unconditionally OK.  */
13267       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
13268         goto identical_types;
13269
13270       last_eq_type = sequence_type (*last_ts);
13271       eq_type = sequence_type (sym->ts);
13272
13273       /* Since the pair of objects is not of the same type, mixed or
13274          non-default sequences can be rejected.  */
13275
13276       msg = "Sequence %s with mixed components in EQUIVALENCE "
13277             "statement at %L with different type objects";
13278       if ((object ==2
13279            && last_eq_type == SEQ_MIXED
13280            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
13281               == FAILURE)
13282           || (eq_type == SEQ_MIXED
13283               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13284                                  &e->where) == FAILURE))
13285         continue;
13286
13287       msg = "Non-default type object or sequence %s in EQUIVALENCE "
13288             "statement at %L with objects of different type";
13289       if ((object ==2
13290            && last_eq_type == SEQ_NONDEFAULT
13291            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
13292                               last_where) == FAILURE)
13293           || (eq_type == SEQ_NONDEFAULT
13294               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13295                                  &e->where) == FAILURE))
13296         continue;
13297
13298       msg ="Non-CHARACTER object '%s' in default CHARACTER "
13299            "EQUIVALENCE statement at %L";
13300       if (last_eq_type == SEQ_CHARACTER
13301           && eq_type != SEQ_CHARACTER
13302           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13303                              &e->where) == FAILURE)
13304                 continue;
13305
13306       msg ="Non-NUMERIC object '%s' in default NUMERIC "
13307            "EQUIVALENCE statement at %L";
13308       if (last_eq_type == SEQ_NUMERIC
13309           && eq_type != SEQ_NUMERIC
13310           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13311                              &e->where) == FAILURE)
13312                 continue;
13313
13314   identical_types:
13315       last_ts =&sym->ts;
13316       last_where = &e->where;
13317
13318       if (!e->ref)
13319         continue;
13320
13321       /* Shall not be an automatic array.  */
13322       if (e->ref->type == REF_ARRAY
13323           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
13324         {
13325           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
13326                      "an EQUIVALENCE object", sym->name, &e->where);
13327           continue;
13328         }
13329
13330       r = e->ref;
13331       while (r)
13332         {
13333           /* Shall not be a structure component.  */
13334           if (r->type == REF_COMPONENT)
13335             {
13336               gfc_error ("Structure component '%s' at %L cannot be an "
13337                          "EQUIVALENCE object",
13338                          r->u.c.component->name, &e->where);
13339               break;
13340             }
13341
13342           /* A substring shall not have length zero.  */
13343           if (r->type == REF_SUBSTRING)
13344             {
13345               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
13346                 {
13347                   gfc_error ("Substring at %L has length zero",
13348                              &r->u.ss.start->where);
13349                   break;
13350                 }
13351             }
13352           r = r->next;
13353         }
13354     }
13355 }
13356
13357
13358 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
13359
13360 static void
13361 resolve_fntype (gfc_namespace *ns)
13362 {
13363   gfc_entry_list *el;
13364   gfc_symbol *sym;
13365
13366   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
13367     return;
13368
13369   /* If there are any entries, ns->proc_name is the entry master
13370      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
13371   if (ns->entries)
13372     sym = ns->entries->sym;
13373   else
13374     sym = ns->proc_name;
13375   if (sym->result == sym
13376       && sym->ts.type == BT_UNKNOWN
13377       && gfc_set_default_type (sym, 0, NULL) == FAILURE
13378       && !sym->attr.untyped)
13379     {
13380       gfc_error ("Function '%s' at %L has no IMPLICIT type",
13381                  sym->name, &sym->declared_at);
13382       sym->attr.untyped = 1;
13383     }
13384
13385   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
13386       && !sym->attr.contained
13387       && !gfc_check_symbol_access (sym->ts.u.derived)
13388       && gfc_check_symbol_access (sym))
13389     {
13390       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
13391                       "%L of PRIVATE type '%s'", sym->name,
13392                       &sym->declared_at, sym->ts.u.derived->name);
13393     }
13394
13395     if (ns->entries)
13396     for (el = ns->entries->next; el; el = el->next)
13397       {
13398         if (el->sym->result == el->sym
13399             && el->sym->ts.type == BT_UNKNOWN
13400             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
13401             && !el->sym->attr.untyped)
13402           {
13403             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
13404                        el->sym->name, &el->sym->declared_at);
13405             el->sym->attr.untyped = 1;
13406           }
13407       }
13408 }
13409
13410
13411 /* 12.3.2.1.1 Defined operators.  */
13412
13413 static gfc_try
13414 check_uop_procedure (gfc_symbol *sym, locus where)
13415 {
13416   gfc_formal_arglist *formal;
13417
13418   if (!sym->attr.function)
13419     {
13420       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
13421                  sym->name, &where);
13422       return FAILURE;
13423     }
13424
13425   if (sym->ts.type == BT_CHARACTER
13426       && !(sym->ts.u.cl && sym->ts.u.cl->length)
13427       && !(sym->result && sym->result->ts.u.cl
13428            && sym->result->ts.u.cl->length))
13429     {
13430       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
13431                  "character length", sym->name, &where);
13432       return FAILURE;
13433     }
13434
13435   formal = sym->formal;
13436   if (!formal || !formal->sym)
13437     {
13438       gfc_error ("User operator procedure '%s' at %L must have at least "
13439                  "one argument", sym->name, &where);
13440       return FAILURE;
13441     }
13442
13443   if (formal->sym->attr.intent != INTENT_IN)
13444     {
13445       gfc_error ("First argument of operator interface at %L must be "
13446                  "INTENT(IN)", &where);
13447       return FAILURE;
13448     }
13449
13450   if (formal->sym->attr.optional)
13451     {
13452       gfc_error ("First argument of operator interface at %L cannot be "
13453                  "optional", &where);
13454       return FAILURE;
13455     }
13456
13457   formal = formal->next;
13458   if (!formal || !formal->sym)
13459     return SUCCESS;
13460
13461   if (formal->sym->attr.intent != INTENT_IN)
13462     {
13463       gfc_error ("Second argument of operator interface at %L must be "
13464                  "INTENT(IN)", &where);
13465       return FAILURE;
13466     }
13467
13468   if (formal->sym->attr.optional)
13469     {
13470       gfc_error ("Second argument of operator interface at %L cannot be "
13471                  "optional", &where);
13472       return FAILURE;
13473     }
13474
13475   if (formal->next)
13476     {
13477       gfc_error ("Operator interface at %L must have, at most, two "
13478                  "arguments", &where);
13479       return FAILURE;
13480     }
13481
13482   return SUCCESS;
13483 }
13484
13485 static void
13486 gfc_resolve_uops (gfc_symtree *symtree)
13487 {
13488   gfc_interface *itr;
13489
13490   if (symtree == NULL)
13491     return;
13492
13493   gfc_resolve_uops (symtree->left);
13494   gfc_resolve_uops (symtree->right);
13495
13496   for (itr = symtree->n.uop->op; itr; itr = itr->next)
13497     check_uop_procedure (itr->sym, itr->sym->declared_at);
13498 }
13499
13500
13501 /* Examine all of the expressions associated with a program unit,
13502    assign types to all intermediate expressions, make sure that all
13503    assignments are to compatible types and figure out which names
13504    refer to which functions or subroutines.  It doesn't check code
13505    block, which is handled by resolve_code.  */
13506
13507 static void
13508 resolve_types (gfc_namespace *ns)
13509 {
13510   gfc_namespace *n;
13511   gfc_charlen *cl;
13512   gfc_data *d;
13513   gfc_equiv *eq;
13514   gfc_namespace* old_ns = gfc_current_ns;
13515
13516   /* Check that all IMPLICIT types are ok.  */
13517   if (!ns->seen_implicit_none)
13518     {
13519       unsigned letter;
13520       for (letter = 0; letter != GFC_LETTERS; ++letter)
13521         if (ns->set_flag[letter]
13522             && resolve_typespec_used (&ns->default_type[letter],
13523                                       &ns->implicit_loc[letter],
13524                                       NULL) == FAILURE)
13525           return;
13526     }
13527
13528   gfc_current_ns = ns;
13529
13530   resolve_entries (ns);
13531
13532   resolve_common_vars (ns->blank_common.head, false);
13533   resolve_common_blocks (ns->common_root);
13534
13535   resolve_contained_functions (ns);
13536
13537   if (ns->proc_name && ns->proc_name->attr.flavor == FL_PROCEDURE
13538       && ns->proc_name->attr.if_source == IFSRC_IFBODY)
13539     resolve_formal_arglist (ns->proc_name);
13540
13541   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
13542
13543   for (cl = ns->cl_list; cl; cl = cl->next)
13544     resolve_charlen (cl);
13545
13546   gfc_traverse_ns (ns, resolve_symbol);
13547
13548   resolve_fntype (ns);
13549
13550   for (n = ns->contained; n; n = n->sibling)
13551     {
13552       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
13553         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
13554                    "also be PURE", n->proc_name->name,
13555                    &n->proc_name->declared_at);
13556
13557       resolve_types (n);
13558     }
13559
13560   forall_flag = 0;
13561   gfc_check_interfaces (ns);
13562
13563   gfc_traverse_ns (ns, resolve_values);
13564
13565   if (ns->save_all)
13566     gfc_save_all (ns);
13567
13568   iter_stack = NULL;
13569   for (d = ns->data; d; d = d->next)
13570     resolve_data (d);
13571
13572   iter_stack = NULL;
13573   gfc_traverse_ns (ns, gfc_formalize_init_value);
13574
13575   gfc_traverse_ns (ns, gfc_verify_binding_labels);
13576
13577   if (ns->common_root != NULL)
13578     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
13579
13580   for (eq = ns->equiv; eq; eq = eq->next)
13581     resolve_equivalence (eq);
13582
13583   /* Warn about unused labels.  */
13584   if (warn_unused_label)
13585     warn_unused_fortran_label (ns->st_labels);
13586
13587   gfc_resolve_uops (ns->uop_root);
13588
13589   gfc_current_ns = old_ns;
13590 }
13591
13592
13593 /* Call resolve_code recursively.  */
13594
13595 static void
13596 resolve_codes (gfc_namespace *ns)
13597 {
13598   gfc_namespace *n;
13599   bitmap_obstack old_obstack;
13600
13601   if (ns->resolved == 1)
13602     return;
13603
13604   for (n = ns->contained; n; n = n->sibling)
13605     resolve_codes (n);
13606
13607   gfc_current_ns = ns;
13608
13609   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
13610   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
13611     cs_base = NULL;
13612
13613   /* Set to an out of range value.  */
13614   current_entry_id = -1;
13615
13616   old_obstack = labels_obstack;
13617   bitmap_obstack_initialize (&labels_obstack);
13618
13619   resolve_code (ns->code, ns);
13620
13621   bitmap_obstack_release (&labels_obstack);
13622   labels_obstack = old_obstack;
13623 }
13624
13625
13626 /* This function is called after a complete program unit has been compiled.
13627    Its purpose is to examine all of the expressions associated with a program
13628    unit, assign types to all intermediate expressions, make sure that all
13629    assignments are to compatible types and figure out which names refer to
13630    which functions or subroutines.  */
13631
13632 void
13633 gfc_resolve (gfc_namespace *ns)
13634 {
13635   gfc_namespace *old_ns;
13636   code_stack *old_cs_base;
13637
13638   if (ns->resolved)
13639     return;
13640
13641   ns->resolved = -1;
13642   old_ns = gfc_current_ns;
13643   old_cs_base = cs_base;
13644
13645   resolve_types (ns);
13646   resolve_codes (ns);
13647
13648   gfc_current_ns = old_ns;
13649   cs_base = old_cs_base;
13650   ns->resolved = 1;
13651
13652   gfc_run_passes (ns);
13653 }