OSDN Git Service

2012-01-30 Pascal Obry <obry@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009,
3    2010, 2011, 2012
4    Free Software Foundation, Inc.
5    Contributed by Andy Vaught
6
7 This file is part of GCC.
8
9 GCC is free software; you can redistribute it and/or modify it under
10 the terms of the GNU General Public License as published by the Free
11 Software Foundation; either version 3, or (at your option) any later
12 version.
13
14 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15 WARRANTY; without even the implied warranty of MERCHANTABILITY or
16 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
17 for more details.
18
19 You should have received a copy of the GNU General Public License
20 along with GCC; see the file COPYING3.  If not see
21 <http://www.gnu.org/licenses/>.  */
22
23 #include "config.h"
24 #include "system.h"
25 #include "flags.h"
26 #include "gfortran.h"
27 #include "obstack.h"
28 #include "bitmap.h"
29 #include "arith.h"  /* For gfc_compare_expr().  */
30 #include "dependency.h"
31 #include "data.h"
32 #include "target-memory.h" /* for gfc_simplify_transfer */
33 #include "constructor.h"
34
35 /* Types used in equivalence statements.  */
36
37 typedef enum seq_type
38 {
39   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
40 }
41 seq_type;
42
43 /* Stack to keep track of the nesting of blocks as we move through the
44    code.  See resolve_branch() and resolve_code().  */
45
46 typedef struct code_stack
47 {
48   struct gfc_code *head, *current;
49   struct code_stack *prev;
50
51   /* This bitmap keeps track of the targets valid for a branch from
52      inside this block except for END {IF|SELECT}s of enclosing
53      blocks.  */
54   bitmap reachable_labels;
55 }
56 code_stack;
57
58 static code_stack *cs_base = NULL;
59
60
61 /* Nonzero if we're inside a FORALL or DO CONCURRENT block.  */
62
63 static int forall_flag;
64 static int do_concurrent_flag;
65
66 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
67
68 static int omp_workshare_flag;
69
70 /* Nonzero if we are processing a formal arglist. The corresponding function
71    resets the flag each time that it is read.  */
72 static int formal_arg_flag = 0;
73
74 /* True if we are resolving a specification expression.  */
75 static int specification_expr = 0;
76
77 /* The id of the last entry seen.  */
78 static int current_entry_id;
79
80 /* We use bitmaps to determine if a branch target is valid.  */
81 static bitmap_obstack labels_obstack;
82
83 /* True when simplifying a EXPR_VARIABLE argument to an inquiry function.  */
84 static bool inquiry_argument = false;
85
86 int
87 gfc_is_formal_arg (void)
88 {
89   return formal_arg_flag;
90 }
91
92 /* Is the symbol host associated?  */
93 static bool
94 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
95 {
96   for (ns = ns->parent; ns; ns = ns->parent)
97     {      
98       if (sym->ns == ns)
99         return true;
100     }
101
102   return false;
103 }
104
105 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
106    an ABSTRACT derived-type.  If where is not NULL, an error message with that
107    locus is printed, optionally using name.  */
108
109 static gfc_try
110 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
111 {
112   if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
113     {
114       if (where)
115         {
116           if (name)
117             gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
118                        name, where, ts->u.derived->name);
119           else
120             gfc_error ("ABSTRACT type '%s' used at %L",
121                        ts->u.derived->name, where);
122         }
123
124       return FAILURE;
125     }
126
127   return SUCCESS;
128 }
129
130
131 static void resolve_symbol (gfc_symbol *sym);
132 static gfc_try resolve_intrinsic (gfc_symbol *sym, locus *loc);
133
134
135 /* Resolve the interface for a PROCEDURE declaration or procedure pointer.  */
136
137 static gfc_try
138 resolve_procedure_interface (gfc_symbol *sym)
139 {
140   if (sym->ts.interface == sym)
141     {
142       gfc_error ("PROCEDURE '%s' at %L may not be used as its own interface",
143                  sym->name, &sym->declared_at);
144       return FAILURE;
145     }
146   if (sym->ts.interface->attr.procedure)
147     {
148       gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared "
149                  "in a later PROCEDURE statement", sym->ts.interface->name,
150                  sym->name, &sym->declared_at);
151       return FAILURE;
152     }
153
154   /* Get the attributes from the interface (now resolved).  */
155   if (sym->ts.interface->attr.if_source || sym->ts.interface->attr.intrinsic)
156     {
157       gfc_symbol *ifc = sym->ts.interface;
158       resolve_symbol (ifc);
159
160       if (ifc->attr.intrinsic)
161         resolve_intrinsic (ifc, &ifc->declared_at);
162
163       if (ifc->result)
164         {
165           sym->ts = ifc->result->ts;
166           sym->result = sym;
167         }
168       else   
169         sym->ts = ifc->ts;
170       sym->ts.interface = ifc;
171       sym->attr.function = ifc->attr.function;
172       sym->attr.subroutine = ifc->attr.subroutine;
173       gfc_copy_formal_args (sym, ifc);
174
175       sym->attr.allocatable = ifc->attr.allocatable;
176       sym->attr.pointer = ifc->attr.pointer;
177       sym->attr.pure = ifc->attr.pure;
178       sym->attr.elemental = ifc->attr.elemental;
179       sym->attr.dimension = ifc->attr.dimension;
180       sym->attr.contiguous = ifc->attr.contiguous;
181       sym->attr.recursive = ifc->attr.recursive;
182       sym->attr.always_explicit = ifc->attr.always_explicit;
183       sym->attr.ext_attr |= ifc->attr.ext_attr;
184       sym->attr.is_bind_c = ifc->attr.is_bind_c;
185       /* Copy array spec.  */
186       sym->as = gfc_copy_array_spec (ifc->as);
187       if (sym->as)
188         {
189           int i;
190           for (i = 0; i < sym->as->rank; i++)
191             {
192               gfc_expr_replace_symbols (sym->as->lower[i], sym);
193               gfc_expr_replace_symbols (sym->as->upper[i], sym);
194             }
195         }
196       /* Copy char length.  */
197       if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
198         {
199           sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
200           gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
201           if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
202               && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
203             return FAILURE;
204         }
205     }
206   else if (sym->ts.interface->name[0] != '\0')
207     {
208       gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
209                  sym->ts.interface->name, sym->name, &sym->declared_at);
210       return FAILURE;
211     }
212
213   return SUCCESS;
214 }
215
216
217 /* Resolve types of formal argument lists.  These have to be done early so that
218    the formal argument lists of module procedures can be copied to the
219    containing module before the individual procedures are resolved
220    individually.  We also resolve argument lists of procedures in interface
221    blocks because they are self-contained scoping units.
222
223    Since a dummy argument cannot be a non-dummy procedure, the only
224    resort left for untyped names are the IMPLICIT types.  */
225
226 static void
227 resolve_formal_arglist (gfc_symbol *proc)
228 {
229   gfc_formal_arglist *f;
230   gfc_symbol *sym;
231   int i;
232
233   if (proc->result != NULL)
234     sym = proc->result;
235   else
236     sym = proc;
237
238   if (gfc_elemental (proc)
239       || sym->attr.pointer || sym->attr.allocatable
240       || (sym->as && sym->as->rank > 0))
241     {
242       proc->attr.always_explicit = 1;
243       sym->attr.always_explicit = 1;
244     }
245
246   formal_arg_flag = 1;
247
248   for (f = proc->formal; f; f = f->next)
249     {
250       sym = f->sym;
251
252       if (sym == NULL)
253         {
254           /* Alternate return placeholder.  */
255           if (gfc_elemental (proc))
256             gfc_error ("Alternate return specifier in elemental subroutine "
257                        "'%s' at %L is not allowed", proc->name,
258                        &proc->declared_at);
259           if (proc->attr.function)
260             gfc_error ("Alternate return specifier in function "
261                        "'%s' at %L is not allowed", proc->name,
262                        &proc->declared_at);
263           continue;
264         }
265       else if (sym->attr.procedure && sym->ts.interface
266                && sym->attr.if_source != IFSRC_DECL)
267         resolve_procedure_interface (sym);
268
269       if (sym->attr.if_source != IFSRC_UNKNOWN)
270         resolve_formal_arglist (sym);
271
272       if (sym->attr.subroutine || sym->attr.external)
273         {
274           if (sym->attr.flavor == FL_UNKNOWN)
275             gfc_add_flavor (&sym->attr, FL_PROCEDURE, sym->name, &sym->declared_at);
276         }
277       else
278         {
279           if (sym->ts.type == BT_UNKNOWN && !proc->attr.intrinsic
280               && (!sym->attr.function || sym->result == sym))
281             gfc_set_default_type (sym, 1, sym->ns);
282         }
283
284       gfc_resolve_array_spec (sym->as, 0);
285
286       /* We can't tell if an array with dimension (:) is assumed or deferred
287          shape until we know if it has the pointer or allocatable attributes.
288       */
289       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
290           && !(sym->attr.pointer || sym->attr.allocatable)
291           && sym->attr.flavor != FL_PROCEDURE)
292         {
293           sym->as->type = AS_ASSUMED_SHAPE;
294           for (i = 0; i < sym->as->rank; i++)
295             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
296                                                   NULL, 1);
297         }
298
299       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
300           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
301           || sym->attr.optional)
302         {
303           proc->attr.always_explicit = 1;
304           if (proc->result)
305             proc->result->attr.always_explicit = 1;
306         }
307
308       /* If the flavor is unknown at this point, it has to be a variable.
309          A procedure specification would have already set the type.  */
310
311       if (sym->attr.flavor == FL_UNKNOWN)
312         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
313
314       if (gfc_pure (proc))
315         {
316           if (sym->attr.flavor == FL_PROCEDURE)
317             {
318               /* F08:C1279.  */
319               if (!gfc_pure (sym))
320                 {
321                   gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
322                             "also be PURE", sym->name, &sym->declared_at);
323                   continue;
324                 }
325             }
326           else if (!sym->attr.pointer)
327             {
328               if (proc->attr.function && sym->attr.intent != INTENT_IN)
329                 {
330                   if (sym->attr.value)
331                     gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s'"
332                                     " of pure function '%s' at %L with VALUE "
333                                     "attribute but without INTENT(IN)",
334                                     sym->name, proc->name, &sym->declared_at);
335                   else
336                     gfc_error ("Argument '%s' of pure function '%s' at %L must "
337                                "be INTENT(IN) or VALUE", sym->name, proc->name,
338                                &sym->declared_at);
339                 }
340
341               if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
342                 {
343                   if (sym->attr.value)
344                     gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s'"
345                                     " of pure subroutine '%s' at %L with VALUE "
346                                     "attribute but without INTENT", sym->name,
347                                     proc->name, &sym->declared_at);
348                   else
349                     gfc_error ("Argument '%s' of pure subroutine '%s' at %L "
350                                "must have its INTENT specified or have the "
351                                "VALUE attribute", sym->name, proc->name,
352                                &sym->declared_at);
353                 }
354             }
355         }
356
357       if (proc->attr.implicit_pure)
358         {
359           if (sym->attr.flavor == FL_PROCEDURE)
360             {
361               if (!gfc_pure(sym))
362                 proc->attr.implicit_pure = 0;
363             }
364           else if (!sym->attr.pointer)
365             {
366               if (proc->attr.function && sym->attr.intent != INTENT_IN)
367                 proc->attr.implicit_pure = 0;
368
369               if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
370                 proc->attr.implicit_pure = 0;
371             }
372         }
373
374       if (gfc_elemental (proc))
375         {
376           /* F08:C1289.  */
377           if (sym->attr.codimension
378               || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
379                   && CLASS_DATA (sym)->attr.codimension))
380             {
381               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
382                          "procedure", sym->name, &sym->declared_at);
383               continue;
384             }
385
386           if (sym->as || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
387                           && CLASS_DATA (sym)->as))
388             {
389               gfc_error ("Argument '%s' of elemental procedure at %L must "
390                          "be scalar", sym->name, &sym->declared_at);
391               continue;
392             }
393
394           if (sym->attr.allocatable
395               || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
396                   && CLASS_DATA (sym)->attr.allocatable))
397             {
398               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
399                          "have the ALLOCATABLE attribute", sym->name,
400                          &sym->declared_at);
401               continue;
402             }
403
404           if (sym->attr.pointer
405               || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
406                   && CLASS_DATA (sym)->attr.class_pointer))
407             {
408               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
409                          "have the POINTER attribute", sym->name,
410                          &sym->declared_at);
411               continue;
412             }
413
414           if (sym->attr.flavor == FL_PROCEDURE)
415             {
416               gfc_error ("Dummy procedure '%s' not allowed in elemental "
417                          "procedure '%s' at %L", sym->name, proc->name,
418                          &sym->declared_at);
419               continue;
420             }
421
422           if (sym->attr.intent == INTENT_UNKNOWN)
423             {
424               gfc_error ("Argument '%s' of elemental procedure '%s' at %L must "
425                          "have its INTENT specified", sym->name, proc->name,
426                          &sym->declared_at);
427               continue;
428             }
429         }
430
431       /* Each dummy shall be specified to be scalar.  */
432       if (proc->attr.proc == PROC_ST_FUNCTION)
433         {
434           if (sym->as != NULL)
435             {
436               gfc_error ("Argument '%s' of statement function at %L must "
437                          "be scalar", sym->name, &sym->declared_at);
438               continue;
439             }
440
441           if (sym->ts.type == BT_CHARACTER)
442             {
443               gfc_charlen *cl = sym->ts.u.cl;
444               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
445                 {
446                   gfc_error ("Character-valued argument '%s' of statement "
447                              "function at %L must have constant length",
448                              sym->name, &sym->declared_at);
449                   continue;
450                 }
451             }
452         }
453     }
454   formal_arg_flag = 0;
455 }
456
457
458 /* Work function called when searching for symbols that have argument lists
459    associated with them.  */
460
461 static void
462 find_arglists (gfc_symbol *sym)
463 {
464   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns
465       || sym->attr.flavor == FL_DERIVED)
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.external)
908     gfc_error ("COMMON block '%s' at %L can not have the EXTERNAL attribute",
909                sym->name, &common_root->n.common->where);
910
911   if (sym->attr.intrinsic)
912     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
913                sym->name, &common_root->n.common->where);
914   else if (sym->attr.result
915            || gfc_is_function_return_value (sym, gfc_current_ns))
916     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
917                     "that is also a function result", sym->name,
918                     &common_root->n.common->where);
919   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
920            && sym->attr.proc != PROC_ST_FUNCTION)
921     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
922                     "that is also a global procedure", sym->name,
923                     &common_root->n.common->where);
924 }
925
926
927 /* Resolve contained function types.  Because contained functions can call one
928    another, they have to be worked out before any of the contained procedures
929    can be resolved.
930
931    The good news is that if a function doesn't already have a type, the only
932    way it can get one is through an IMPLICIT type or a RESULT variable, because
933    by definition contained functions are contained namespace they're contained
934    in, not in a sibling or parent namespace.  */
935
936 static void
937 resolve_contained_functions (gfc_namespace *ns)
938 {
939   gfc_namespace *child;
940   gfc_entry_list *el;
941
942   resolve_formal_arglists (ns);
943
944   for (child = ns->contained; child; child = child->sibling)
945     {
946       /* Resolve alternate entry points first.  */
947       resolve_entries (child);
948
949       /* Then check function return types.  */
950       resolve_contained_fntype (child->proc_name, child);
951       for (el = child->entries; el; el = el->next)
952         resolve_contained_fntype (el->sym, child);
953     }
954 }
955
956
957 static gfc_try resolve_fl_derived0 (gfc_symbol *sym);
958
959
960 /* Resolve all of the elements of a structure constructor and make sure that
961    the types are correct. The 'init' flag indicates that the given
962    constructor is an initializer.  */
963
964 static gfc_try
965 resolve_structure_cons (gfc_expr *expr, int init)
966 {
967   gfc_constructor *cons;
968   gfc_component *comp;
969   gfc_try t;
970   symbol_attribute a;
971
972   t = SUCCESS;
973
974   if (expr->ts.type == BT_DERIVED)
975     resolve_fl_derived0 (expr->ts.u.derived);
976
977   cons = gfc_constructor_first (expr->value.constructor);
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   /* A constructor may have references if it is the result of substituting a
997      parameter variable.  In this case we just pull out the component we
998      want.  */
999   if (expr->ref)
1000     comp = expr->ref->u.c.sym->components;
1001   else
1002     comp = expr->ts.u.derived->components;
1003
1004   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
1005     {
1006       int rank;
1007
1008       if (!cons->expr)
1009         continue;
1010
1011       if (gfc_resolve_expr (cons->expr) == FAILURE)
1012         {
1013           t = FAILURE;
1014           continue;
1015         }
1016
1017       rank = comp->as ? comp->as->rank : 0;
1018       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
1019           && (comp->attr.allocatable || cons->expr->rank))
1020         {
1021           gfc_error ("The rank of the element in the structure "
1022                      "constructor at %L does not match that of the "
1023                      "component (%d/%d)", &cons->expr->where,
1024                      cons->expr->rank, rank);
1025           t = FAILURE;
1026         }
1027
1028       /* If we don't have the right type, try to convert it.  */
1029
1030       if (!comp->attr.proc_pointer &&
1031           !gfc_compare_types (&cons->expr->ts, &comp->ts))
1032         {
1033           t = FAILURE;
1034           if (strcmp (comp->name, "_extends") == 0)
1035             {
1036               /* Can afford to be brutal with the _extends initializer.
1037                  The derived type can get lost because it is PRIVATE
1038                  but it is not usage constrained by the standard.  */
1039               cons->expr->ts = comp->ts;
1040               t = SUCCESS;
1041             }
1042           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
1043             gfc_error ("The element in the structure constructor at %L, "
1044                        "for pointer component '%s', is %s but should be %s",
1045                        &cons->expr->where, comp->name,
1046                        gfc_basic_typename (cons->expr->ts.type),
1047                        gfc_basic_typename (comp->ts.type));
1048           else
1049             t = gfc_convert_type (cons->expr, &comp->ts, 1);
1050         }
1051
1052       /* For strings, the length of the constructor should be the same as
1053          the one of the structure, ensure this if the lengths are known at
1054          compile time and when we are dealing with PARAMETER or structure
1055          constructors.  */
1056       if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1057           && comp->ts.u.cl->length
1058           && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1059           && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1060           && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1061           && cons->expr->rank != 0
1062           && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1063                       comp->ts.u.cl->length->value.integer) != 0)
1064         {
1065           if (cons->expr->expr_type == EXPR_VARIABLE
1066               && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1067             {
1068               /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1069                  to make use of the gfc_resolve_character_array_constructor
1070                  machinery.  The expression is later simplified away to
1071                  an array of string literals.  */
1072               gfc_expr *para = cons->expr;
1073               cons->expr = gfc_get_expr ();
1074               cons->expr->ts = para->ts;
1075               cons->expr->where = para->where;
1076               cons->expr->expr_type = EXPR_ARRAY;
1077               cons->expr->rank = para->rank;
1078               cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1079               gfc_constructor_append_expr (&cons->expr->value.constructor,
1080                                            para, &cons->expr->where);
1081             }
1082           if (cons->expr->expr_type == EXPR_ARRAY)
1083             {
1084               gfc_constructor *p;
1085               p = gfc_constructor_first (cons->expr->value.constructor);
1086               if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1087                 {
1088                   gfc_charlen *cl, *cl2;
1089
1090                   cl2 = NULL;
1091                   for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1092                     {
1093                       if (cl == cons->expr->ts.u.cl)
1094                         break;
1095                       cl2 = cl;
1096                     }
1097
1098                   gcc_assert (cl);
1099
1100                   if (cl2)
1101                     cl2->next = cl->next;
1102
1103                   gfc_free_expr (cl->length);
1104                   free (cl);
1105                 }
1106
1107               cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1108               cons->expr->ts.u.cl->length_from_typespec = true;
1109               cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1110               gfc_resolve_character_array_constructor (cons->expr);
1111             }
1112         }
1113
1114       if (cons->expr->expr_type == EXPR_NULL
1115           && !(comp->attr.pointer || comp->attr.allocatable
1116                || comp->attr.proc_pointer
1117                || (comp->ts.type == BT_CLASS
1118                    && (CLASS_DATA (comp)->attr.class_pointer
1119                        || CLASS_DATA (comp)->attr.allocatable))))
1120         {
1121           t = FAILURE;
1122           gfc_error ("The NULL in the structure constructor at %L is "
1123                      "being applied to component '%s', which is neither "
1124                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
1125                      comp->name);
1126         }
1127
1128       if (comp->attr.proc_pointer && comp->ts.interface)
1129         {
1130           /* Check procedure pointer interface.  */
1131           gfc_symbol *s2 = NULL;
1132           gfc_component *c2;
1133           const char *name;
1134           char err[200];
1135
1136           if (gfc_is_proc_ptr_comp (cons->expr, &c2))
1137             {
1138               s2 = c2->ts.interface;
1139               name = c2->name;
1140             }
1141           else if (cons->expr->expr_type == EXPR_FUNCTION)
1142             {
1143               s2 = cons->expr->symtree->n.sym->result;
1144               name = cons->expr->symtree->n.sym->result->name;
1145             }
1146           else if (cons->expr->expr_type != EXPR_NULL)
1147             {
1148               s2 = cons->expr->symtree->n.sym;
1149               name = cons->expr->symtree->n.sym->name;
1150             }
1151
1152           if (s2 && !gfc_compare_interfaces (comp->ts.interface, s2, name, 0, 1,
1153                                              err, sizeof (err)))
1154             {
1155               gfc_error ("Interface mismatch for procedure-pointer component "
1156                          "'%s' in structure constructor at %L: %s",
1157                          comp->name, &cons->expr->where, err);
1158               return FAILURE;
1159             }
1160         }
1161
1162       if (!comp->attr.pointer || comp->attr.proc_pointer
1163           || cons->expr->expr_type == EXPR_NULL)
1164         continue;
1165
1166       a = gfc_expr_attr (cons->expr);
1167
1168       if (!a.pointer && !a.target)
1169         {
1170           t = FAILURE;
1171           gfc_error ("The element in the structure constructor at %L, "
1172                      "for pointer component '%s' should be a POINTER or "
1173                      "a TARGET", &cons->expr->where, comp->name);
1174         }
1175
1176       if (init)
1177         {
1178           /* F08:C461. Additional checks for pointer initialization.  */
1179           if (a.allocatable)
1180             {
1181               t = FAILURE;
1182               gfc_error ("Pointer initialization target at %L "
1183                          "must not be ALLOCATABLE ", &cons->expr->where);
1184             }
1185           if (!a.save)
1186             {
1187               t = FAILURE;
1188               gfc_error ("Pointer initialization target at %L "
1189                          "must have the SAVE attribute", &cons->expr->where);
1190             }
1191         }
1192
1193       /* F2003, C1272 (3).  */
1194       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
1195           && (gfc_impure_variable (cons->expr->symtree->n.sym)
1196               || gfc_is_coindexed (cons->expr)))
1197         {
1198           t = FAILURE;
1199           gfc_error ("Invalid expression in the structure constructor for "
1200                      "pointer component '%s' at %L in PURE procedure",
1201                      comp->name, &cons->expr->where);
1202         }
1203
1204       if (gfc_implicit_pure (NULL)
1205             && cons->expr->expr_type == EXPR_VARIABLE
1206             && (gfc_impure_variable (cons->expr->symtree->n.sym)
1207                 || gfc_is_coindexed (cons->expr)))
1208         gfc_current_ns->proc_name->attr.implicit_pure = 0;
1209
1210     }
1211
1212   return t;
1213 }
1214
1215
1216 /****************** Expression name resolution ******************/
1217
1218 /* Returns 0 if a symbol was not declared with a type or
1219    attribute declaration statement, nonzero otherwise.  */
1220
1221 static int
1222 was_declared (gfc_symbol *sym)
1223 {
1224   symbol_attribute a;
1225
1226   a = sym->attr;
1227
1228   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1229     return 1;
1230
1231   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1232       || a.optional || a.pointer || a.save || a.target || a.volatile_
1233       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1234       || a.asynchronous || a.codimension)
1235     return 1;
1236
1237   return 0;
1238 }
1239
1240
1241 /* Determine if a symbol is generic or not.  */
1242
1243 static int
1244 generic_sym (gfc_symbol *sym)
1245 {
1246   gfc_symbol *s;
1247
1248   if (sym->attr.generic ||
1249       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1250     return 1;
1251
1252   if (was_declared (sym) || sym->ns->parent == NULL)
1253     return 0;
1254
1255   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1256   
1257   if (s != NULL)
1258     {
1259       if (s == sym)
1260         return 0;
1261       else
1262         return generic_sym (s);
1263     }
1264
1265   return 0;
1266 }
1267
1268
1269 /* Determine if a symbol is specific or not.  */
1270
1271 static int
1272 specific_sym (gfc_symbol *sym)
1273 {
1274   gfc_symbol *s;
1275
1276   if (sym->attr.if_source == IFSRC_IFBODY
1277       || sym->attr.proc == PROC_MODULE
1278       || sym->attr.proc == PROC_INTERNAL
1279       || sym->attr.proc == PROC_ST_FUNCTION
1280       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1281       || sym->attr.external)
1282     return 1;
1283
1284   if (was_declared (sym) || sym->ns->parent == NULL)
1285     return 0;
1286
1287   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1288
1289   return (s == NULL) ? 0 : specific_sym (s);
1290 }
1291
1292
1293 /* Figure out if the procedure is specific, generic or unknown.  */
1294
1295 typedef enum
1296 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1297 proc_type;
1298
1299 static proc_type
1300 procedure_kind (gfc_symbol *sym)
1301 {
1302   if (generic_sym (sym))
1303     return PTYPE_GENERIC;
1304
1305   if (specific_sym (sym))
1306     return PTYPE_SPECIFIC;
1307
1308   return PTYPE_UNKNOWN;
1309 }
1310
1311 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1312    is nonzero when matching actual arguments.  */
1313
1314 static int need_full_assumed_size = 0;
1315
1316 static bool
1317 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1318 {
1319   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1320       return false;
1321
1322   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1323      What should it be?  */
1324   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1325           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1326                && (e->ref->u.ar.type == AR_FULL))
1327     {
1328       gfc_error ("The upper bound in the last dimension must "
1329                  "appear in the reference to the assumed size "
1330                  "array '%s' at %L", sym->name, &e->where);
1331       return true;
1332     }
1333   return false;
1334 }
1335
1336
1337 /* Look for bad assumed size array references in argument expressions
1338   of elemental and array valued intrinsic procedures.  Since this is
1339   called from procedure resolution functions, it only recurses at
1340   operators.  */
1341
1342 static bool
1343 resolve_assumed_size_actual (gfc_expr *e)
1344 {
1345   if (e == NULL)
1346    return false;
1347
1348   switch (e->expr_type)
1349     {
1350     case EXPR_VARIABLE:
1351       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1352         return true;
1353       break;
1354
1355     case EXPR_OP:
1356       if (resolve_assumed_size_actual (e->value.op.op1)
1357           || resolve_assumed_size_actual (e->value.op.op2))
1358         return true;
1359       break;
1360
1361     default:
1362       break;
1363     }
1364   return false;
1365 }
1366
1367
1368 /* Check a generic procedure, passed as an actual argument, to see if
1369    there is a matching specific name.  If none, it is an error, and if
1370    more than one, the reference is ambiguous.  */
1371 static int
1372 count_specific_procs (gfc_expr *e)
1373 {
1374   int n;
1375   gfc_interface *p;
1376   gfc_symbol *sym;
1377         
1378   n = 0;
1379   sym = e->symtree->n.sym;
1380
1381   for (p = sym->generic; p; p = p->next)
1382     if (strcmp (sym->name, p->sym->name) == 0)
1383       {
1384         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1385                                        sym->name);
1386         n++;
1387       }
1388
1389   if (n > 1)
1390     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1391                &e->where);
1392
1393   if (n == 0)
1394     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1395                "argument at %L", sym->name, &e->where);
1396
1397   return n;
1398 }
1399
1400
1401 /* See if a call to sym could possibly be a not allowed RECURSION because of
1402    a missing RECURIVE declaration.  This means that either sym is the current
1403    context itself, or sym is the parent of a contained procedure calling its
1404    non-RECURSIVE containing procedure.
1405    This also works if sym is an ENTRY.  */
1406
1407 static bool
1408 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1409 {
1410   gfc_symbol* proc_sym;
1411   gfc_symbol* context_proc;
1412   gfc_namespace* real_context;
1413
1414   if (sym->attr.flavor == FL_PROGRAM
1415       || sym->attr.flavor == FL_DERIVED)
1416     return false;
1417
1418   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1419
1420   /* If we've got an ENTRY, find real procedure.  */
1421   if (sym->attr.entry && sym->ns->entries)
1422     proc_sym = sym->ns->entries->sym;
1423   else
1424     proc_sym = sym;
1425
1426   /* If sym is RECURSIVE, all is well of course.  */
1427   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1428     return false;
1429
1430   /* Find the context procedure's "real" symbol if it has entries.
1431      We look for a procedure symbol, so recurse on the parents if we don't
1432      find one (like in case of a BLOCK construct).  */
1433   for (real_context = context; ; real_context = real_context->parent)
1434     {
1435       /* We should find something, eventually!  */
1436       gcc_assert (real_context);
1437
1438       context_proc = (real_context->entries ? real_context->entries->sym
1439                                             : real_context->proc_name);
1440
1441       /* In some special cases, there may not be a proc_name, like for this
1442          invalid code:
1443          real(bad_kind()) function foo () ...
1444          when checking the call to bad_kind ().
1445          In these cases, we simply return here and assume that the
1446          call is ok.  */
1447       if (!context_proc)
1448         return false;
1449
1450       if (context_proc->attr.flavor != FL_LABEL)
1451         break;
1452     }
1453
1454   /* A call from sym's body to itself is recursion, of course.  */
1455   if (context_proc == proc_sym)
1456     return true;
1457
1458   /* The same is true if context is a contained procedure and sym the
1459      containing one.  */
1460   if (context_proc->attr.contained)
1461     {
1462       gfc_symbol* parent_proc;
1463
1464       gcc_assert (context->parent);
1465       parent_proc = (context->parent->entries ? context->parent->entries->sym
1466                                               : context->parent->proc_name);
1467
1468       if (parent_proc == proc_sym)
1469         return true;
1470     }
1471
1472   return false;
1473 }
1474
1475
1476 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1477    its typespec and formal argument list.  */
1478
1479 static gfc_try
1480 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1481 {
1482   gfc_intrinsic_sym* isym = NULL;
1483   const char* symstd;
1484
1485   if (sym->formal)
1486     return SUCCESS;
1487
1488   /* Already resolved.  */
1489   if (sym->from_intmod && sym->ts.type != BT_UNKNOWN)
1490     return SUCCESS;
1491
1492   /* We already know this one is an intrinsic, so we don't call
1493      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1494      gfc_find_subroutine directly to check whether it is a function or
1495      subroutine.  */
1496
1497   if (sym->intmod_sym_id)
1498     isym = gfc_intrinsic_function_by_id ((gfc_isym_id) sym->intmod_sym_id);
1499   else
1500     isym = gfc_find_function (sym->name);
1501
1502   if (isym)
1503     {
1504       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1505           && !sym->attr.implicit_type)
1506         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1507                       " ignored", sym->name, &sym->declared_at);
1508
1509       if (!sym->attr.function &&
1510           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1511         return FAILURE;
1512
1513       sym->ts = isym->ts;
1514     }
1515   else if ((isym = gfc_find_subroutine (sym->name)))
1516     {
1517       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1518         {
1519           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1520                       " specifier", sym->name, &sym->declared_at);
1521           return FAILURE;
1522         }
1523
1524       if (!sym->attr.subroutine &&
1525           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1526         return FAILURE;
1527     }
1528   else
1529     {
1530       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1531                  &sym->declared_at);
1532       return FAILURE;
1533     }
1534
1535   gfc_copy_formal_args_intr (sym, isym);
1536
1537   /* Check it is actually available in the standard settings.  */
1538   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1539       == FAILURE)
1540     {
1541       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1542                  " available in the current standard settings but %s.  Use"
1543                  " an appropriate -std=* option or enable -fall-intrinsics"
1544                  " in order to use it.",
1545                  sym->name, &sym->declared_at, symstd);
1546       return FAILURE;
1547     }
1548
1549   return SUCCESS;
1550 }
1551
1552
1553 /* Resolve a procedure expression, like passing it to a called procedure or as
1554    RHS for a procedure pointer assignment.  */
1555
1556 static gfc_try
1557 resolve_procedure_expression (gfc_expr* expr)
1558 {
1559   gfc_symbol* sym;
1560
1561   if (expr->expr_type != EXPR_VARIABLE)
1562     return SUCCESS;
1563   gcc_assert (expr->symtree);
1564
1565   sym = expr->symtree->n.sym;
1566
1567   if (sym->attr.intrinsic)
1568     resolve_intrinsic (sym, &expr->where);
1569
1570   if (sym->attr.flavor != FL_PROCEDURE
1571       || (sym->attr.function && sym->result == sym))
1572     return SUCCESS;
1573
1574   /* A non-RECURSIVE procedure that is used as procedure expression within its
1575      own body is in danger of being called recursively.  */
1576   if (is_illegal_recursion (sym, gfc_current_ns))
1577     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1578                  " itself recursively.  Declare it RECURSIVE or use"
1579                  " -frecursive", sym->name, &expr->where);
1580   
1581   return SUCCESS;
1582 }
1583
1584
1585 /* Resolve an actual argument list.  Most of the time, this is just
1586    resolving the expressions in the list.
1587    The exception is that we sometimes have to decide whether arguments
1588    that look like procedure arguments are really simple variable
1589    references.  */
1590
1591 static gfc_try
1592 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1593                         bool no_formal_args)
1594 {
1595   gfc_symbol *sym;
1596   gfc_symtree *parent_st;
1597   gfc_expr *e;
1598   int save_need_full_assumed_size;
1599
1600   for (; arg; arg = arg->next)
1601     {
1602       e = arg->expr;
1603       if (e == NULL)
1604         {
1605           /* Check the label is a valid branching target.  */
1606           if (arg->label)
1607             {
1608               if (arg->label->defined == ST_LABEL_UNKNOWN)
1609                 {
1610                   gfc_error ("Label %d referenced at %L is never defined",
1611                              arg->label->value, &arg->label->where);
1612                   return FAILURE;
1613                 }
1614             }
1615           continue;
1616         }
1617
1618       if (e->expr_type == EXPR_VARIABLE
1619             && e->symtree->n.sym->attr.generic
1620             && no_formal_args
1621             && count_specific_procs (e) != 1)
1622         return FAILURE;
1623
1624       if (e->ts.type != BT_PROCEDURE)
1625         {
1626           save_need_full_assumed_size = need_full_assumed_size;
1627           if (e->expr_type != EXPR_VARIABLE)
1628             need_full_assumed_size = 0;
1629           if (gfc_resolve_expr (e) != SUCCESS)
1630             return FAILURE;
1631           need_full_assumed_size = save_need_full_assumed_size;
1632           goto argument_list;
1633         }
1634
1635       /* See if the expression node should really be a variable reference.  */
1636
1637       sym = e->symtree->n.sym;
1638
1639       if (sym->attr.flavor == FL_PROCEDURE
1640           || sym->attr.intrinsic
1641           || sym->attr.external)
1642         {
1643           int actual_ok;
1644
1645           /* If a procedure is not already determined to be something else
1646              check if it is intrinsic.  */
1647           if (!sym->attr.intrinsic
1648               && !(sym->attr.external || sym->attr.use_assoc
1649                    || sym->attr.if_source == IFSRC_IFBODY)
1650               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1651             sym->attr.intrinsic = 1;
1652
1653           if (sym->attr.proc == PROC_ST_FUNCTION)
1654             {
1655               gfc_error ("Statement function '%s' at %L is not allowed as an "
1656                          "actual argument", sym->name, &e->where);
1657             }
1658
1659           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1660                                                sym->attr.subroutine);
1661           if (sym->attr.intrinsic && actual_ok == 0)
1662             {
1663               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1664                          "actual argument", sym->name, &e->where);
1665             }
1666
1667           if (sym->attr.contained && !sym->attr.use_assoc
1668               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1669             {
1670               if (gfc_notify_std (GFC_STD_F2008,
1671                                   "Fortran 2008: Internal procedure '%s' is"
1672                                   " used as actual argument at %L",
1673                                   sym->name, &e->where) == FAILURE)
1674                 return FAILURE;
1675             }
1676
1677           if (sym->attr.elemental && !sym->attr.intrinsic)
1678             {
1679               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1680                          "allowed as an actual argument at %L", sym->name,
1681                          &e->where);
1682             }
1683
1684           /* Check if a generic interface has a specific procedure
1685             with the same name before emitting an error.  */
1686           if (sym->attr.generic && count_specific_procs (e) != 1)
1687             return FAILURE;
1688           
1689           /* Just in case a specific was found for the expression.  */
1690           sym = e->symtree->n.sym;
1691
1692           /* If the symbol is the function that names the current (or
1693              parent) scope, then we really have a variable reference.  */
1694
1695           if (gfc_is_function_return_value (sym, sym->ns))
1696             goto got_variable;
1697
1698           /* If all else fails, see if we have a specific intrinsic.  */
1699           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1700             {
1701               gfc_intrinsic_sym *isym;
1702
1703               isym = gfc_find_function (sym->name);
1704               if (isym == NULL || !isym->specific)
1705                 {
1706                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1707                              "for the reference '%s' at %L", sym->name,
1708                              &e->where);
1709                   return FAILURE;
1710                 }
1711               sym->ts = isym->ts;
1712               sym->attr.intrinsic = 1;
1713               sym->attr.function = 1;
1714             }
1715
1716           if (gfc_resolve_expr (e) == FAILURE)
1717             return FAILURE;
1718           goto argument_list;
1719         }
1720
1721       /* See if the name is a module procedure in a parent unit.  */
1722
1723       if (was_declared (sym) || sym->ns->parent == NULL)
1724         goto got_variable;
1725
1726       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1727         {
1728           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1729           return FAILURE;
1730         }
1731
1732       if (parent_st == NULL)
1733         goto got_variable;
1734
1735       sym = parent_st->n.sym;
1736       e->symtree = parent_st;           /* Point to the right thing.  */
1737
1738       if (sym->attr.flavor == FL_PROCEDURE
1739           || sym->attr.intrinsic
1740           || sym->attr.external)
1741         {
1742           if (gfc_resolve_expr (e) == FAILURE)
1743             return FAILURE;
1744           goto argument_list;
1745         }
1746
1747     got_variable:
1748       e->expr_type = EXPR_VARIABLE;
1749       e->ts = sym->ts;
1750       if ((sym->as != NULL && sym->ts.type != BT_CLASS)
1751           || (sym->ts.type == BT_CLASS && sym->attr.class_ok
1752               && CLASS_DATA (sym)->as))
1753         {
1754           e->rank = sym->ts.type == BT_CLASS
1755                     ? CLASS_DATA (sym)->as->rank : sym->as->rank;
1756           e->ref = gfc_get_ref ();
1757           e->ref->type = REF_ARRAY;
1758           e->ref->u.ar.type = AR_FULL;
1759           e->ref->u.ar.as = sym->ts.type == BT_CLASS
1760                             ? CLASS_DATA (sym)->as : sym->as;
1761         }
1762
1763       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1764          primary.c (match_actual_arg). If above code determines that it
1765          is a  variable instead, it needs to be resolved as it was not
1766          done at the beginning of this function.  */
1767       save_need_full_assumed_size = need_full_assumed_size;
1768       if (e->expr_type != EXPR_VARIABLE)
1769         need_full_assumed_size = 0;
1770       if (gfc_resolve_expr (e) != SUCCESS)
1771         return FAILURE;
1772       need_full_assumed_size = save_need_full_assumed_size;
1773
1774     argument_list:
1775       /* Check argument list functions %VAL, %LOC and %REF.  There is
1776          nothing to do for %REF.  */
1777       if (arg->name && arg->name[0] == '%')
1778         {
1779           if (strncmp ("%VAL", arg->name, 4) == 0)
1780             {
1781               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1782                 {
1783                   gfc_error ("By-value argument at %L is not of numeric "
1784                              "type", &e->where);
1785                   return FAILURE;
1786                 }
1787
1788               if (e->rank)
1789                 {
1790                   gfc_error ("By-value argument at %L cannot be an array or "
1791                              "an array section", &e->where);
1792                 return FAILURE;
1793                 }
1794
1795               /* Intrinsics are still PROC_UNKNOWN here.  However,
1796                  since same file external procedures are not resolvable
1797                  in gfortran, it is a good deal easier to leave them to
1798                  intrinsic.c.  */
1799               if (ptype != PROC_UNKNOWN
1800                   && ptype != PROC_DUMMY
1801                   && ptype != PROC_EXTERNAL
1802                   && ptype != PROC_MODULE)
1803                 {
1804                   gfc_error ("By-value argument at %L is not allowed "
1805                              "in this context", &e->where);
1806                   return FAILURE;
1807                 }
1808             }
1809
1810           /* Statement functions have already been excluded above.  */
1811           else if (strncmp ("%LOC", arg->name, 4) == 0
1812                    && e->ts.type == BT_PROCEDURE)
1813             {
1814               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1815                 {
1816                   gfc_error ("Passing internal procedure at %L by location "
1817                              "not allowed", &e->where);
1818                   return FAILURE;
1819                 }
1820             }
1821         }
1822
1823       /* Fortran 2008, C1237.  */
1824       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1825           && gfc_has_ultimate_pointer (e))
1826         {
1827           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1828                      "component", &e->where);
1829           return FAILURE;
1830         }
1831     }
1832
1833   return SUCCESS;
1834 }
1835
1836
1837 /* Do the checks of the actual argument list that are specific to elemental
1838    procedures.  If called with c == NULL, we have a function, otherwise if
1839    expr == NULL, we have a subroutine.  */
1840
1841 static gfc_try
1842 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1843 {
1844   gfc_actual_arglist *arg0;
1845   gfc_actual_arglist *arg;
1846   gfc_symbol *esym = NULL;
1847   gfc_intrinsic_sym *isym = NULL;
1848   gfc_expr *e = NULL;
1849   gfc_intrinsic_arg *iformal = NULL;
1850   gfc_formal_arglist *eformal = NULL;
1851   bool formal_optional = false;
1852   bool set_by_optional = false;
1853   int i;
1854   int rank = 0;
1855
1856   /* Is this an elemental procedure?  */
1857   if (expr && expr->value.function.actual != NULL)
1858     {
1859       if (expr->value.function.esym != NULL
1860           && expr->value.function.esym->attr.elemental)
1861         {
1862           arg0 = expr->value.function.actual;
1863           esym = expr->value.function.esym;
1864         }
1865       else if (expr->value.function.isym != NULL
1866                && expr->value.function.isym->elemental)
1867         {
1868           arg0 = expr->value.function.actual;
1869           isym = expr->value.function.isym;
1870         }
1871       else
1872         return SUCCESS;
1873     }
1874   else if (c && c->ext.actual != NULL)
1875     {
1876       arg0 = c->ext.actual;
1877       
1878       if (c->resolved_sym)
1879         esym = c->resolved_sym;
1880       else
1881         esym = c->symtree->n.sym;
1882       gcc_assert (esym);
1883
1884       if (!esym->attr.elemental)
1885         return SUCCESS;
1886     }
1887   else
1888     return SUCCESS;
1889
1890   /* The rank of an elemental is the rank of its array argument(s).  */
1891   for (arg = arg0; arg; arg = arg->next)
1892     {
1893       if (arg->expr != NULL && arg->expr->rank > 0)
1894         {
1895           rank = arg->expr->rank;
1896           if (arg->expr->expr_type == EXPR_VARIABLE
1897               && arg->expr->symtree->n.sym->attr.optional)
1898             set_by_optional = true;
1899
1900           /* Function specific; set the result rank and shape.  */
1901           if (expr)
1902             {
1903               expr->rank = rank;
1904               if (!expr->shape && arg->expr->shape)
1905                 {
1906                   expr->shape = gfc_get_shape (rank);
1907                   for (i = 0; i < rank; i++)
1908                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1909                 }
1910             }
1911           break;
1912         }
1913     }
1914
1915   /* If it is an array, it shall not be supplied as an actual argument
1916      to an elemental procedure unless an array of the same rank is supplied
1917      as an actual argument corresponding to a nonoptional dummy argument of
1918      that elemental procedure(12.4.1.5).  */
1919   formal_optional = false;
1920   if (isym)
1921     iformal = isym->formal;
1922   else
1923     eformal = esym->formal;
1924
1925   for (arg = arg0; arg; arg = arg->next)
1926     {
1927       if (eformal)
1928         {
1929           if (eformal->sym && eformal->sym->attr.optional)
1930             formal_optional = true;
1931           eformal = eformal->next;
1932         }
1933       else if (isym && iformal)
1934         {
1935           if (iformal->optional)
1936             formal_optional = true;
1937           iformal = iformal->next;
1938         }
1939       else if (isym)
1940         formal_optional = true;
1941
1942       if (pedantic && arg->expr != NULL
1943           && arg->expr->expr_type == EXPR_VARIABLE
1944           && arg->expr->symtree->n.sym->attr.optional
1945           && formal_optional
1946           && arg->expr->rank
1947           && (set_by_optional || arg->expr->rank != rank)
1948           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1949         {
1950           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1951                        "MISSING, it cannot be the actual argument of an "
1952                        "ELEMENTAL procedure unless there is a non-optional "
1953                        "argument with the same rank (12.4.1.5)",
1954                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1955           return FAILURE;
1956         }
1957     }
1958
1959   for (arg = arg0; arg; arg = arg->next)
1960     {
1961       if (arg->expr == NULL || arg->expr->rank == 0)
1962         continue;
1963
1964       /* Being elemental, the last upper bound of an assumed size array
1965          argument must be present.  */
1966       if (resolve_assumed_size_actual (arg->expr))
1967         return FAILURE;
1968
1969       /* Elemental procedure's array actual arguments must conform.  */
1970       if (e != NULL)
1971         {
1972           if (gfc_check_conformance (arg->expr, e,
1973                                      "elemental procedure") == FAILURE)
1974             return FAILURE;
1975         }
1976       else
1977         e = arg->expr;
1978     }
1979
1980   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1981      is an array, the intent inout/out variable needs to be also an array.  */
1982   if (rank > 0 && esym && expr == NULL)
1983     for (eformal = esym->formal, arg = arg0; arg && eformal;
1984          arg = arg->next, eformal = eformal->next)
1985       if ((eformal->sym->attr.intent == INTENT_OUT
1986            || eformal->sym->attr.intent == INTENT_INOUT)
1987           && arg->expr && arg->expr->rank == 0)
1988         {
1989           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1990                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1991                      "actual argument is an array", &arg->expr->where,
1992                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1993                      : "INOUT", eformal->sym->name, esym->name);
1994           return FAILURE;
1995         }
1996   return SUCCESS;
1997 }
1998
1999
2000 /* This function does the checking of references to global procedures
2001    as defined in sections 18.1 and 14.1, respectively, of the Fortran
2002    77 and 95 standards.  It checks for a gsymbol for the name, making
2003    one if it does not already exist.  If it already exists, then the
2004    reference being resolved must correspond to the type of gsymbol.
2005    Otherwise, the new symbol is equipped with the attributes of the
2006    reference.  The corresponding code that is called in creating
2007    global entities is parse.c.
2008
2009    In addition, for all but -std=legacy, the gsymbols are used to
2010    check the interfaces of external procedures from the same file.
2011    The namespace of the gsymbol is resolved and then, once this is
2012    done the interface is checked.  */
2013
2014
2015 static bool
2016 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
2017 {
2018   if (!gsym_ns->proc_name->attr.recursive)
2019     return true;
2020
2021   if (sym->ns == gsym_ns)
2022     return false;
2023
2024   if (sym->ns->parent && sym->ns->parent == gsym_ns)
2025     return false;
2026
2027   return true;
2028 }
2029
2030 static bool
2031 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
2032 {
2033   if (gsym_ns->entries)
2034     {
2035       gfc_entry_list *entry = gsym_ns->entries;
2036
2037       for (; entry; entry = entry->next)
2038         {
2039           if (strcmp (sym->name, entry->sym->name) == 0)
2040             {
2041               if (strcmp (gsym_ns->proc_name->name,
2042                           sym->ns->proc_name->name) == 0)
2043                 return false;
2044
2045               if (sym->ns->parent
2046                   && strcmp (gsym_ns->proc_name->name,
2047                              sym->ns->parent->proc_name->name) == 0)
2048                 return false;
2049             }
2050         }
2051     }
2052   return true;
2053 }
2054
2055 static void
2056 resolve_global_procedure (gfc_symbol *sym, locus *where,
2057                           gfc_actual_arglist **actual, int sub)
2058 {
2059   gfc_gsymbol * gsym;
2060   gfc_namespace *ns;
2061   enum gfc_symbol_type type;
2062
2063   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
2064
2065   gsym = gfc_get_gsymbol (sym->name);
2066
2067   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
2068     gfc_global_used (gsym, where);
2069
2070   if (gfc_option.flag_whole_file
2071         && (sym->attr.if_source == IFSRC_UNKNOWN
2072             || sym->attr.if_source == IFSRC_IFBODY)
2073         && gsym->type != GSYM_UNKNOWN
2074         && gsym->ns
2075         && gsym->ns->resolved != -1
2076         && gsym->ns->proc_name
2077         && not_in_recursive (sym, gsym->ns)
2078         && not_entry_self_reference (sym, gsym->ns))
2079     {
2080       gfc_symbol *def_sym;
2081
2082       /* Resolve the gsymbol namespace if needed.  */
2083       if (!gsym->ns->resolved)
2084         {
2085           gfc_dt_list *old_dt_list;
2086           struct gfc_omp_saved_state old_omp_state;
2087
2088           /* Stash away derived types so that the backend_decls do not
2089              get mixed up.  */
2090           old_dt_list = gfc_derived_types;
2091           gfc_derived_types = NULL;
2092           /* And stash away openmp state.  */
2093           gfc_omp_save_and_clear_state (&old_omp_state);
2094
2095           gfc_resolve (gsym->ns);
2096
2097           /* Store the new derived types with the global namespace.  */
2098           if (gfc_derived_types)
2099             gsym->ns->derived_types = gfc_derived_types;
2100
2101           /* Restore the derived types of this namespace.  */
2102           gfc_derived_types = old_dt_list;
2103           /* And openmp state.  */
2104           gfc_omp_restore_state (&old_omp_state);
2105         }
2106
2107       /* Make sure that translation for the gsymbol occurs before
2108          the procedure currently being resolved.  */
2109       ns = gfc_global_ns_list;
2110       for (; ns && ns != gsym->ns; ns = ns->sibling)
2111         {
2112           if (ns->sibling == gsym->ns)
2113             {
2114               ns->sibling = gsym->ns->sibling;
2115               gsym->ns->sibling = gfc_global_ns_list;
2116               gfc_global_ns_list = gsym->ns;
2117               break;
2118             }
2119         }
2120
2121       def_sym = gsym->ns->proc_name;
2122       if (def_sym->attr.entry_master)
2123         {
2124           gfc_entry_list *entry;
2125           for (entry = gsym->ns->entries; entry; entry = entry->next)
2126             if (strcmp (entry->sym->name, sym->name) == 0)
2127               {
2128                 def_sym = entry->sym;
2129                 break;
2130               }
2131         }
2132
2133       /* Differences in constant character lengths.  */
2134       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
2135         {
2136           long int l1 = 0, l2 = 0;
2137           gfc_charlen *cl1 = sym->ts.u.cl;
2138           gfc_charlen *cl2 = def_sym->ts.u.cl;
2139
2140           if (cl1 != NULL
2141               && cl1->length != NULL
2142               && cl1->length->expr_type == EXPR_CONSTANT)
2143             l1 = mpz_get_si (cl1->length->value.integer);
2144
2145           if (cl2 != NULL
2146               && cl2->length != NULL
2147               && cl2->length->expr_type == EXPR_CONSTANT)
2148             l2 = mpz_get_si (cl2->length->value.integer);
2149
2150           if (l1 && l2 && l1 != l2)
2151             gfc_error ("Character length mismatch in return type of "
2152                        "function '%s' at %L (%ld/%ld)", sym->name,
2153                        &sym->declared_at, l1, l2);
2154         }
2155
2156      /* Type mismatch of function return type and expected type.  */
2157      if (sym->attr.function
2158          && !gfc_compare_types (&sym->ts, &def_sym->ts))
2159         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
2160                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2161                    gfc_typename (&def_sym->ts));
2162
2163       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
2164         {
2165           gfc_formal_arglist *arg = def_sym->formal;
2166           for ( ; arg; arg = arg->next)
2167             if (!arg->sym)
2168               continue;
2169             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
2170             else if (arg->sym->attr.allocatable
2171                      || arg->sym->attr.asynchronous
2172                      || arg->sym->attr.optional
2173                      || arg->sym->attr.pointer
2174                      || arg->sym->attr.target
2175                      || arg->sym->attr.value
2176                      || arg->sym->attr.volatile_)
2177               {
2178                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
2179                            "has an attribute that requires an explicit "
2180                            "interface for this procedure", arg->sym->name,
2181                            sym->name, &sym->declared_at);
2182                 break;
2183               }
2184             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
2185             else if (arg->sym && arg->sym->as
2186                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
2187               {
2188                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
2189                            "argument '%s' must have an explicit interface",
2190                            sym->name, &sym->declared_at, arg->sym->name);
2191                 break;
2192               }
2193             /* F2008, 12.4.2.2 (2c)  */
2194             else if (arg->sym->attr.codimension)
2195               {
2196                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
2197                            "'%s' must have an explicit interface",
2198                            sym->name, &sym->declared_at, arg->sym->name);
2199                 break;
2200               }
2201             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
2202             else if (false) /* TODO: is a parametrized derived type  */
2203               {
2204                 gfc_error ("Procedure '%s' at %L with parametrized derived "
2205                            "type argument '%s' must have an explicit "
2206                            "interface", sym->name, &sym->declared_at,
2207                            arg->sym->name);
2208                 break;
2209               }
2210             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
2211             else if (arg->sym->ts.type == BT_CLASS)
2212               {
2213                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
2214                            "argument '%s' must have an explicit interface",
2215                            sym->name, &sym->declared_at, arg->sym->name);
2216                 break;
2217               }
2218         }
2219
2220       if (def_sym->attr.function)
2221         {
2222           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
2223           if (def_sym->as && def_sym->as->rank
2224               && (!sym->as || sym->as->rank != def_sym->as->rank))
2225             gfc_error ("The reference to function '%s' at %L either needs an "
2226                        "explicit INTERFACE or the rank is incorrect", sym->name,
2227                        where);
2228
2229           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
2230           if ((def_sym->result->attr.pointer
2231                || def_sym->result->attr.allocatable)
2232                && (sym->attr.if_source != IFSRC_IFBODY
2233                    || def_sym->result->attr.pointer
2234                         != sym->result->attr.pointer
2235                    || def_sym->result->attr.allocatable
2236                         != sym->result->attr.allocatable))
2237             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
2238                        "result must have an explicit interface", sym->name,
2239                        where);
2240
2241           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
2242           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
2243               && def_sym->ts.type == BT_CHARACTER && def_sym->ts.u.cl->length != NULL)
2244             {
2245               gfc_charlen *cl = sym->ts.u.cl;
2246
2247               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
2248                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
2249                 {
2250                   gfc_error ("Nonconstant character-length function '%s' at %L "
2251                              "must have an explicit interface", sym->name,
2252                              &sym->declared_at);
2253                 }
2254             }
2255         }
2256
2257       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2258       if (def_sym->attr.elemental && !sym->attr.elemental)
2259         {
2260           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2261                      "interface", sym->name, &sym->declared_at);
2262         }
2263
2264       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2265       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2266         {
2267           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2268                      "an explicit interface", sym->name, &sym->declared_at);
2269         }
2270
2271       if (gfc_option.flag_whole_file == 1
2272           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2273               && !(gfc_option.warn_std & GFC_STD_GNU)))
2274         gfc_errors_to_warnings (1);
2275
2276       if (sym->attr.if_source != IFSRC_IFBODY)  
2277         gfc_procedure_use (def_sym, actual, where);
2278
2279       gfc_errors_to_warnings (0);
2280     }
2281
2282   if (gsym->type == GSYM_UNKNOWN)
2283     {
2284       gsym->type = type;
2285       gsym->where = *where;
2286     }
2287
2288   gsym->used = 1;
2289 }
2290
2291
2292 /************* Function resolution *************/
2293
2294 /* Resolve a function call known to be generic.
2295    Section 14.1.2.4.1.  */
2296
2297 static match
2298 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2299 {
2300   gfc_symbol *s;
2301
2302   if (sym->attr.generic)
2303     {
2304       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2305       if (s != NULL)
2306         {
2307           expr->value.function.name = s->name;
2308           expr->value.function.esym = s;
2309
2310           if (s->ts.type != BT_UNKNOWN)
2311             expr->ts = s->ts;
2312           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2313             expr->ts = s->result->ts;
2314
2315           if (s->as != NULL)
2316             expr->rank = s->as->rank;
2317           else if (s->result != NULL && s->result->as != NULL)
2318             expr->rank = s->result->as->rank;
2319
2320           gfc_set_sym_referenced (expr->value.function.esym);
2321
2322           return MATCH_YES;
2323         }
2324
2325       /* TODO: Need to search for elemental references in generic
2326          interface.  */
2327     }
2328
2329   if (sym->attr.intrinsic)
2330     return gfc_intrinsic_func_interface (expr, 0);
2331
2332   return MATCH_NO;
2333 }
2334
2335
2336 static gfc_try
2337 resolve_generic_f (gfc_expr *expr)
2338 {
2339   gfc_symbol *sym;
2340   match m;
2341   gfc_interface *intr = NULL;
2342
2343   sym = expr->symtree->n.sym;
2344
2345   for (;;)
2346     {
2347       m = resolve_generic_f0 (expr, sym);
2348       if (m == MATCH_YES)
2349         return SUCCESS;
2350       else if (m == MATCH_ERROR)
2351         return FAILURE;
2352
2353 generic:
2354       if (!intr)
2355         for (intr = sym->generic; intr; intr = intr->next)
2356           if (intr->sym->attr.flavor == FL_DERIVED)
2357             break;
2358
2359       if (sym->ns->parent == NULL)
2360         break;
2361       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2362
2363       if (sym == NULL)
2364         break;
2365       if (!generic_sym (sym))
2366         goto generic;
2367     }
2368
2369   /* Last ditch attempt.  See if the reference is to an intrinsic
2370      that possesses a matching interface.  14.1.2.4  */
2371   if (sym  && !intr && !gfc_is_intrinsic (sym, 0, expr->where))
2372     {
2373       gfc_error ("There is no specific function for the generic '%s' "
2374                  "at %L", expr->symtree->n.sym->name, &expr->where);
2375       return FAILURE;
2376     }
2377
2378   if (intr)
2379     {
2380       if (gfc_convert_to_structure_constructor (expr, intr->sym, NULL, NULL,
2381                                                 false) != SUCCESS)
2382         return FAILURE;
2383       return resolve_structure_cons (expr, 0);
2384     }
2385
2386   m = gfc_intrinsic_func_interface (expr, 0);
2387   if (m == MATCH_YES)
2388     return SUCCESS;
2389
2390   if (m == MATCH_NO)
2391     gfc_error ("Generic function '%s' at %L is not consistent with a "
2392                "specific intrinsic interface", expr->symtree->n.sym->name,
2393                &expr->where);
2394
2395   return FAILURE;
2396 }
2397
2398
2399 /* Resolve a function call known to be specific.  */
2400
2401 static match
2402 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2403 {
2404   match m;
2405
2406   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2407     {
2408       if (sym->attr.dummy)
2409         {
2410           sym->attr.proc = PROC_DUMMY;
2411           goto found;
2412         }
2413
2414       sym->attr.proc = PROC_EXTERNAL;
2415       goto found;
2416     }
2417
2418   if (sym->attr.proc == PROC_MODULE
2419       || sym->attr.proc == PROC_ST_FUNCTION
2420       || sym->attr.proc == PROC_INTERNAL)
2421     goto found;
2422
2423   if (sym->attr.intrinsic)
2424     {
2425       m = gfc_intrinsic_func_interface (expr, 1);
2426       if (m == MATCH_YES)
2427         return MATCH_YES;
2428       if (m == MATCH_NO)
2429         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2430                    "with an intrinsic", sym->name, &expr->where);
2431
2432       return MATCH_ERROR;
2433     }
2434
2435   return MATCH_NO;
2436
2437 found:
2438   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2439
2440   if (sym->result)
2441     expr->ts = sym->result->ts;
2442   else
2443     expr->ts = sym->ts;
2444   expr->value.function.name = sym->name;
2445   expr->value.function.esym = sym;
2446   if (sym->as != NULL)
2447     expr->rank = sym->as->rank;
2448
2449   return MATCH_YES;
2450 }
2451
2452
2453 static gfc_try
2454 resolve_specific_f (gfc_expr *expr)
2455 {
2456   gfc_symbol *sym;
2457   match m;
2458
2459   sym = expr->symtree->n.sym;
2460
2461   for (;;)
2462     {
2463       m = resolve_specific_f0 (sym, expr);
2464       if (m == MATCH_YES)
2465         return SUCCESS;
2466       if (m == MATCH_ERROR)
2467         return FAILURE;
2468
2469       if (sym->ns->parent == NULL)
2470         break;
2471
2472       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2473
2474       if (sym == NULL)
2475         break;
2476     }
2477
2478   gfc_error ("Unable to resolve the specific function '%s' at %L",
2479              expr->symtree->n.sym->name, &expr->where);
2480
2481   return SUCCESS;
2482 }
2483
2484
2485 /* Resolve a procedure call not known to be generic nor specific.  */
2486
2487 static gfc_try
2488 resolve_unknown_f (gfc_expr *expr)
2489 {
2490   gfc_symbol *sym;
2491   gfc_typespec *ts;
2492
2493   sym = expr->symtree->n.sym;
2494
2495   if (sym->attr.dummy)
2496     {
2497       sym->attr.proc = PROC_DUMMY;
2498       expr->value.function.name = sym->name;
2499       goto set_type;
2500     }
2501
2502   /* See if we have an intrinsic function reference.  */
2503
2504   if (gfc_is_intrinsic (sym, 0, expr->where))
2505     {
2506       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2507         return SUCCESS;
2508       return FAILURE;
2509     }
2510
2511   /* The reference is to an external name.  */
2512
2513   sym->attr.proc = PROC_EXTERNAL;
2514   expr->value.function.name = sym->name;
2515   expr->value.function.esym = expr->symtree->n.sym;
2516
2517   if (sym->as != NULL)
2518     expr->rank = sym->as->rank;
2519
2520   /* Type of the expression is either the type of the symbol or the
2521      default type of the symbol.  */
2522
2523 set_type:
2524   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2525
2526   if (sym->ts.type != BT_UNKNOWN)
2527     expr->ts = sym->ts;
2528   else
2529     {
2530       ts = gfc_get_default_type (sym->name, sym->ns);
2531
2532       if (ts->type == BT_UNKNOWN)
2533         {
2534           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2535                      sym->name, &expr->where);
2536           return FAILURE;
2537         }
2538       else
2539         expr->ts = *ts;
2540     }
2541
2542   return SUCCESS;
2543 }
2544
2545
2546 /* Return true, if the symbol is an external procedure.  */
2547 static bool
2548 is_external_proc (gfc_symbol *sym)
2549 {
2550   if (!sym->attr.dummy && !sym->attr.contained
2551         && !(sym->attr.intrinsic
2552               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2553         && sym->attr.proc != PROC_ST_FUNCTION
2554         && !sym->attr.proc_pointer
2555         && !sym->attr.use_assoc
2556         && sym->name)
2557     return true;
2558
2559   return false;
2560 }
2561
2562
2563 /* Figure out if a function reference is pure or not.  Also set the name
2564    of the function for a potential error message.  Return nonzero if the
2565    function is PURE, zero if not.  */
2566 static int
2567 pure_stmt_function (gfc_expr *, gfc_symbol *);
2568
2569 static int
2570 pure_function (gfc_expr *e, const char **name)
2571 {
2572   int pure;
2573
2574   *name = NULL;
2575
2576   if (e->symtree != NULL
2577         && e->symtree->n.sym != NULL
2578         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2579     return pure_stmt_function (e, e->symtree->n.sym);
2580
2581   if (e->value.function.esym)
2582     {
2583       pure = gfc_pure (e->value.function.esym);
2584       *name = e->value.function.esym->name;
2585     }
2586   else if (e->value.function.isym)
2587     {
2588       pure = e->value.function.isym->pure
2589              || e->value.function.isym->elemental;
2590       *name = e->value.function.isym->name;
2591     }
2592   else
2593     {
2594       /* Implicit functions are not pure.  */
2595       pure = 0;
2596       *name = e->value.function.name;
2597     }
2598
2599   return pure;
2600 }
2601
2602
2603 static bool
2604 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2605                  int *f ATTRIBUTE_UNUSED)
2606 {
2607   const char *name;
2608
2609   /* Don't bother recursing into other statement functions
2610      since they will be checked individually for purity.  */
2611   if (e->expr_type != EXPR_FUNCTION
2612         || !e->symtree
2613         || e->symtree->n.sym == sym
2614         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2615     return false;
2616
2617   return pure_function (e, &name) ? false : true;
2618 }
2619
2620
2621 static int
2622 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2623 {
2624   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2625 }
2626
2627
2628 static gfc_try
2629 is_scalar_expr_ptr (gfc_expr *expr)
2630 {
2631   gfc_try retval = SUCCESS;
2632   gfc_ref *ref;
2633   int start;
2634   int end;
2635
2636   /* See if we have a gfc_ref, which means we have a substring, array
2637      reference, or a component.  */
2638   if (expr->ref != NULL)
2639     {
2640       ref = expr->ref;
2641       while (ref->next != NULL)
2642         ref = ref->next;
2643
2644       switch (ref->type)
2645         {
2646         case REF_SUBSTRING:
2647           if (ref->u.ss.start == NULL || ref->u.ss.end == NULL
2648               || gfc_dep_compare_expr (ref->u.ss.start, ref->u.ss.end) != 0)
2649             retval = FAILURE;
2650           break;
2651
2652         case REF_ARRAY:
2653           if (ref->u.ar.type == AR_ELEMENT)
2654             retval = SUCCESS;
2655           else if (ref->u.ar.type == AR_FULL)
2656             {
2657               /* The user can give a full array if the array is of size 1.  */
2658               if (ref->u.ar.as != NULL
2659                   && ref->u.ar.as->rank == 1
2660                   && ref->u.ar.as->type == AS_EXPLICIT
2661                   && ref->u.ar.as->lower[0] != NULL
2662                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2663                   && ref->u.ar.as->upper[0] != NULL
2664                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2665                 {
2666                   /* If we have a character string, we need to check if
2667                      its length is one.  */
2668                   if (expr->ts.type == BT_CHARACTER)
2669                     {
2670                       if (expr->ts.u.cl == NULL
2671                           || expr->ts.u.cl->length == NULL
2672                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2673                           != 0)
2674                         retval = FAILURE;
2675                     }
2676                   else
2677                     {
2678                       /* We have constant lower and upper bounds.  If the
2679                          difference between is 1, it can be considered a
2680                          scalar.  
2681                          FIXME: Use gfc_dep_compare_expr instead.  */
2682                       start = (int) mpz_get_si
2683                                 (ref->u.ar.as->lower[0]->value.integer);
2684                       end = (int) mpz_get_si
2685                                 (ref->u.ar.as->upper[0]->value.integer);
2686                       if (end - start + 1 != 1)
2687                         retval = FAILURE;
2688                    }
2689                 }
2690               else
2691                 retval = FAILURE;
2692             }
2693           else
2694             retval = FAILURE;
2695           break;
2696         default:
2697           retval = SUCCESS;
2698           break;
2699         }
2700     }
2701   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2702     {
2703       /* Character string.  Make sure it's of length 1.  */
2704       if (expr->ts.u.cl == NULL
2705           || expr->ts.u.cl->length == NULL
2706           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2707         retval = FAILURE;
2708     }
2709   else if (expr->rank != 0)
2710     retval = FAILURE;
2711
2712   return retval;
2713 }
2714
2715
2716 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2717    and, in the case of c_associated, set the binding label based on
2718    the arguments.  */
2719
2720 static gfc_try
2721 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2722                           gfc_symbol **new_sym)
2723 {
2724   char name[GFC_MAX_SYMBOL_LEN + 1];
2725   int optional_arg = 0;
2726   gfc_try retval = SUCCESS;
2727   gfc_symbol *args_sym;
2728   gfc_typespec *arg_ts;
2729   symbol_attribute arg_attr;
2730
2731   if (args->expr->expr_type == EXPR_CONSTANT
2732       || args->expr->expr_type == EXPR_OP
2733       || args->expr->expr_type == EXPR_NULL)
2734     {
2735       gfc_error ("Argument to '%s' at %L is not a variable",
2736                  sym->name, &(args->expr->where));
2737       return FAILURE;
2738     }
2739
2740   args_sym = args->expr->symtree->n.sym;
2741
2742   /* The typespec for the actual arg should be that stored in the expr
2743      and not necessarily that of the expr symbol (args_sym), because
2744      the actual expression could be a part-ref of the expr symbol.  */
2745   arg_ts = &(args->expr->ts);
2746   arg_attr = gfc_expr_attr (args->expr);
2747     
2748   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2749     {
2750       /* If the user gave two args then they are providing something for
2751          the optional arg (the second cptr).  Therefore, set the name and
2752          binding label to the c_associated for two cptrs.  Otherwise,
2753          set c_associated to expect one cptr.  */
2754       if (args->next)
2755         {
2756           /* two args.  */
2757           sprintf (name, "%s_2", sym->name);
2758           optional_arg = 1;
2759         }
2760       else
2761         {
2762           /* one arg.  */
2763           sprintf (name, "%s_1", sym->name);
2764           optional_arg = 0;
2765         }
2766
2767       /* Get a new symbol for the version of c_associated that
2768          will get called.  */
2769       *new_sym = get_iso_c_sym (sym, name, NULL, optional_arg);
2770     }
2771   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2772            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2773     {
2774       sprintf (name, "%s", sym->name);
2775
2776       /* Error check the call.  */
2777       if (args->next != NULL)
2778         {
2779           gfc_error_now ("More actual than formal arguments in '%s' "
2780                          "call at %L", name, &(args->expr->where));
2781           retval = FAILURE;
2782         }
2783       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2784         {
2785           gfc_ref *ref;
2786           bool seen_section;
2787
2788           /* Make sure we have either the target or pointer attribute.  */
2789           if (!arg_attr.target && !arg_attr.pointer)
2790             {
2791               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2792                              "a TARGET or an associated pointer",
2793                              args_sym->name,
2794                              sym->name, &(args->expr->where));
2795               retval = FAILURE;
2796             }
2797
2798           if (gfc_is_coindexed (args->expr))
2799             {
2800               gfc_error_now ("Coindexed argument not permitted"
2801                              " in '%s' call at %L", name,
2802                              &(args->expr->where));
2803               retval = FAILURE;
2804             }
2805
2806           /* Follow references to make sure there are no array
2807              sections.  */
2808           seen_section = false;
2809
2810           for (ref=args->expr->ref; ref; ref = ref->next)
2811             {
2812               if (ref->type == REF_ARRAY)
2813                 {
2814                   if (ref->u.ar.type == AR_SECTION)
2815                     seen_section = true;
2816
2817                   if (ref->u.ar.type != AR_ELEMENT)
2818                     {
2819                       gfc_ref *r;
2820                       for (r = ref->next; r; r=r->next)
2821                         if (r->type == REF_COMPONENT)
2822                           {
2823                             gfc_error_now ("Array section not permitted"
2824                                            " in '%s' call at %L", name,
2825                                            &(args->expr->where));
2826                             retval = FAILURE;
2827                             break;
2828                           }
2829                     }
2830                 }
2831             }
2832
2833           if (seen_section && retval == SUCCESS)
2834             gfc_warning ("Array section in '%s' call at %L", name,
2835                          &(args->expr->where));
2836                          
2837           /* See if we have interoperable type and type param.  */
2838           if (gfc_verify_c_interop (arg_ts) == SUCCESS
2839               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2840             {
2841               if (args_sym->attr.target == 1)
2842                 {
2843                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2844                      has the target attribute and is interoperable.  */
2845                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2846                      allocatable variable that has the TARGET attribute and
2847                      is not an array of zero size.  */
2848                   if (args_sym->attr.allocatable == 1)
2849                     {
2850                       if (args_sym->attr.dimension != 0 
2851                           && (args_sym->as && args_sym->as->rank == 0))
2852                         {
2853                           gfc_error_now ("Allocatable variable '%s' used as a "
2854                                          "parameter to '%s' at %L must not be "
2855                                          "an array of zero size",
2856                                          args_sym->name, sym->name,
2857                                          &(args->expr->where));
2858                           retval = FAILURE;
2859                         }
2860                     }
2861                   else
2862                     {
2863                       /* A non-allocatable target variable with C
2864                          interoperable type and type parameters must be
2865                          interoperable.  */
2866                       if (args_sym && args_sym->attr.dimension)
2867                         {
2868                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2869                             {
2870                               gfc_error ("Assumed-shape array '%s' at %L "
2871                                          "cannot be an argument to the "
2872                                          "procedure '%s' because "
2873                                          "it is not C interoperable",
2874                                          args_sym->name,
2875                                          &(args->expr->where), sym->name);
2876                               retval = FAILURE;
2877                             }
2878                           else if (args_sym->as->type == AS_DEFERRED)
2879                             {
2880                               gfc_error ("Deferred-shape array '%s' at %L "
2881                                          "cannot be an argument to the "
2882                                          "procedure '%s' because "
2883                                          "it is not C interoperable",
2884                                          args_sym->name,
2885                                          &(args->expr->where), sym->name);
2886                               retval = FAILURE;
2887                             }
2888                         }
2889                               
2890                       /* Make sure it's not a character string.  Arrays of
2891                          any type should be ok if the variable is of a C
2892                          interoperable type.  */
2893                       if (arg_ts->type == BT_CHARACTER)
2894                         if (arg_ts->u.cl != NULL
2895                             && (arg_ts->u.cl->length == NULL
2896                                 || arg_ts->u.cl->length->expr_type
2897                                    != EXPR_CONSTANT
2898                                 || mpz_cmp_si
2899                                     (arg_ts->u.cl->length->value.integer, 1)
2900                                    != 0)
2901                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2902                           {
2903                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2904                                            "at %L must have a length of 1",
2905                                            args_sym->name, sym->name,
2906                                            &(args->expr->where));
2907                             retval = FAILURE;
2908                           }
2909                     }
2910                 }
2911               else if (arg_attr.pointer
2912                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2913                 {
2914                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2915                      scalar pointer.  */
2916                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2917                                  "associated scalar POINTER", args_sym->name,
2918                                  sym->name, &(args->expr->where));
2919                   retval = FAILURE;
2920                 }
2921             }
2922           else
2923             {
2924               /* The parameter is not required to be C interoperable.  If it
2925                  is not C interoperable, it must be a nonpolymorphic scalar
2926                  with no length type parameters.  It still must have either
2927                  the pointer or target attribute, and it can be
2928                  allocatable (but must be allocated when c_loc is called).  */
2929               if (args->expr->rank != 0 
2930                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2931                 {
2932                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2933                                  "scalar", args_sym->name, sym->name,
2934                                  &(args->expr->where));
2935                   retval = FAILURE;
2936                 }
2937               else if (arg_ts->type == BT_CHARACTER 
2938                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2939                 {
2940                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2941                                  "%L must have a length of 1",
2942                                  args_sym->name, sym->name,
2943                                  &(args->expr->where));
2944                   retval = FAILURE;
2945                 }
2946               else if (arg_ts->type == BT_CLASS)
2947                 {
2948                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
2949                                  "polymorphic", args_sym->name, sym->name,
2950                                  &(args->expr->where));
2951                   retval = FAILURE;
2952                 }
2953             }
2954         }
2955       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2956         {
2957           if (args_sym->attr.flavor != FL_PROCEDURE)
2958             {
2959               /* TODO: Update this error message to allow for procedure
2960                  pointers once they are implemented.  */
2961               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2962                              "procedure",
2963                              args_sym->name, sym->name,
2964                              &(args->expr->where));
2965               retval = FAILURE;
2966             }
2967           else if (args_sym->attr.is_bind_c != 1)
2968             {
2969               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2970                              "BIND(C)",
2971                              args_sym->name, sym->name,
2972                              &(args->expr->where));
2973               retval = FAILURE;
2974             }
2975         }
2976       
2977       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2978       *new_sym = sym;
2979     }
2980   else
2981     {
2982       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2983                           "iso_c_binding function: '%s'!\n", sym->name);
2984     }
2985
2986   return retval;
2987 }
2988
2989
2990 /* Resolve a function call, which means resolving the arguments, then figuring
2991    out which entity the name refers to.  */
2992
2993 static gfc_try
2994 resolve_function (gfc_expr *expr)
2995 {
2996   gfc_actual_arglist *arg;
2997   gfc_symbol *sym;
2998   const char *name;
2999   gfc_try t;
3000   int temp;
3001   procedure_type p = PROC_INTRINSIC;
3002   bool no_formal_args;
3003
3004   sym = NULL;
3005   if (expr->symtree)
3006     sym = expr->symtree->n.sym;
3007
3008   /* If this is a procedure pointer component, it has already been resolved.  */
3009   if (gfc_is_proc_ptr_comp (expr, NULL))
3010     return SUCCESS;
3011   
3012   if (sym && sym->attr.intrinsic
3013       && resolve_intrinsic (sym, &expr->where) == FAILURE)
3014     return FAILURE;
3015
3016   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
3017     {
3018       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
3019       return FAILURE;
3020     }
3021
3022   /* If this ia a deferred TBP with an abstract interface (which may
3023      of course be referenced), expr->value.function.esym will be set.  */
3024   if (sym && sym->attr.abstract && !expr->value.function.esym)
3025     {
3026       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3027                  sym->name, &expr->where);
3028       return FAILURE;
3029     }
3030
3031   /* Switch off assumed size checking and do this again for certain kinds
3032      of procedure, once the procedure itself is resolved.  */
3033   need_full_assumed_size++;
3034
3035   if (expr->symtree && expr->symtree->n.sym)
3036     p = expr->symtree->n.sym->attr.proc;
3037
3038   if (expr->value.function.isym && expr->value.function.isym->inquiry)
3039     inquiry_argument = true;
3040   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
3041
3042   if (resolve_actual_arglist (expr->value.function.actual,
3043                               p, no_formal_args) == FAILURE)
3044     {
3045       inquiry_argument = false;
3046       return FAILURE;
3047     }
3048
3049   inquiry_argument = false;
3050  
3051   /* Need to setup the call to the correct c_associated, depending on
3052      the number of cptrs to user gives to compare.  */
3053   if (sym && sym->attr.is_iso_c == 1)
3054     {
3055       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
3056           == FAILURE)
3057         return FAILURE;
3058       
3059       /* Get the symtree for the new symbol (resolved func).
3060          the old one will be freed later, when it's no longer used.  */
3061       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
3062     }
3063   
3064   /* Resume assumed_size checking.  */
3065   need_full_assumed_size--;
3066
3067   /* If the procedure is external, check for usage.  */
3068   if (sym && is_external_proc (sym))
3069     resolve_global_procedure (sym, &expr->where,
3070                               &expr->value.function.actual, 0);
3071
3072   if (sym && sym->ts.type == BT_CHARACTER
3073       && sym->ts.u.cl
3074       && sym->ts.u.cl->length == NULL
3075       && !sym->attr.dummy
3076       && !sym->ts.deferred
3077       && expr->value.function.esym == NULL
3078       && !sym->attr.contained)
3079     {
3080       /* Internal procedures are taken care of in resolve_contained_fntype.  */
3081       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
3082                  "be used at %L since it is not a dummy argument",
3083                  sym->name, &expr->where);
3084       return FAILURE;
3085     }
3086
3087   /* See if function is already resolved.  */
3088
3089   if (expr->value.function.name != NULL)
3090     {
3091       if (expr->ts.type == BT_UNKNOWN)
3092         expr->ts = sym->ts;
3093       t = SUCCESS;
3094     }
3095   else
3096     {
3097       /* Apply the rules of section 14.1.2.  */
3098
3099       switch (procedure_kind (sym))
3100         {
3101         case PTYPE_GENERIC:
3102           t = resolve_generic_f (expr);
3103           break;
3104
3105         case PTYPE_SPECIFIC:
3106           t = resolve_specific_f (expr);
3107           break;
3108
3109         case PTYPE_UNKNOWN:
3110           t = resolve_unknown_f (expr);
3111           break;
3112
3113         default:
3114           gfc_internal_error ("resolve_function(): bad function type");
3115         }
3116     }
3117
3118   /* If the expression is still a function (it might have simplified),
3119      then we check to see if we are calling an elemental function.  */
3120
3121   if (expr->expr_type != EXPR_FUNCTION)
3122     return t;
3123
3124   temp = need_full_assumed_size;
3125   need_full_assumed_size = 0;
3126
3127   if (resolve_elemental_actual (expr, NULL) == FAILURE)
3128     return FAILURE;
3129
3130   if (omp_workshare_flag
3131       && expr->value.function.esym
3132       && ! gfc_elemental (expr->value.function.esym))
3133     {
3134       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
3135                  "in WORKSHARE construct", expr->value.function.esym->name,
3136                  &expr->where);
3137       t = FAILURE;
3138     }
3139
3140 #define GENERIC_ID expr->value.function.isym->id
3141   else if (expr->value.function.actual != NULL
3142            && expr->value.function.isym != NULL
3143            && GENERIC_ID != GFC_ISYM_LBOUND
3144            && GENERIC_ID != GFC_ISYM_LEN
3145            && GENERIC_ID != GFC_ISYM_LOC
3146            && GENERIC_ID != GFC_ISYM_PRESENT)
3147     {
3148       /* Array intrinsics must also have the last upper bound of an
3149          assumed size array argument.  UBOUND and SIZE have to be
3150          excluded from the check if the second argument is anything
3151          than a constant.  */
3152
3153       for (arg = expr->value.function.actual; arg; arg = arg->next)
3154         {
3155           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3156               && arg->next != NULL && arg->next->expr)
3157             {
3158               if (arg->next->expr->expr_type != EXPR_CONSTANT)
3159                 break;
3160
3161               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
3162                 break;
3163
3164               if ((int)mpz_get_si (arg->next->expr->value.integer)
3165                         < arg->expr->rank)
3166                 break;
3167             }
3168
3169           if (arg->expr != NULL
3170               && arg->expr->rank > 0
3171               && resolve_assumed_size_actual (arg->expr))
3172             return FAILURE;
3173         }
3174     }
3175 #undef GENERIC_ID
3176
3177   need_full_assumed_size = temp;
3178   name = NULL;
3179
3180   if (!pure_function (expr, &name) && name)
3181     {
3182       if (forall_flag)
3183         {
3184           gfc_error ("Reference to non-PURE function '%s' at %L inside a "
3185                      "FORALL %s", name, &expr->where,
3186                      forall_flag == 2 ? "mask" : "block");
3187           t = FAILURE;
3188         }
3189       else if (do_concurrent_flag)
3190         {
3191           gfc_error ("Reference to non-PURE function '%s' at %L inside a "
3192                      "DO CONCURRENT %s", name, &expr->where,
3193                      do_concurrent_flag == 2 ? "mask" : "block");
3194           t = FAILURE;
3195         }
3196       else if (gfc_pure (NULL))
3197         {
3198           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
3199                      "procedure within a PURE procedure", name, &expr->where);
3200           t = FAILURE;
3201         }
3202
3203       if (gfc_implicit_pure (NULL))
3204         gfc_current_ns->proc_name->attr.implicit_pure = 0;
3205     }
3206
3207   /* Functions without the RECURSIVE attribution are not allowed to
3208    * call themselves.  */
3209   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3210     {
3211       gfc_symbol *esym;
3212       esym = expr->value.function.esym;
3213
3214       if (is_illegal_recursion (esym, gfc_current_ns))
3215       {
3216         if (esym->attr.entry && esym->ns->entries)
3217           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3218                      " function '%s' is not RECURSIVE",
3219                      esym->name, &expr->where, esym->ns->entries->sym->name);
3220         else
3221           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
3222                      " is not RECURSIVE", esym->name, &expr->where);
3223
3224         t = FAILURE;
3225       }
3226     }
3227
3228   /* Character lengths of use associated functions may contains references to
3229      symbols not referenced from the current program unit otherwise.  Make sure
3230      those symbols are marked as referenced.  */
3231
3232   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3233       && expr->value.function.esym->attr.use_assoc)
3234     {
3235       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3236     }
3237
3238   /* Make sure that the expression has a typespec that works.  */
3239   if (expr->ts.type == BT_UNKNOWN)
3240     {
3241       if (expr->symtree->n.sym->result
3242             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3243             && !expr->symtree->n.sym->result->attr.proc_pointer)
3244         expr->ts = expr->symtree->n.sym->result->ts;
3245     }
3246
3247   return t;
3248 }
3249
3250
3251 /************* Subroutine resolution *************/
3252
3253 static void
3254 pure_subroutine (gfc_code *c, gfc_symbol *sym)
3255 {
3256   if (gfc_pure (sym))
3257     return;
3258
3259   if (forall_flag)
3260     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
3261                sym->name, &c->loc);
3262   else if (do_concurrent_flag)
3263     gfc_error ("Subroutine call to '%s' in DO CONCURRENT block at %L is not "
3264                "PURE", sym->name, &c->loc);
3265   else if (gfc_pure (NULL))
3266     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
3267                &c->loc);
3268
3269   if (gfc_implicit_pure (NULL))
3270     gfc_current_ns->proc_name->attr.implicit_pure = 0;
3271 }
3272
3273
3274 static match
3275 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3276 {
3277   gfc_symbol *s;
3278
3279   if (sym->attr.generic)
3280     {
3281       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3282       if (s != NULL)
3283         {
3284           c->resolved_sym = s;
3285           pure_subroutine (c, s);
3286           return MATCH_YES;
3287         }
3288
3289       /* TODO: Need to search for elemental references in generic interface.  */
3290     }
3291
3292   if (sym->attr.intrinsic)
3293     return gfc_intrinsic_sub_interface (c, 0);
3294
3295   return MATCH_NO;
3296 }
3297
3298
3299 static gfc_try
3300 resolve_generic_s (gfc_code *c)
3301 {
3302   gfc_symbol *sym;
3303   match m;
3304
3305   sym = c->symtree->n.sym;
3306
3307   for (;;)
3308     {
3309       m = resolve_generic_s0 (c, sym);
3310       if (m == MATCH_YES)
3311         return SUCCESS;
3312       else if (m == MATCH_ERROR)
3313         return FAILURE;
3314
3315 generic:
3316       if (sym->ns->parent == NULL)
3317         break;
3318       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3319
3320       if (sym == NULL)
3321         break;
3322       if (!generic_sym (sym))
3323         goto generic;
3324     }
3325
3326   /* Last ditch attempt.  See if the reference is to an intrinsic
3327      that possesses a matching interface.  14.1.2.4  */
3328   sym = c->symtree->n.sym;
3329
3330   if (!gfc_is_intrinsic (sym, 1, c->loc))
3331     {
3332       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3333                  sym->name, &c->loc);
3334       return FAILURE;
3335     }
3336
3337   m = gfc_intrinsic_sub_interface (c, 0);
3338   if (m == MATCH_YES)
3339     return SUCCESS;
3340   if (m == MATCH_NO)
3341     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3342                "intrinsic subroutine interface", sym->name, &c->loc);
3343
3344   return FAILURE;
3345 }
3346
3347
3348 /* Set the name and binding label of the subroutine symbol in the call
3349    expression represented by 'c' to include the type and kind of the
3350    second parameter.  This function is for resolving the appropriate
3351    version of c_f_pointer() and c_f_procpointer().  For example, a
3352    call to c_f_pointer() for a default integer pointer could have a
3353    name of c_f_pointer_i4.  If no second arg exists, which is an error
3354    for these two functions, it defaults to the generic symbol's name
3355    and binding label.  */
3356
3357 static void
3358 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3359                     char *name, const char **binding_label)
3360 {
3361   gfc_expr *arg = NULL;
3362   char type;
3363   int kind;
3364
3365   /* The second arg of c_f_pointer and c_f_procpointer determines
3366      the type and kind for the procedure name.  */
3367   arg = c->ext.actual->next->expr;
3368
3369   if (arg != NULL)
3370     {
3371       /* Set up the name to have the given symbol's name,
3372          plus the type and kind.  */
3373       /* a derived type is marked with the type letter 'u' */
3374       if (arg->ts.type == BT_DERIVED)
3375         {
3376           type = 'd';
3377           kind = 0; /* set the kind as 0 for now */
3378         }
3379       else
3380         {
3381           type = gfc_type_letter (arg->ts.type);
3382           kind = arg->ts.kind;
3383         }
3384
3385       if (arg->ts.type == BT_CHARACTER)
3386         /* Kind info for character strings not needed.  */
3387         kind = 0;
3388
3389       sprintf (name, "%s_%c%d", sym->name, type, kind);
3390       /* Set up the binding label as the given symbol's label plus
3391          the type and kind.  */
3392       *binding_label = gfc_get_string ("%s_%c%d", sym->binding_label, type, 
3393                                        kind);
3394     }
3395   else
3396     {
3397       /* If the second arg is missing, set the name and label as
3398          was, cause it should at least be found, and the missing
3399          arg error will be caught by compare_parameters().  */
3400       sprintf (name, "%s", sym->name);
3401       *binding_label = sym->binding_label;
3402     }
3403    
3404   return;
3405 }
3406
3407
3408 /* Resolve a generic version of the iso_c_binding procedure given
3409    (sym) to the specific one based on the type and kind of the
3410    argument(s).  Currently, this function resolves c_f_pointer() and
3411    c_f_procpointer based on the type and kind of the second argument
3412    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3413    Upon successfully exiting, c->resolved_sym will hold the resolved
3414    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3415    otherwise.  */
3416
3417 match
3418 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3419 {
3420   gfc_symbol *new_sym;
3421   /* this is fine, since we know the names won't use the max */
3422   char name[GFC_MAX_SYMBOL_LEN + 1];
3423   const char* binding_label;
3424   /* default to success; will override if find error */
3425   match m = MATCH_YES;
3426
3427   /* Make sure the actual arguments are in the necessary order (based on the 
3428      formal args) before resolving.  */
3429   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3430
3431   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3432       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3433     {
3434       set_name_and_label (c, sym, name, &binding_label);
3435       
3436       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3437         {
3438           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3439             {
3440               /* Make sure we got a third arg if the second arg has non-zero
3441                  rank.  We must also check that the type and rank are
3442                  correct since we short-circuit this check in
3443                  gfc_procedure_use() (called above to sort actual args).  */
3444               if (c->ext.actual->next->expr->rank != 0)
3445                 {
3446                   if(c->ext.actual->next->next == NULL 
3447                      || c->ext.actual->next->next->expr == NULL)
3448                     {
3449                       m = MATCH_ERROR;
3450                       gfc_error ("Missing SHAPE parameter for call to %s "
3451                                  "at %L", sym->name, &(c->loc));
3452                     }
3453                   else if (c->ext.actual->next->next->expr->ts.type
3454                            != BT_INTEGER
3455                            || c->ext.actual->next->next->expr->rank != 1)
3456                     {
3457                       m = MATCH_ERROR;
3458                       gfc_error ("SHAPE parameter for call to %s at %L must "
3459                                  "be a rank 1 INTEGER array", sym->name,
3460                                  &(c->loc));
3461                     }
3462                 }
3463             }
3464         }
3465       
3466       if (m != MATCH_ERROR)
3467         {
3468           /* the 1 means to add the optional arg to formal list */
3469           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3470          
3471           /* for error reporting, say it's declared where the original was */
3472           new_sym->declared_at = sym->declared_at;
3473         }
3474     }
3475   else
3476     {
3477       /* no differences for c_loc or c_funloc */
3478       new_sym = sym;
3479     }
3480
3481   /* set the resolved symbol */
3482   if (m != MATCH_ERROR)
3483     c->resolved_sym = new_sym;
3484   else
3485     c->resolved_sym = sym;
3486   
3487   return m;
3488 }
3489
3490
3491 /* Resolve a subroutine call known to be specific.  */
3492
3493 static match
3494 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3495 {
3496   match m;
3497
3498   if(sym->attr.is_iso_c)
3499     {
3500       m = gfc_iso_c_sub_interface (c,sym);
3501       return m;
3502     }
3503   
3504   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3505     {
3506       if (sym->attr.dummy)
3507         {
3508           sym->attr.proc = PROC_DUMMY;
3509           goto found;
3510         }
3511
3512       sym->attr.proc = PROC_EXTERNAL;
3513       goto found;
3514     }
3515
3516   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3517     goto found;
3518
3519   if (sym->attr.intrinsic)
3520     {
3521       m = gfc_intrinsic_sub_interface (c, 1);
3522       if (m == MATCH_YES)
3523         return MATCH_YES;
3524       if (m == MATCH_NO)
3525         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3526                    "with an intrinsic", sym->name, &c->loc);
3527
3528       return MATCH_ERROR;
3529     }
3530
3531   return MATCH_NO;
3532
3533 found:
3534   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3535
3536   c->resolved_sym = sym;
3537   pure_subroutine (c, sym);
3538
3539   return MATCH_YES;
3540 }
3541
3542
3543 static gfc_try
3544 resolve_specific_s (gfc_code *c)
3545 {
3546   gfc_symbol *sym;
3547   match m;
3548
3549   sym = c->symtree->n.sym;
3550
3551   for (;;)
3552     {
3553       m = resolve_specific_s0 (c, sym);
3554       if (m == MATCH_YES)
3555         return SUCCESS;
3556       if (m == MATCH_ERROR)
3557         return FAILURE;
3558
3559       if (sym->ns->parent == NULL)
3560         break;
3561
3562       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3563
3564       if (sym == NULL)
3565         break;
3566     }
3567
3568   sym = c->symtree->n.sym;
3569   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3570              sym->name, &c->loc);
3571
3572   return FAILURE;
3573 }
3574
3575
3576 /* Resolve a subroutine call not known to be generic nor specific.  */
3577
3578 static gfc_try
3579 resolve_unknown_s (gfc_code *c)
3580 {
3581   gfc_symbol *sym;
3582
3583   sym = c->symtree->n.sym;
3584
3585   if (sym->attr.dummy)
3586     {
3587       sym->attr.proc = PROC_DUMMY;
3588       goto found;
3589     }
3590
3591   /* See if we have an intrinsic function reference.  */
3592
3593   if (gfc_is_intrinsic (sym, 1, c->loc))
3594     {
3595       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3596         return SUCCESS;
3597       return FAILURE;
3598     }
3599
3600   /* The reference is to an external name.  */
3601
3602 found:
3603   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3604
3605   c->resolved_sym = sym;
3606
3607   pure_subroutine (c, sym);
3608
3609   return SUCCESS;
3610 }
3611
3612
3613 /* Resolve a subroutine call.  Although it was tempting to use the same code
3614    for functions, subroutines and functions are stored differently and this
3615    makes things awkward.  */
3616
3617 static gfc_try
3618 resolve_call (gfc_code *c)
3619 {
3620   gfc_try t;
3621   procedure_type ptype = PROC_INTRINSIC;
3622   gfc_symbol *csym, *sym;
3623   bool no_formal_args;
3624
3625   csym = c->symtree ? c->symtree->n.sym : NULL;
3626
3627   if (csym && csym->ts.type != BT_UNKNOWN)
3628     {
3629       gfc_error ("'%s' at %L has a type, which is not consistent with "
3630                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3631       return FAILURE;
3632     }
3633
3634   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3635     {
3636       gfc_symtree *st;
3637       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3638       sym = st ? st->n.sym : NULL;
3639       if (sym && csym != sym
3640               && sym->ns == gfc_current_ns
3641               && sym->attr.flavor == FL_PROCEDURE
3642               && sym->attr.contained)
3643         {
3644           sym->refs++;
3645           if (csym->attr.generic)
3646             c->symtree->n.sym = sym;
3647           else
3648             c->symtree = st;
3649           csym = c->symtree->n.sym;
3650         }
3651     }
3652
3653   /* If this ia a deferred TBP with an abstract interface
3654      (which may of course be referenced), c->expr1 will be set.  */
3655   if (csym && csym->attr.abstract && !c->expr1)
3656     {
3657       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3658                  csym->name, &c->loc);
3659       return FAILURE;
3660     }
3661
3662   /* Subroutines without the RECURSIVE attribution are not allowed to
3663    * call themselves.  */
3664   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3665     {
3666       if (csym->attr.entry && csym->ns->entries)
3667         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3668                    " subroutine '%s' is not RECURSIVE",
3669                    csym->name, &c->loc, csym->ns->entries->sym->name);
3670       else
3671         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3672                    " is not RECURSIVE", csym->name, &c->loc);
3673
3674       t = FAILURE;
3675     }
3676
3677   /* Switch off assumed size checking and do this again for certain kinds
3678      of procedure, once the procedure itself is resolved.  */
3679   need_full_assumed_size++;
3680
3681   if (csym)
3682     ptype = csym->attr.proc;
3683
3684   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3685   if (resolve_actual_arglist (c->ext.actual, ptype,
3686                               no_formal_args) == FAILURE)
3687     return FAILURE;
3688
3689   /* Resume assumed_size checking.  */
3690   need_full_assumed_size--;
3691
3692   /* If external, check for usage.  */
3693   if (csym && is_external_proc (csym))
3694     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3695
3696   t = SUCCESS;
3697   if (c->resolved_sym == NULL)
3698     {
3699       c->resolved_isym = NULL;
3700       switch (procedure_kind (csym))
3701         {
3702         case PTYPE_GENERIC:
3703           t = resolve_generic_s (c);
3704           break;
3705
3706         case PTYPE_SPECIFIC:
3707           t = resolve_specific_s (c);
3708           break;
3709
3710         case PTYPE_UNKNOWN:
3711           t = resolve_unknown_s (c);
3712           break;
3713
3714         default:
3715           gfc_internal_error ("resolve_subroutine(): bad function type");
3716         }
3717     }
3718
3719   /* Some checks of elemental subroutine actual arguments.  */
3720   if (resolve_elemental_actual (NULL, c) == FAILURE)
3721     return FAILURE;
3722
3723   return t;
3724 }
3725
3726
3727 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3728    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3729    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3730    if their shapes do not match.  If either op1->shape or op2->shape is
3731    NULL, return SUCCESS.  */
3732
3733 static gfc_try
3734 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3735 {
3736   gfc_try t;
3737   int i;
3738
3739   t = SUCCESS;
3740
3741   if (op1->shape != NULL && op2->shape != NULL)
3742     {
3743       for (i = 0; i < op1->rank; i++)
3744         {
3745           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3746            {
3747              gfc_error ("Shapes for operands at %L and %L are not conformable",
3748                          &op1->where, &op2->where);
3749              t = FAILURE;
3750              break;
3751            }
3752         }
3753     }
3754
3755   return t;
3756 }
3757
3758
3759 /* Resolve an operator expression node.  This can involve replacing the
3760    operation with a user defined function call.  */
3761
3762 static gfc_try
3763 resolve_operator (gfc_expr *e)
3764 {
3765   gfc_expr *op1, *op2;
3766   char msg[200];
3767   bool dual_locus_error;
3768   gfc_try t;
3769
3770   /* Resolve all subnodes-- give them types.  */
3771
3772   switch (e->value.op.op)
3773     {
3774     default:
3775       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3776         return FAILURE;
3777
3778     /* Fall through...  */
3779
3780     case INTRINSIC_NOT:
3781     case INTRINSIC_UPLUS:
3782     case INTRINSIC_UMINUS:
3783     case INTRINSIC_PARENTHESES:
3784       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3785         return FAILURE;
3786       break;
3787     }
3788
3789   /* Typecheck the new node.  */
3790
3791   op1 = e->value.op.op1;
3792   op2 = e->value.op.op2;
3793   dual_locus_error = false;
3794
3795   if ((op1 && op1->expr_type == EXPR_NULL)
3796       || (op2 && op2->expr_type == EXPR_NULL))
3797     {
3798       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3799       goto bad_op;
3800     }
3801
3802   switch (e->value.op.op)
3803     {
3804     case INTRINSIC_UPLUS:
3805     case INTRINSIC_UMINUS:
3806       if (op1->ts.type == BT_INTEGER
3807           || op1->ts.type == BT_REAL
3808           || op1->ts.type == BT_COMPLEX)
3809         {
3810           e->ts = op1->ts;
3811           break;
3812         }
3813
3814       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3815                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3816       goto bad_op;
3817
3818     case INTRINSIC_PLUS:
3819     case INTRINSIC_MINUS:
3820     case INTRINSIC_TIMES:
3821     case INTRINSIC_DIVIDE:
3822     case INTRINSIC_POWER:
3823       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3824         {
3825           gfc_type_convert_binary (e, 1);
3826           break;
3827         }
3828
3829       sprintf (msg,
3830                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3831                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3832                gfc_typename (&op2->ts));
3833       goto bad_op;
3834
3835     case INTRINSIC_CONCAT:
3836       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3837           && op1->ts.kind == op2->ts.kind)
3838         {
3839           e->ts.type = BT_CHARACTER;
3840           e->ts.kind = op1->ts.kind;
3841           break;
3842         }
3843
3844       sprintf (msg,
3845                _("Operands of string concatenation operator at %%L are %s/%s"),
3846                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3847       goto bad_op;
3848
3849     case INTRINSIC_AND:
3850     case INTRINSIC_OR:
3851     case INTRINSIC_EQV:
3852     case INTRINSIC_NEQV:
3853       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3854         {
3855           e->ts.type = BT_LOGICAL;
3856           e->ts.kind = gfc_kind_max (op1, op2);
3857           if (op1->ts.kind < e->ts.kind)
3858             gfc_convert_type (op1, &e->ts, 2);
3859           else if (op2->ts.kind < e->ts.kind)
3860             gfc_convert_type (op2, &e->ts, 2);
3861           break;
3862         }
3863
3864       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3865                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3866                gfc_typename (&op2->ts));
3867
3868       goto bad_op;
3869
3870     case INTRINSIC_NOT:
3871       if (op1->ts.type == BT_LOGICAL)
3872         {
3873           e->ts.type = BT_LOGICAL;
3874           e->ts.kind = op1->ts.kind;
3875           break;
3876         }
3877
3878       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3879                gfc_typename (&op1->ts));
3880       goto bad_op;
3881
3882     case INTRINSIC_GT:
3883     case INTRINSIC_GT_OS:
3884     case INTRINSIC_GE:
3885     case INTRINSIC_GE_OS:
3886     case INTRINSIC_LT:
3887     case INTRINSIC_LT_OS:
3888     case INTRINSIC_LE:
3889     case INTRINSIC_LE_OS:
3890       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3891         {
3892           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3893           goto bad_op;
3894         }
3895
3896       /* Fall through...  */
3897
3898     case INTRINSIC_EQ:
3899     case INTRINSIC_EQ_OS:
3900     case INTRINSIC_NE:
3901     case INTRINSIC_NE_OS:
3902       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3903           && op1->ts.kind == op2->ts.kind)
3904         {
3905           e->ts.type = BT_LOGICAL;
3906           e->ts.kind = gfc_default_logical_kind;
3907           break;
3908         }
3909
3910       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3911         {
3912           gfc_type_convert_binary (e, 1);
3913
3914           e->ts.type = BT_LOGICAL;
3915           e->ts.kind = gfc_default_logical_kind;
3916           break;
3917         }
3918
3919       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3920         sprintf (msg,
3921                  _("Logicals at %%L must be compared with %s instead of %s"),
3922                  (e->value.op.op == INTRINSIC_EQ 
3923                   || e->value.op.op == INTRINSIC_EQ_OS)
3924                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3925       else
3926         sprintf (msg,
3927                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3928                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3929                  gfc_typename (&op2->ts));
3930
3931       goto bad_op;
3932
3933     case INTRINSIC_USER:
3934       if (e->value.op.uop->op == NULL)
3935         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3936       else if (op2 == NULL)
3937         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3938                  e->value.op.uop->name, gfc_typename (&op1->ts));
3939       else
3940         {
3941           sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3942                    e->value.op.uop->name, gfc_typename (&op1->ts),
3943                    gfc_typename (&op2->ts));
3944           e->value.op.uop->op->sym->attr.referenced = 1;
3945         }
3946
3947       goto bad_op;
3948
3949     case INTRINSIC_PARENTHESES:
3950       e->ts = op1->ts;
3951       if (e->ts.type == BT_CHARACTER)
3952         e->ts.u.cl = op1->ts.u.cl;
3953       break;
3954
3955     default:
3956       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3957     }
3958
3959   /* Deal with arrayness of an operand through an operator.  */
3960
3961   t = SUCCESS;
3962
3963   switch (e->value.op.op)
3964     {
3965     case INTRINSIC_PLUS:
3966     case INTRINSIC_MINUS:
3967     case INTRINSIC_TIMES:
3968     case INTRINSIC_DIVIDE:
3969     case INTRINSIC_POWER:
3970     case INTRINSIC_CONCAT:
3971     case INTRINSIC_AND:
3972     case INTRINSIC_OR:
3973     case INTRINSIC_EQV:
3974     case INTRINSIC_NEQV:
3975     case INTRINSIC_EQ:
3976     case INTRINSIC_EQ_OS:
3977     case INTRINSIC_NE:
3978     case INTRINSIC_NE_OS:
3979     case INTRINSIC_GT:
3980     case INTRINSIC_GT_OS:
3981     case INTRINSIC_GE:
3982     case INTRINSIC_GE_OS:
3983     case INTRINSIC_LT:
3984     case INTRINSIC_LT_OS:
3985     case INTRINSIC_LE:
3986     case INTRINSIC_LE_OS:
3987
3988       if (op1->rank == 0 && op2->rank == 0)
3989         e->rank = 0;
3990
3991       if (op1->rank == 0 && op2->rank != 0)
3992         {
3993           e->rank = op2->rank;
3994
3995           if (e->shape == NULL)
3996             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3997         }
3998
3999       if (op1->rank != 0 && op2->rank == 0)
4000         {
4001           e->rank = op1->rank;
4002
4003           if (e->shape == NULL)
4004             e->shape = gfc_copy_shape (op1->shape, op1->rank);
4005         }
4006
4007       if (op1->rank != 0 && op2->rank != 0)
4008         {
4009           if (op1->rank == op2->rank)
4010             {
4011               e->rank = op1->rank;
4012               if (e->shape == NULL)
4013                 {
4014                   t = compare_shapes (op1, op2);
4015                   if (t == FAILURE)
4016                     e->shape = NULL;
4017                   else
4018                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
4019                 }
4020             }
4021           else
4022             {
4023               /* Allow higher level expressions to work.  */
4024               e->rank = 0;
4025
4026               /* Try user-defined operators, and otherwise throw an error.  */
4027               dual_locus_error = true;
4028               sprintf (msg,
4029                        _("Inconsistent ranks for operator at %%L and %%L"));
4030               goto bad_op;
4031             }
4032         }
4033
4034       break;
4035
4036     case INTRINSIC_PARENTHESES:
4037     case INTRINSIC_NOT:
4038     case INTRINSIC_UPLUS:
4039     case INTRINSIC_UMINUS:
4040       /* Simply copy arrayness attribute */
4041       e->rank = op1->rank;
4042
4043       if (e->shape == NULL)
4044         e->shape = gfc_copy_shape (op1->shape, op1->rank);
4045
4046       break;
4047
4048     default:
4049       break;
4050     }
4051
4052   /* Attempt to simplify the expression.  */
4053   if (t == SUCCESS)
4054     {
4055       t = gfc_simplify_expr (e, 0);
4056       /* Some calls do not succeed in simplification and return FAILURE
4057          even though there is no error; e.g. variable references to
4058          PARAMETER arrays.  */
4059       if (!gfc_is_constant_expr (e))
4060         t = SUCCESS;
4061     }
4062   return t;
4063
4064 bad_op:
4065
4066   {
4067     match m = gfc_extend_expr (e);
4068     if (m == MATCH_YES)
4069       return SUCCESS;
4070     if (m == MATCH_ERROR)
4071       return FAILURE;
4072   }
4073
4074   if (dual_locus_error)
4075     gfc_error (msg, &op1->where, &op2->where);
4076   else
4077     gfc_error (msg, &e->where);
4078
4079   return FAILURE;
4080 }
4081
4082
4083 /************** Array resolution subroutines **************/
4084
4085 typedef enum
4086 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
4087 comparison;
4088
4089 /* Compare two integer expressions.  */
4090
4091 static comparison
4092 compare_bound (gfc_expr *a, gfc_expr *b)
4093 {
4094   int i;
4095
4096   if (a == NULL || a->expr_type != EXPR_CONSTANT
4097       || b == NULL || b->expr_type != EXPR_CONSTANT)
4098     return CMP_UNKNOWN;
4099
4100   /* If either of the types isn't INTEGER, we must have
4101      raised an error earlier.  */
4102
4103   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
4104     return CMP_UNKNOWN;
4105
4106   i = mpz_cmp (a->value.integer, b->value.integer);
4107
4108   if (i < 0)
4109     return CMP_LT;
4110   if (i > 0)
4111     return CMP_GT;
4112   return CMP_EQ;
4113 }
4114
4115
4116 /* Compare an integer expression with an integer.  */
4117
4118 static comparison
4119 compare_bound_int (gfc_expr *a, int b)
4120 {
4121   int i;
4122
4123   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4124     return CMP_UNKNOWN;
4125
4126   if (a->ts.type != BT_INTEGER)
4127     gfc_internal_error ("compare_bound_int(): Bad expression");
4128
4129   i = mpz_cmp_si (a->value.integer, b);
4130
4131   if (i < 0)
4132     return CMP_LT;
4133   if (i > 0)
4134     return CMP_GT;
4135   return CMP_EQ;
4136 }
4137
4138
4139 /* Compare an integer expression with a mpz_t.  */
4140
4141 static comparison
4142 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
4143 {
4144   int i;
4145
4146   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4147     return CMP_UNKNOWN;
4148
4149   if (a->ts.type != BT_INTEGER)
4150     gfc_internal_error ("compare_bound_int(): Bad expression");
4151
4152   i = mpz_cmp (a->value.integer, b);
4153
4154   if (i < 0)
4155     return CMP_LT;
4156   if (i > 0)
4157     return CMP_GT;
4158   return CMP_EQ;
4159 }
4160
4161
4162 /* Compute the last value of a sequence given by a triplet.  
4163    Return 0 if it wasn't able to compute the last value, or if the
4164    sequence if empty, and 1 otherwise.  */
4165
4166 static int
4167 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
4168                                 gfc_expr *stride, mpz_t last)
4169 {
4170   mpz_t rem;
4171
4172   if (start == NULL || start->expr_type != EXPR_CONSTANT
4173       || end == NULL || end->expr_type != EXPR_CONSTANT
4174       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
4175     return 0;
4176
4177   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
4178       || (stride != NULL && stride->ts.type != BT_INTEGER))
4179     return 0;
4180
4181   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
4182     {
4183       if (compare_bound (start, end) == CMP_GT)
4184         return 0;
4185       mpz_set (last, end->value.integer);
4186       return 1;
4187     }
4188
4189   if (compare_bound_int (stride, 0) == CMP_GT)
4190     {
4191       /* Stride is positive */
4192       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
4193         return 0;
4194     }
4195   else
4196     {
4197       /* Stride is negative */
4198       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
4199         return 0;
4200     }
4201
4202   mpz_init (rem);
4203   mpz_sub (rem, end->value.integer, start->value.integer);
4204   mpz_tdiv_r (rem, rem, stride->value.integer);
4205   mpz_sub (last, end->value.integer, rem);
4206   mpz_clear (rem);
4207
4208   return 1;
4209 }
4210
4211
4212 /* Compare a single dimension of an array reference to the array
4213    specification.  */
4214
4215 static gfc_try
4216 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
4217 {
4218   mpz_t last_value;
4219
4220   if (ar->dimen_type[i] == DIMEN_STAR)
4221     {
4222       gcc_assert (ar->stride[i] == NULL);
4223       /* This implies [*] as [*:] and [*:3] are not possible.  */
4224       if (ar->start[i] == NULL)
4225         {
4226           gcc_assert (ar->end[i] == NULL);
4227           return SUCCESS;
4228         }
4229     }
4230
4231 /* Given start, end and stride values, calculate the minimum and
4232    maximum referenced indexes.  */
4233
4234   switch (ar->dimen_type[i])
4235     {
4236     case DIMEN_VECTOR:
4237     case DIMEN_THIS_IMAGE:
4238       break;
4239
4240     case DIMEN_STAR:
4241     case DIMEN_ELEMENT:
4242       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4243         {
4244           if (i < as->rank)
4245             gfc_warning ("Array reference at %L is out of bounds "
4246                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
4247                          mpz_get_si (ar->start[i]->value.integer),
4248                          mpz_get_si (as->lower[i]->value.integer), i+1);
4249           else
4250             gfc_warning ("Array reference at %L is out of bounds "
4251                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
4252                          mpz_get_si (ar->start[i]->value.integer),
4253                          mpz_get_si (as->lower[i]->value.integer),
4254                          i + 1 - as->rank);
4255           return SUCCESS;
4256         }
4257       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4258         {
4259           if (i < as->rank)
4260             gfc_warning ("Array reference at %L is out of bounds "
4261                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
4262                          mpz_get_si (ar->start[i]->value.integer),
4263                          mpz_get_si (as->upper[i]->value.integer), i+1);
4264           else
4265             gfc_warning ("Array reference at %L is out of bounds "
4266                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
4267                          mpz_get_si (ar->start[i]->value.integer),
4268                          mpz_get_si (as->upper[i]->value.integer),
4269                          i + 1 - as->rank);
4270           return SUCCESS;
4271         }
4272
4273       break;
4274
4275     case DIMEN_RANGE:
4276       {
4277 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4278 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4279
4280         comparison comp_start_end = compare_bound (AR_START, AR_END);
4281
4282         /* Check for zero stride, which is not allowed.  */
4283         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4284           {
4285             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4286             return FAILURE;
4287           }
4288
4289         /* if start == len || (stride > 0 && start < len)
4290                            || (stride < 0 && start > len),
4291            then the array section contains at least one element.  In this
4292            case, there is an out-of-bounds access if
4293            (start < lower || start > upper).  */
4294         if (compare_bound (AR_START, AR_END) == CMP_EQ
4295             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4296                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4297             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4298                 && comp_start_end == CMP_GT))
4299           {
4300             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4301               {
4302                 gfc_warning ("Lower array reference at %L is out of bounds "
4303                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4304                        mpz_get_si (AR_START->value.integer),
4305                        mpz_get_si (as->lower[i]->value.integer), i+1);
4306                 return SUCCESS;
4307               }
4308             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4309               {
4310                 gfc_warning ("Lower array reference at %L is out of bounds "
4311                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4312                        mpz_get_si (AR_START->value.integer),
4313                        mpz_get_si (as->upper[i]->value.integer), i+1);
4314                 return SUCCESS;
4315               }
4316           }
4317
4318         /* If we can compute the highest index of the array section,
4319            then it also has to be between lower and upper.  */
4320         mpz_init (last_value);
4321         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4322                                             last_value))
4323           {
4324             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4325               {
4326                 gfc_warning ("Upper array reference at %L is out of bounds "
4327                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4328                        mpz_get_si (last_value),
4329                        mpz_get_si (as->lower[i]->value.integer), i+1);
4330                 mpz_clear (last_value);
4331                 return SUCCESS;
4332               }
4333             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4334               {
4335                 gfc_warning ("Upper array reference at %L is out of bounds "
4336                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4337                        mpz_get_si (last_value),
4338                        mpz_get_si (as->upper[i]->value.integer), i+1);
4339                 mpz_clear (last_value);
4340                 return SUCCESS;
4341               }
4342           }
4343         mpz_clear (last_value);
4344
4345 #undef AR_START
4346 #undef AR_END
4347       }
4348       break;
4349
4350     default:
4351       gfc_internal_error ("check_dimension(): Bad array reference");
4352     }
4353
4354   return SUCCESS;
4355 }
4356
4357
4358 /* Compare an array reference with an array specification.  */
4359
4360 static gfc_try
4361 compare_spec_to_ref (gfc_array_ref *ar)
4362 {
4363   gfc_array_spec *as;
4364   int i;
4365
4366   as = ar->as;
4367   i = as->rank - 1;
4368   /* TODO: Full array sections are only allowed as actual parameters.  */
4369   if (as->type == AS_ASSUMED_SIZE
4370       && (/*ar->type == AR_FULL
4371           ||*/ (ar->type == AR_SECTION
4372               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4373     {
4374       gfc_error ("Rightmost upper bound of assumed size array section "
4375                  "not specified at %L", &ar->where);
4376       return FAILURE;
4377     }
4378
4379   if (ar->type == AR_FULL)
4380     return SUCCESS;
4381
4382   if (as->rank != ar->dimen)
4383     {
4384       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4385                  &ar->where, ar->dimen, as->rank);
4386       return FAILURE;
4387     }
4388
4389   /* ar->codimen == 0 is a local array.  */
4390   if (as->corank != ar->codimen && ar->codimen != 0)
4391     {
4392       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4393                  &ar->where, ar->codimen, as->corank);
4394       return FAILURE;
4395     }
4396
4397   for (i = 0; i < as->rank; i++)
4398     if (check_dimension (i, ar, as) == FAILURE)
4399       return FAILURE;
4400
4401   /* Local access has no coarray spec.  */
4402   if (ar->codimen != 0)
4403     for (i = as->rank; i < as->rank + as->corank; i++)
4404       {
4405         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate
4406             && ar->dimen_type[i] != DIMEN_THIS_IMAGE)
4407           {
4408             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4409                        i + 1 - as->rank, &ar->where);
4410             return FAILURE;
4411           }
4412         if (check_dimension (i, ar, as) == FAILURE)
4413           return FAILURE;
4414       }
4415
4416   return SUCCESS;
4417 }
4418
4419
4420 /* Resolve one part of an array index.  */
4421
4422 static gfc_try
4423 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4424                      int force_index_integer_kind)
4425 {
4426   gfc_typespec ts;
4427
4428   if (index == NULL)
4429     return SUCCESS;
4430
4431   if (gfc_resolve_expr (index) == FAILURE)
4432     return FAILURE;
4433
4434   if (check_scalar && index->rank != 0)
4435     {
4436       gfc_error ("Array index at %L must be scalar", &index->where);
4437       return FAILURE;
4438     }
4439
4440   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4441     {
4442       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4443                  &index->where, gfc_basic_typename (index->ts.type));
4444       return FAILURE;
4445     }
4446
4447   if (index->ts.type == BT_REAL)
4448     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4449                         &index->where) == FAILURE)
4450       return FAILURE;
4451
4452   if ((index->ts.kind != gfc_index_integer_kind
4453        && force_index_integer_kind)
4454       || index->ts.type != BT_INTEGER)
4455     {
4456       gfc_clear_ts (&ts);
4457       ts.type = BT_INTEGER;
4458       ts.kind = gfc_index_integer_kind;
4459
4460       gfc_convert_type_warn (index, &ts, 2, 0);
4461     }
4462
4463   return SUCCESS;
4464 }
4465
4466 /* Resolve one part of an array index.  */
4467
4468 gfc_try
4469 gfc_resolve_index (gfc_expr *index, int check_scalar)
4470 {
4471   return gfc_resolve_index_1 (index, check_scalar, 1);
4472 }
4473
4474 /* Resolve a dim argument to an intrinsic function.  */
4475
4476 gfc_try
4477 gfc_resolve_dim_arg (gfc_expr *dim)
4478 {
4479   if (dim == NULL)
4480     return SUCCESS;
4481
4482   if (gfc_resolve_expr (dim) == FAILURE)
4483     return FAILURE;
4484
4485   if (dim->rank != 0)
4486     {
4487       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4488       return FAILURE;
4489
4490     }
4491
4492   if (dim->ts.type != BT_INTEGER)
4493     {
4494       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4495       return FAILURE;
4496     }
4497
4498   if (dim->ts.kind != gfc_index_integer_kind)
4499     {
4500       gfc_typespec ts;
4501
4502       gfc_clear_ts (&ts);
4503       ts.type = BT_INTEGER;
4504       ts.kind = gfc_index_integer_kind;
4505
4506       gfc_convert_type_warn (dim, &ts, 2, 0);
4507     }
4508
4509   return SUCCESS;
4510 }
4511
4512 /* Given an expression that contains array references, update those array
4513    references to point to the right array specifications.  While this is
4514    filled in during matching, this information is difficult to save and load
4515    in a module, so we take care of it here.
4516
4517    The idea here is that the original array reference comes from the
4518    base symbol.  We traverse the list of reference structures, setting
4519    the stored reference to references.  Component references can
4520    provide an additional array specification.  */
4521
4522 static void
4523 find_array_spec (gfc_expr *e)
4524 {
4525   gfc_array_spec *as;
4526   gfc_component *c;
4527   gfc_ref *ref;
4528
4529   if (e->symtree->n.sym->ts.type == BT_CLASS)
4530     as = CLASS_DATA (e->symtree->n.sym)->as;
4531   else
4532     as = e->symtree->n.sym->as;
4533
4534   for (ref = e->ref; ref; ref = ref->next)
4535     switch (ref->type)
4536       {
4537       case REF_ARRAY:
4538         if (as == NULL)
4539           gfc_internal_error ("find_array_spec(): Missing spec");
4540
4541         ref->u.ar.as = as;
4542         as = NULL;
4543         break;
4544
4545       case REF_COMPONENT:
4546         c = ref->u.c.component;
4547         if (c->attr.dimension)
4548           {
4549             if (as != NULL)
4550               gfc_internal_error ("find_array_spec(): unused as(1)");
4551             as = c->as;
4552           }
4553
4554         break;
4555
4556       case REF_SUBSTRING:
4557         break;
4558       }
4559
4560   if (as != NULL)
4561     gfc_internal_error ("find_array_spec(): unused as(2)");
4562 }
4563
4564
4565 /* Resolve an array reference.  */
4566
4567 static gfc_try
4568 resolve_array_ref (gfc_array_ref *ar)
4569 {
4570   int i, check_scalar;
4571   gfc_expr *e;
4572
4573   for (i = 0; i < ar->dimen + ar->codimen; i++)
4574     {
4575       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4576
4577       /* Do not force gfc_index_integer_kind for the start.  We can
4578          do fine with any integer kind.  This avoids temporary arrays
4579          created for indexing with a vector.  */
4580       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4581         return FAILURE;
4582       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4583         return FAILURE;
4584       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4585         return FAILURE;
4586
4587       e = ar->start[i];
4588
4589       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4590         switch (e->rank)
4591           {
4592           case 0:
4593             ar->dimen_type[i] = DIMEN_ELEMENT;
4594             break;
4595
4596           case 1:
4597             ar->dimen_type[i] = DIMEN_VECTOR;
4598             if (e->expr_type == EXPR_VARIABLE
4599                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4600               ar->start[i] = gfc_get_parentheses (e);
4601             break;
4602
4603           default:
4604             gfc_error ("Array index at %L is an array of rank %d",
4605                        &ar->c_where[i], e->rank);
4606             return FAILURE;
4607           }
4608
4609       /* Fill in the upper bound, which may be lower than the
4610          specified one for something like a(2:10:5), which is
4611          identical to a(2:7:5).  Only relevant for strides not equal
4612          to one.  Don't try a division by zero.  */
4613       if (ar->dimen_type[i] == DIMEN_RANGE
4614           && ar->stride[i] != NULL && ar->stride[i]->expr_type == EXPR_CONSTANT
4615           && mpz_cmp_si (ar->stride[i]->value.integer, 1L) != 0
4616           && mpz_cmp_si (ar->stride[i]->value.integer, 0L) != 0)
4617         {
4618           mpz_t size, end;
4619
4620           if (gfc_ref_dimen_size (ar, i, &size, &end) == SUCCESS)
4621             {
4622               if (ar->end[i] == NULL)
4623                 {
4624                   ar->end[i] =
4625                     gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
4626                                            &ar->where);
4627                   mpz_set (ar->end[i]->value.integer, end);
4628                 }
4629               else if (ar->end[i]->ts.type == BT_INTEGER
4630                        && ar->end[i]->expr_type == EXPR_CONSTANT)
4631                 {
4632                   mpz_set (ar->end[i]->value.integer, end);
4633                 }
4634               else
4635                 gcc_unreachable ();
4636
4637               mpz_clear (size);
4638               mpz_clear (end);
4639             }
4640         }
4641     }
4642
4643   if (ar->type == AR_FULL)
4644     {
4645       if (ar->as->rank == 0)
4646         ar->type = AR_ELEMENT;
4647
4648       /* Make sure array is the same as array(:,:), this way
4649          we don't need to special case all the time.  */
4650       ar->dimen = ar->as->rank;
4651       for (i = 0; i < ar->dimen; i++)
4652         {
4653           ar->dimen_type[i] = DIMEN_RANGE;
4654
4655           gcc_assert (ar->start[i] == NULL);
4656           gcc_assert (ar->end[i] == NULL);
4657           gcc_assert (ar->stride[i] == NULL);
4658         }
4659     }
4660
4661   /* If the reference type is unknown, figure out what kind it is.  */
4662
4663   if (ar->type == AR_UNKNOWN)
4664     {
4665       ar->type = AR_ELEMENT;
4666       for (i = 0; i < ar->dimen; i++)
4667         if (ar->dimen_type[i] == DIMEN_RANGE
4668             || ar->dimen_type[i] == DIMEN_VECTOR)
4669           {
4670             ar->type = AR_SECTION;
4671             break;
4672           }
4673     }
4674
4675   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4676     return FAILURE;
4677
4678   if (ar->as->corank && ar->codimen == 0)
4679     {
4680       int n;
4681       ar->codimen = ar->as->corank;
4682       for (n = ar->dimen; n < ar->dimen + ar->codimen; n++)
4683         ar->dimen_type[n] = DIMEN_THIS_IMAGE;
4684     }
4685
4686   return SUCCESS;
4687 }
4688
4689
4690 static gfc_try
4691 resolve_substring (gfc_ref *ref)
4692 {
4693   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4694
4695   if (ref->u.ss.start != NULL)
4696     {
4697       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4698         return FAILURE;
4699
4700       if (ref->u.ss.start->ts.type != BT_INTEGER)
4701         {
4702           gfc_error ("Substring start index at %L must be of type INTEGER",
4703                      &ref->u.ss.start->where);
4704           return FAILURE;
4705         }
4706
4707       if (ref->u.ss.start->rank != 0)
4708         {
4709           gfc_error ("Substring start index at %L must be scalar",
4710                      &ref->u.ss.start->where);
4711           return FAILURE;
4712         }
4713
4714       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4715           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4716               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4717         {
4718           gfc_error ("Substring start index at %L is less than one",
4719                      &ref->u.ss.start->where);
4720           return FAILURE;
4721         }
4722     }
4723
4724   if (ref->u.ss.end != NULL)
4725     {
4726       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4727         return FAILURE;
4728
4729       if (ref->u.ss.end->ts.type != BT_INTEGER)
4730         {
4731           gfc_error ("Substring end index at %L must be of type INTEGER",
4732                      &ref->u.ss.end->where);
4733           return FAILURE;
4734         }
4735
4736       if (ref->u.ss.end->rank != 0)
4737         {
4738           gfc_error ("Substring end index at %L must be scalar",
4739                      &ref->u.ss.end->where);
4740           return FAILURE;
4741         }
4742
4743       if (ref->u.ss.length != NULL
4744           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4745           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4746               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4747         {
4748           gfc_error ("Substring end index at %L exceeds the string length",
4749                      &ref->u.ss.start->where);
4750           return FAILURE;
4751         }
4752
4753       if (compare_bound_mpz_t (ref->u.ss.end,
4754                                gfc_integer_kinds[k].huge) == CMP_GT
4755           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4756               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4757         {
4758           gfc_error ("Substring end index at %L is too large",
4759                      &ref->u.ss.end->where);
4760           return FAILURE;
4761         }
4762     }
4763
4764   return SUCCESS;
4765 }
4766
4767
4768 /* This function supplies missing substring charlens.  */
4769
4770 void
4771 gfc_resolve_substring_charlen (gfc_expr *e)
4772 {
4773   gfc_ref *char_ref;
4774   gfc_expr *start, *end;
4775
4776   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4777     if (char_ref->type == REF_SUBSTRING)
4778       break;
4779
4780   if (!char_ref)
4781     return;
4782
4783   gcc_assert (char_ref->next == NULL);
4784
4785   if (e->ts.u.cl)
4786     {
4787       if (e->ts.u.cl->length)
4788         gfc_free_expr (e->ts.u.cl->length);
4789       else if (e->expr_type == EXPR_VARIABLE
4790                  && e->symtree->n.sym->attr.dummy)
4791         return;
4792     }
4793
4794   e->ts.type = BT_CHARACTER;
4795   e->ts.kind = gfc_default_character_kind;
4796
4797   if (!e->ts.u.cl)
4798     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4799
4800   if (char_ref->u.ss.start)
4801     start = gfc_copy_expr (char_ref->u.ss.start);
4802   else
4803     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4804
4805   if (char_ref->u.ss.end)
4806     end = gfc_copy_expr (char_ref->u.ss.end);
4807   else if (e->expr_type == EXPR_VARIABLE)
4808     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4809   else
4810     end = NULL;
4811
4812   if (!start || !end)
4813     return;
4814
4815   /* Length = (end - start +1).  */
4816   e->ts.u.cl->length = gfc_subtract (end, start);
4817   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4818                                 gfc_get_int_expr (gfc_default_integer_kind,
4819                                                   NULL, 1));
4820
4821   e->ts.u.cl->length->ts.type = BT_INTEGER;
4822   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4823
4824   /* Make sure that the length is simplified.  */
4825   gfc_simplify_expr (e->ts.u.cl->length, 1);
4826   gfc_resolve_expr (e->ts.u.cl->length);
4827 }
4828
4829
4830 /* Resolve subtype references.  */
4831
4832 static gfc_try
4833 resolve_ref (gfc_expr *expr)
4834 {
4835   int current_part_dimension, n_components, seen_part_dimension;
4836   gfc_ref *ref;
4837
4838   for (ref = expr->ref; ref; ref = ref->next)
4839     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4840       {
4841         find_array_spec (expr);
4842         break;
4843       }
4844
4845   for (ref = expr->ref; ref; ref = ref->next)
4846     switch (ref->type)
4847       {
4848       case REF_ARRAY:
4849         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4850           return FAILURE;
4851         break;
4852
4853       case REF_COMPONENT:
4854         break;
4855
4856       case REF_SUBSTRING:
4857         if (resolve_substring (ref) == FAILURE)
4858           return FAILURE;
4859         break;
4860       }
4861
4862   /* Check constraints on part references.  */
4863
4864   current_part_dimension = 0;
4865   seen_part_dimension = 0;
4866   n_components = 0;
4867
4868   for (ref = expr->ref; ref; ref = ref->next)
4869     {
4870       switch (ref->type)
4871         {
4872         case REF_ARRAY:
4873           switch (ref->u.ar.type)
4874             {
4875             case AR_FULL:
4876               /* Coarray scalar.  */
4877               if (ref->u.ar.as->rank == 0)
4878                 {
4879                   current_part_dimension = 0;
4880                   break;
4881                 }
4882               /* Fall through.  */
4883             case AR_SECTION:
4884               current_part_dimension = 1;
4885               break;
4886
4887             case AR_ELEMENT:
4888               current_part_dimension = 0;
4889               break;
4890
4891             case AR_UNKNOWN:
4892               gfc_internal_error ("resolve_ref(): Bad array reference");
4893             }
4894
4895           break;
4896
4897         case REF_COMPONENT:
4898           if (current_part_dimension || seen_part_dimension)
4899             {
4900               /* F03:C614.  */
4901               if (ref->u.c.component->attr.pointer
4902                   || ref->u.c.component->attr.proc_pointer)
4903                 {
4904                   gfc_error ("Component to the right of a part reference "
4905                              "with nonzero rank must not have the POINTER "
4906                              "attribute at %L", &expr->where);
4907                   return FAILURE;
4908                 }
4909               else if (ref->u.c.component->attr.allocatable)
4910                 {
4911                   gfc_error ("Component to the right of a part reference "
4912                              "with nonzero rank must not have the ALLOCATABLE "
4913                              "attribute at %L", &expr->where);
4914                   return FAILURE;
4915                 }
4916             }
4917
4918           n_components++;
4919           break;
4920
4921         case REF_SUBSTRING:
4922           break;
4923         }
4924
4925       if (((ref->type == REF_COMPONENT && n_components > 1)
4926            || ref->next == NULL)
4927           && current_part_dimension
4928           && seen_part_dimension)
4929         {
4930           gfc_error ("Two or more part references with nonzero rank must "
4931                      "not be specified at %L", &expr->where);
4932           return FAILURE;
4933         }
4934
4935       if (ref->type == REF_COMPONENT)
4936         {
4937           if (current_part_dimension)
4938             seen_part_dimension = 1;
4939
4940           /* reset to make sure */
4941           current_part_dimension = 0;
4942         }
4943     }
4944
4945   return SUCCESS;
4946 }
4947
4948
4949 /* Given an expression, determine its shape.  This is easier than it sounds.
4950    Leaves the shape array NULL if it is not possible to determine the shape.  */
4951
4952 static void
4953 expression_shape (gfc_expr *e)
4954 {
4955   mpz_t array[GFC_MAX_DIMENSIONS];
4956   int i;
4957
4958   if (e->rank == 0 || e->shape != NULL)
4959     return;
4960
4961   for (i = 0; i < e->rank; i++)
4962     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4963       goto fail;
4964
4965   e->shape = gfc_get_shape (e->rank);
4966
4967   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4968
4969   return;
4970
4971 fail:
4972   for (i--; i >= 0; i--)
4973     mpz_clear (array[i]);
4974 }
4975
4976
4977 /* Given a variable expression node, compute the rank of the expression by
4978    examining the base symbol and any reference structures it may have.  */
4979
4980 static void
4981 expression_rank (gfc_expr *e)
4982 {
4983   gfc_ref *ref;
4984   int i, rank;
4985
4986   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4987      could lead to serious confusion...  */
4988   gcc_assert (e->expr_type != EXPR_COMPCALL);
4989
4990   if (e->ref == NULL)
4991     {
4992       if (e->expr_type == EXPR_ARRAY)
4993         goto done;
4994       /* Constructors can have a rank different from one via RESHAPE().  */
4995
4996       if (e->symtree == NULL)
4997         {
4998           e->rank = 0;
4999           goto done;
5000         }
5001
5002       e->rank = (e->symtree->n.sym->as == NULL)
5003                 ? 0 : e->symtree->n.sym->as->rank;
5004       goto done;
5005     }
5006
5007   rank = 0;
5008
5009   for (ref = e->ref; ref; ref = ref->next)
5010     {
5011       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.proc_pointer
5012           && ref->u.c.component->attr.function && !ref->next)
5013         rank = ref->u.c.component->as ? ref->u.c.component->as->rank : 0;
5014
5015       if (ref->type != REF_ARRAY)
5016         continue;
5017
5018       if (ref->u.ar.type == AR_FULL)
5019         {
5020           rank = ref->u.ar.as->rank;
5021           break;
5022         }
5023
5024       if (ref->u.ar.type == AR_SECTION)
5025         {
5026           /* Figure out the rank of the section.  */
5027           if (rank != 0)
5028             gfc_internal_error ("expression_rank(): Two array specs");
5029
5030           for (i = 0; i < ref->u.ar.dimen; i++)
5031             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
5032                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
5033               rank++;
5034
5035           break;
5036         }
5037     }
5038
5039   e->rank = rank;
5040
5041 done:
5042   expression_shape (e);
5043 }
5044
5045
5046 /* Resolve a variable expression.  */
5047
5048 static gfc_try
5049 resolve_variable (gfc_expr *e)
5050 {
5051   gfc_symbol *sym;
5052   gfc_try t;
5053
5054   t = SUCCESS;
5055
5056   if (e->symtree == NULL)
5057     return FAILURE;
5058   sym = e->symtree->n.sym;
5059
5060   /* If this is an associate-name, it may be parsed with an array reference
5061      in error even though the target is scalar.  Fail directly in this case.  */
5062   if (sym->assoc && !sym->attr.dimension && e->ref && e->ref->type == REF_ARRAY)
5063     return FAILURE;
5064
5065   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.generic)
5066     sym->ts.u.derived = gfc_find_dt_in_generic (sym->ts.u.derived);
5067
5068   /* On the other hand, the parser may not have known this is an array;
5069      in this case, we have to add a FULL reference.  */
5070   if (sym->assoc && sym->attr.dimension && !e->ref)
5071     {
5072       e->ref = gfc_get_ref ();
5073       e->ref->type = REF_ARRAY;
5074       e->ref->u.ar.type = AR_FULL;
5075       e->ref->u.ar.dimen = 0;
5076     }
5077
5078   if (e->ref && resolve_ref (e) == FAILURE)
5079     return FAILURE;
5080
5081   if (sym->attr.flavor == FL_PROCEDURE
5082       && (!sym->attr.function
5083           || (sym->attr.function && sym->result
5084               && sym->result->attr.proc_pointer
5085               && !sym->result->attr.function)))
5086     {
5087       e->ts.type = BT_PROCEDURE;
5088       goto resolve_procedure;
5089     }
5090
5091   if (sym->ts.type != BT_UNKNOWN)
5092     gfc_variable_attr (e, &e->ts);
5093   else
5094     {
5095       /* Must be a simple variable reference.  */
5096       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
5097         return FAILURE;
5098       e->ts = sym->ts;
5099     }
5100
5101   if (check_assumed_size_reference (sym, e))
5102     return FAILURE;
5103
5104   /* Deal with forward references to entries during resolve_code, to
5105      satisfy, at least partially, 12.5.2.5.  */
5106   if (gfc_current_ns->entries
5107       && current_entry_id == sym->entry_id
5108       && cs_base
5109       && cs_base->current
5110       && cs_base->current->op != EXEC_ENTRY)
5111     {
5112       gfc_entry_list *entry;
5113       gfc_formal_arglist *formal;
5114       int n;
5115       bool seen;
5116
5117       /* If the symbol is a dummy...  */
5118       if (sym->attr.dummy && sym->ns == gfc_current_ns)
5119         {
5120           entry = gfc_current_ns->entries;
5121           seen = false;
5122
5123           /* ...test if the symbol is a parameter of previous entries.  */
5124           for (; entry && entry->id <= current_entry_id; entry = entry->next)
5125             for (formal = entry->sym->formal; formal; formal = formal->next)
5126               {
5127                 if (formal->sym && sym->name == formal->sym->name)
5128                   seen = true;
5129               }
5130
5131           /*  If it has not been seen as a dummy, this is an error.  */
5132           if (!seen)
5133             {
5134               if (specification_expr)
5135                 gfc_error ("Variable '%s', used in a specification expression"
5136                            ", is referenced at %L before the ENTRY statement "
5137                            "in which it is a parameter",
5138                            sym->name, &cs_base->current->loc);
5139               else
5140                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
5141                            "statement in which it is a parameter",
5142                            sym->name, &cs_base->current->loc);
5143               t = FAILURE;
5144             }
5145         }
5146
5147       /* Now do the same check on the specification expressions.  */
5148       specification_expr = 1;
5149       if (sym->ts.type == BT_CHARACTER
5150           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
5151         t = FAILURE;
5152
5153       if (sym->as)
5154         for (n = 0; n < sym->as->rank; n++)
5155           {
5156              specification_expr = 1;
5157              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
5158                t = FAILURE;
5159              specification_expr = 1;
5160              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
5161                t = FAILURE;
5162           }
5163       specification_expr = 0;
5164
5165       if (t == SUCCESS)
5166         /* Update the symbol's entry level.  */
5167         sym->entry_id = current_entry_id + 1;
5168     }
5169
5170   /* If a symbol has been host_associated mark it.  This is used latter,
5171      to identify if aliasing is possible via host association.  */
5172   if (sym->attr.flavor == FL_VARIABLE
5173         && gfc_current_ns->parent
5174         && (gfc_current_ns->parent == sym->ns
5175               || (gfc_current_ns->parent->parent
5176                     && gfc_current_ns->parent->parent == sym->ns)))
5177     sym->attr.host_assoc = 1;
5178
5179 resolve_procedure:
5180   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
5181     t = FAILURE;
5182
5183   /* F2008, C617 and C1229.  */
5184   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5185       && gfc_is_coindexed (e))
5186     {
5187       gfc_ref *ref, *ref2 = NULL;
5188
5189       for (ref = e->ref; ref; ref = ref->next)
5190         {
5191           if (ref->type == REF_COMPONENT)
5192             ref2 = ref;
5193           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5194             break;
5195         }
5196
5197       for ( ; ref; ref = ref->next)
5198         if (ref->type == REF_COMPONENT)
5199           break;
5200
5201       /* Expression itself is not coindexed object.  */
5202       if (ref && e->ts.type == BT_CLASS)
5203         {
5204           gfc_error ("Polymorphic subobject of coindexed object at %L",
5205                      &e->where);
5206           t = FAILURE;
5207         }
5208
5209       /* Expression itself is coindexed object.  */
5210       if (ref == NULL)
5211         {
5212           gfc_component *c;
5213           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5214           for ( ; c; c = c->next)
5215             if (c->attr.allocatable && c->ts.type == BT_CLASS)
5216               {
5217                 gfc_error ("Coindexed object with polymorphic allocatable "
5218                          "subcomponent at %L", &e->where);
5219                 t = FAILURE;
5220                 break;
5221               }
5222         }
5223     }
5224
5225   return t;
5226 }
5227
5228
5229 /* Checks to see that the correct symbol has been host associated.
5230    The only situation where this arises is that in which a twice
5231    contained function is parsed after the host association is made.
5232    Therefore, on detecting this, change the symbol in the expression
5233    and convert the array reference into an actual arglist if the old
5234    symbol is a variable.  */
5235 static bool
5236 check_host_association (gfc_expr *e)
5237 {
5238   gfc_symbol *sym, *old_sym;
5239   gfc_symtree *st;
5240   int n;
5241   gfc_ref *ref;
5242   gfc_actual_arglist *arg, *tail = NULL;
5243   bool retval = e->expr_type == EXPR_FUNCTION;
5244
5245   /*  If the expression is the result of substitution in
5246       interface.c(gfc_extend_expr) because there is no way in
5247       which the host association can be wrong.  */
5248   if (e->symtree == NULL
5249         || e->symtree->n.sym == NULL
5250         || e->user_operator)
5251     return retval;
5252
5253   old_sym = e->symtree->n.sym;
5254
5255   if (gfc_current_ns->parent
5256         && old_sym->ns != gfc_current_ns)
5257     {
5258       /* Use the 'USE' name so that renamed module symbols are
5259          correctly handled.  */
5260       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5261
5262       if (sym && old_sym != sym
5263               && sym->ts.type == old_sym->ts.type
5264               && sym->attr.flavor == FL_PROCEDURE
5265               && sym->attr.contained)
5266         {
5267           /* Clear the shape, since it might not be valid.  */
5268           gfc_free_shape (&e->shape, e->rank);
5269
5270           /* Give the expression the right symtree!  */
5271           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5272           gcc_assert (st != NULL);
5273
5274           if (old_sym->attr.flavor == FL_PROCEDURE
5275                 || e->expr_type == EXPR_FUNCTION)
5276             {
5277               /* Original was function so point to the new symbol, since
5278                  the actual argument list is already attached to the
5279                  expression. */
5280               e->value.function.esym = NULL;
5281               e->symtree = st;
5282             }
5283           else
5284             {
5285               /* Original was variable so convert array references into
5286                  an actual arglist. This does not need any checking now
5287                  since resolve_function will take care of it.  */
5288               e->value.function.actual = NULL;
5289               e->expr_type = EXPR_FUNCTION;
5290               e->symtree = st;
5291
5292               /* Ambiguity will not arise if the array reference is not
5293                  the last reference.  */
5294               for (ref = e->ref; ref; ref = ref->next)
5295                 if (ref->type == REF_ARRAY && ref->next == NULL)
5296                   break;
5297
5298               gcc_assert (ref->type == REF_ARRAY);
5299
5300               /* Grab the start expressions from the array ref and
5301                  copy them into actual arguments.  */
5302               for (n = 0; n < ref->u.ar.dimen; n++)
5303                 {
5304                   arg = gfc_get_actual_arglist ();
5305                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5306                   if (e->value.function.actual == NULL)
5307                     tail = e->value.function.actual = arg;
5308                   else
5309                     {
5310                       tail->next = arg;
5311                       tail = arg;
5312                     }
5313                 }
5314
5315               /* Dump the reference list and set the rank.  */
5316               gfc_free_ref_list (e->ref);
5317               e->ref = NULL;
5318               e->rank = sym->as ? sym->as->rank : 0;
5319             }
5320
5321           gfc_resolve_expr (e);
5322           sym->refs++;
5323         }
5324     }
5325   /* This might have changed!  */
5326   return e->expr_type == EXPR_FUNCTION;
5327 }
5328
5329
5330 static void
5331 gfc_resolve_character_operator (gfc_expr *e)
5332 {
5333   gfc_expr *op1 = e->value.op.op1;
5334   gfc_expr *op2 = e->value.op.op2;
5335   gfc_expr *e1 = NULL;
5336   gfc_expr *e2 = NULL;
5337
5338   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5339
5340   if (op1->ts.u.cl && op1->ts.u.cl->length)
5341     e1 = gfc_copy_expr (op1->ts.u.cl->length);
5342   else if (op1->expr_type == EXPR_CONSTANT)
5343     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5344                            op1->value.character.length);
5345
5346   if (op2->ts.u.cl && op2->ts.u.cl->length)
5347     e2 = gfc_copy_expr (op2->ts.u.cl->length);
5348   else if (op2->expr_type == EXPR_CONSTANT)
5349     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5350                            op2->value.character.length);
5351
5352   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5353
5354   if (!e1 || !e2)
5355     return;
5356
5357   e->ts.u.cl->length = gfc_add (e1, e2);
5358   e->ts.u.cl->length->ts.type = BT_INTEGER;
5359   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5360   gfc_simplify_expr (e->ts.u.cl->length, 0);
5361   gfc_resolve_expr (e->ts.u.cl->length);
5362
5363   return;
5364 }
5365
5366
5367 /*  Ensure that an character expression has a charlen and, if possible, a
5368     length expression.  */
5369
5370 static void
5371 fixup_charlen (gfc_expr *e)
5372 {
5373   /* The cases fall through so that changes in expression type and the need
5374      for multiple fixes are picked up.  In all circumstances, a charlen should
5375      be available for the middle end to hang a backend_decl on.  */
5376   switch (e->expr_type)
5377     {
5378     case EXPR_OP:
5379       gfc_resolve_character_operator (e);
5380
5381     case EXPR_ARRAY:
5382       if (e->expr_type == EXPR_ARRAY)
5383         gfc_resolve_character_array_constructor (e);
5384
5385     case EXPR_SUBSTRING:
5386       if (!e->ts.u.cl && e->ref)
5387         gfc_resolve_substring_charlen (e);
5388
5389     default:
5390       if (!e->ts.u.cl)
5391         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5392
5393       break;
5394     }
5395 }
5396
5397
5398 /* Update an actual argument to include the passed-object for type-bound
5399    procedures at the right position.  */
5400
5401 static gfc_actual_arglist*
5402 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5403                      const char *name)
5404 {
5405   gcc_assert (argpos > 0);
5406
5407   if (argpos == 1)
5408     {
5409       gfc_actual_arglist* result;
5410
5411       result = gfc_get_actual_arglist ();
5412       result->expr = po;
5413       result->next = lst;
5414       if (name)
5415         result->name = name;
5416
5417       return result;
5418     }
5419
5420   if (lst)
5421     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5422   else
5423     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5424   return lst;
5425 }
5426
5427
5428 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5429
5430 static gfc_expr*
5431 extract_compcall_passed_object (gfc_expr* e)
5432 {
5433   gfc_expr* po;
5434
5435   gcc_assert (e->expr_type == EXPR_COMPCALL);
5436
5437   if (e->value.compcall.base_object)
5438     po = gfc_copy_expr (e->value.compcall.base_object);
5439   else
5440     {
5441       po = gfc_get_expr ();
5442       po->expr_type = EXPR_VARIABLE;
5443       po->symtree = e->symtree;
5444       po->ref = gfc_copy_ref (e->ref);
5445       po->where = e->where;
5446     }
5447
5448   if (gfc_resolve_expr (po) == FAILURE)
5449     return NULL;
5450
5451   return po;
5452 }
5453
5454
5455 /* Update the arglist of an EXPR_COMPCALL expression to include the
5456    passed-object.  */
5457
5458 static gfc_try
5459 update_compcall_arglist (gfc_expr* e)
5460 {
5461   gfc_expr* po;
5462   gfc_typebound_proc* tbp;
5463
5464   tbp = e->value.compcall.tbp;
5465
5466   if (tbp->error)
5467     return FAILURE;
5468
5469   po = extract_compcall_passed_object (e);
5470   if (!po)
5471     return FAILURE;
5472
5473   if (tbp->nopass || e->value.compcall.ignore_pass)
5474     {
5475       gfc_free_expr (po);
5476       return SUCCESS;
5477     }
5478
5479   gcc_assert (tbp->pass_arg_num > 0);
5480   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5481                                                   tbp->pass_arg_num,
5482                                                   tbp->pass_arg);
5483
5484   return SUCCESS;
5485 }
5486
5487
5488 /* Extract the passed object from a PPC call (a copy of it).  */
5489
5490 static gfc_expr*
5491 extract_ppc_passed_object (gfc_expr *e)
5492 {
5493   gfc_expr *po;
5494   gfc_ref **ref;
5495
5496   po = gfc_get_expr ();
5497   po->expr_type = EXPR_VARIABLE;
5498   po->symtree = e->symtree;
5499   po->ref = gfc_copy_ref (e->ref);
5500   po->where = e->where;
5501
5502   /* Remove PPC reference.  */
5503   ref = &po->ref;
5504   while ((*ref)->next)
5505     ref = &(*ref)->next;
5506   gfc_free_ref_list (*ref);
5507   *ref = NULL;
5508
5509   if (gfc_resolve_expr (po) == FAILURE)
5510     return NULL;
5511
5512   return po;
5513 }
5514
5515
5516 /* Update the actual arglist of a procedure pointer component to include the
5517    passed-object.  */
5518
5519 static gfc_try
5520 update_ppc_arglist (gfc_expr* e)
5521 {
5522   gfc_expr* po;
5523   gfc_component *ppc;
5524   gfc_typebound_proc* tb;
5525
5526   if (!gfc_is_proc_ptr_comp (e, &ppc))
5527     return FAILURE;
5528
5529   tb = ppc->tb;
5530
5531   if (tb->error)
5532     return FAILURE;
5533   else if (tb->nopass)
5534     return SUCCESS;
5535
5536   po = extract_ppc_passed_object (e);
5537   if (!po)
5538     return FAILURE;
5539
5540   /* F08:R739.  */
5541   if (po->rank > 0)
5542     {
5543       gfc_error ("Passed-object at %L must be scalar", &e->where);
5544       return FAILURE;
5545     }
5546
5547   /* F08:C611.  */
5548   if (po->ts.type == BT_DERIVED && po->ts.u.derived->attr.abstract)
5549     {
5550       gfc_error ("Base object for procedure-pointer component call at %L is of"
5551                  " ABSTRACT type '%s'", &e->where, po->ts.u.derived->name);
5552       return FAILURE;
5553     }
5554
5555   gcc_assert (tb->pass_arg_num > 0);
5556   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5557                                                   tb->pass_arg_num,
5558                                                   tb->pass_arg);
5559
5560   return SUCCESS;
5561 }
5562
5563
5564 /* Check that the object a TBP is called on is valid, i.e. it must not be
5565    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5566
5567 static gfc_try
5568 check_typebound_baseobject (gfc_expr* e)
5569 {
5570   gfc_expr* base;
5571   gfc_try return_value = FAILURE;
5572
5573   base = extract_compcall_passed_object (e);
5574   if (!base)
5575     return FAILURE;
5576
5577   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5578
5579   /* F08:C611.  */
5580   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5581     {
5582       gfc_error ("Base object for type-bound procedure call at %L is of"
5583                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5584       goto cleanup;
5585     }
5586
5587   /* F08:C1230. If the procedure called is NOPASS,
5588      the base object must be scalar.  */
5589   if (e->value.compcall.tbp->nopass && base->rank > 0)
5590     {
5591       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5592                  " be scalar", &e->where);
5593       goto cleanup;
5594     }
5595
5596   return_value = SUCCESS;
5597
5598 cleanup:
5599   gfc_free_expr (base);
5600   return return_value;
5601 }
5602
5603
5604 /* Resolve a call to a type-bound procedure, either function or subroutine,
5605    statically from the data in an EXPR_COMPCALL expression.  The adapted
5606    arglist and the target-procedure symtree are returned.  */
5607
5608 static gfc_try
5609 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5610                           gfc_actual_arglist** actual)
5611 {
5612   gcc_assert (e->expr_type == EXPR_COMPCALL);
5613   gcc_assert (!e->value.compcall.tbp->is_generic);
5614
5615   /* Update the actual arglist for PASS.  */
5616   if (update_compcall_arglist (e) == FAILURE)
5617     return FAILURE;
5618
5619   *actual = e->value.compcall.actual;
5620   *target = e->value.compcall.tbp->u.specific;
5621
5622   gfc_free_ref_list (e->ref);
5623   e->ref = NULL;
5624   e->value.compcall.actual = NULL;
5625
5626   /* If we find a deferred typebound procedure, check for derived types
5627      that an over-riding typebound procedure has not been missed.  */
5628   if (e->value.compcall.tbp->deferred
5629         && e->value.compcall.name
5630         && !e->value.compcall.tbp->non_overridable
5631         && e->value.compcall.base_object
5632         && e->value.compcall.base_object->ts.type == BT_DERIVED)
5633     {
5634       gfc_symtree *st;
5635       gfc_symbol *derived;
5636
5637       /* Use the derived type of the base_object.  */
5638       derived = e->value.compcall.base_object->ts.u.derived;
5639       st = NULL;
5640
5641       /* If necessary, go throught the inheritance chain.  */
5642       while (!st && derived)
5643         {
5644           /* Look for the typebound procedure 'name'.  */
5645           if (derived->f2k_derived && derived->f2k_derived->tb_sym_root)
5646             st = gfc_find_symtree (derived->f2k_derived->tb_sym_root,
5647                                    e->value.compcall.name);
5648           if (!st)
5649             derived = gfc_get_derived_super_type (derived);
5650         }
5651
5652       /* Now find the specific name in the derived type namespace.  */
5653       if (st && st->n.tb && st->n.tb->u.specific)
5654         gfc_find_sym_tree (st->n.tb->u.specific->name,
5655                            derived->ns, 1, &st);
5656       if (st)
5657         *target = st;
5658     }
5659   return SUCCESS;
5660 }
5661
5662
5663 /* Get the ultimate declared type from an expression.  In addition,
5664    return the last class/derived type reference and the copy of the
5665    reference list.  If check_types is set true, derived types are
5666    identified as well as class references.  */
5667 static gfc_symbol*
5668 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5669                         gfc_expr *e, bool check_types)
5670 {
5671   gfc_symbol *declared;
5672   gfc_ref *ref;
5673
5674   declared = NULL;
5675   if (class_ref)
5676     *class_ref = NULL;
5677   if (new_ref)
5678     *new_ref = gfc_copy_ref (e->ref);
5679
5680   for (ref = e->ref; ref; ref = ref->next)
5681     {
5682       if (ref->type != REF_COMPONENT)
5683         continue;
5684
5685       if ((ref->u.c.component->ts.type == BT_CLASS
5686              || (check_types && ref->u.c.component->ts.type == BT_DERIVED))
5687           && ref->u.c.component->attr.flavor != FL_PROCEDURE)
5688         {
5689           declared = ref->u.c.component->ts.u.derived;
5690           if (class_ref)
5691             *class_ref = ref;
5692         }
5693     }
5694
5695   if (declared == NULL)
5696     declared = e->symtree->n.sym->ts.u.derived;
5697
5698   return declared;
5699 }
5700
5701
5702 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5703    which of the specific bindings (if any) matches the arglist and transform
5704    the expression into a call of that binding.  */
5705
5706 static gfc_try
5707 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5708 {
5709   gfc_typebound_proc* genproc;
5710   const char* genname;
5711   gfc_symtree *st;
5712   gfc_symbol *derived;
5713
5714   gcc_assert (e->expr_type == EXPR_COMPCALL);
5715   genname = e->value.compcall.name;
5716   genproc = e->value.compcall.tbp;
5717
5718   if (!genproc->is_generic)
5719     return SUCCESS;
5720
5721   /* Try the bindings on this type and in the inheritance hierarchy.  */
5722   for (; genproc; genproc = genproc->overridden)
5723     {
5724       gfc_tbp_generic* g;
5725
5726       gcc_assert (genproc->is_generic);
5727       for (g = genproc->u.generic; g; g = g->next)
5728         {
5729           gfc_symbol* target;
5730           gfc_actual_arglist* args;
5731           bool matches;
5732
5733           gcc_assert (g->specific);
5734
5735           if (g->specific->error)
5736             continue;
5737
5738           target = g->specific->u.specific->n.sym;
5739
5740           /* Get the right arglist by handling PASS/NOPASS.  */
5741           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5742           if (!g->specific->nopass)
5743             {
5744               gfc_expr* po;
5745               po = extract_compcall_passed_object (e);
5746               if (!po)
5747                 return FAILURE;
5748
5749               gcc_assert (g->specific->pass_arg_num > 0);
5750               gcc_assert (!g->specific->error);
5751               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5752                                           g->specific->pass_arg);
5753             }
5754           resolve_actual_arglist (args, target->attr.proc,
5755                                   is_external_proc (target) && !target->formal);
5756
5757           /* Check if this arglist matches the formal.  */
5758           matches = gfc_arglist_matches_symbol (&args, target);
5759
5760           /* Clean up and break out of the loop if we've found it.  */
5761           gfc_free_actual_arglist (args);
5762           if (matches)
5763             {
5764               e->value.compcall.tbp = g->specific;
5765               genname = g->specific_st->name;
5766               /* Pass along the name for CLASS methods, where the vtab
5767                  procedure pointer component has to be referenced.  */
5768               if (name)
5769                 *name = genname;
5770               goto success;
5771             }
5772         }
5773     }
5774
5775   /* Nothing matching found!  */
5776   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5777              " '%s' at %L", genname, &e->where);
5778   return FAILURE;
5779
5780 success:
5781   /* Make sure that we have the right specific instance for the name.  */
5782   derived = get_declared_from_expr (NULL, NULL, e, true);
5783
5784   st = gfc_find_typebound_proc (derived, NULL, genname, true, &e->where);
5785   if (st)
5786     e->value.compcall.tbp = st->n.tb;
5787
5788   return SUCCESS;
5789 }
5790
5791
5792 /* Resolve a call to a type-bound subroutine.  */
5793
5794 static gfc_try
5795 resolve_typebound_call (gfc_code* c, const char **name)
5796 {
5797   gfc_actual_arglist* newactual;
5798   gfc_symtree* target;
5799
5800   /* Check that's really a SUBROUTINE.  */
5801   if (!c->expr1->value.compcall.tbp->subroutine)
5802     {
5803       gfc_error ("'%s' at %L should be a SUBROUTINE",
5804                  c->expr1->value.compcall.name, &c->loc);
5805       return FAILURE;
5806     }
5807
5808   if (check_typebound_baseobject (c->expr1) == FAILURE)
5809     return FAILURE;
5810
5811   /* Pass along the name for CLASS methods, where the vtab
5812      procedure pointer component has to be referenced.  */
5813   if (name)
5814     *name = c->expr1->value.compcall.name;
5815
5816   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5817     return FAILURE;
5818
5819   /* Transform into an ordinary EXEC_CALL for now.  */
5820
5821   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5822     return FAILURE;
5823
5824   c->ext.actual = newactual;
5825   c->symtree = target;
5826   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5827
5828   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5829
5830   gfc_free_expr (c->expr1);
5831   c->expr1 = gfc_get_expr ();
5832   c->expr1->expr_type = EXPR_FUNCTION;
5833   c->expr1->symtree = target;
5834   c->expr1->where = c->loc;
5835
5836   return resolve_call (c);
5837 }
5838
5839
5840 /* Resolve a component-call expression.  */
5841 static gfc_try
5842 resolve_compcall (gfc_expr* e, const char **name)
5843 {
5844   gfc_actual_arglist* newactual;
5845   gfc_symtree* target;
5846
5847   /* Check that's really a FUNCTION.  */
5848   if (!e->value.compcall.tbp->function)
5849     {
5850       gfc_error ("'%s' at %L should be a FUNCTION",
5851                  e->value.compcall.name, &e->where);
5852       return FAILURE;
5853     }
5854
5855   /* These must not be assign-calls!  */
5856   gcc_assert (!e->value.compcall.assign);
5857
5858   if (check_typebound_baseobject (e) == FAILURE)
5859     return FAILURE;
5860
5861   /* Pass along the name for CLASS methods, where the vtab
5862      procedure pointer component has to be referenced.  */
5863   if (name)
5864     *name = e->value.compcall.name;
5865
5866   if (resolve_typebound_generic_call (e, name) == FAILURE)
5867     return FAILURE;
5868   gcc_assert (!e->value.compcall.tbp->is_generic);
5869
5870   /* Take the rank from the function's symbol.  */
5871   if (e->value.compcall.tbp->u.specific->n.sym->as)
5872     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5873
5874   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5875      arglist to the TBP's binding target.  */
5876
5877   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5878     return FAILURE;
5879
5880   e->value.function.actual = newactual;
5881   e->value.function.name = NULL;
5882   e->value.function.esym = target->n.sym;
5883   e->value.function.isym = NULL;
5884   e->symtree = target;
5885   e->ts = target->n.sym->ts;
5886   e->expr_type = EXPR_FUNCTION;
5887
5888   /* Resolution is not necessary if this is a class subroutine; this
5889      function only has to identify the specific proc. Resolution of
5890      the call will be done next in resolve_typebound_call.  */
5891   return gfc_resolve_expr (e);
5892 }
5893
5894
5895
5896 /* Resolve a typebound function, or 'method'. First separate all
5897    the non-CLASS references by calling resolve_compcall directly.  */
5898
5899 static gfc_try
5900 resolve_typebound_function (gfc_expr* e)
5901 {
5902   gfc_symbol *declared;
5903   gfc_component *c;
5904   gfc_ref *new_ref;
5905   gfc_ref *class_ref;
5906   gfc_symtree *st;
5907   const char *name;
5908   gfc_typespec ts;
5909   gfc_expr *expr;
5910   bool overridable;
5911
5912   st = e->symtree;
5913
5914   /* Deal with typebound operators for CLASS objects.  */
5915   expr = e->value.compcall.base_object;
5916   overridable = !e->value.compcall.tbp->non_overridable;
5917   if (expr && expr->ts.type == BT_CLASS && e->value.compcall.name)
5918     {
5919       /* If the base_object is not a variable, the corresponding actual
5920          argument expression must be stored in e->base_expression so
5921          that the corresponding tree temporary can be used as the base
5922          object in gfc_conv_procedure_call.  */
5923       if (expr->expr_type != EXPR_VARIABLE)
5924         {
5925           gfc_actual_arglist *args;
5926
5927           for (args= e->value.function.actual; args; args = args->next)
5928             {
5929               if (expr == args->expr)
5930                 expr = args->expr;
5931             }
5932         }
5933
5934       /* Since the typebound operators are generic, we have to ensure
5935          that any delays in resolution are corrected and that the vtab
5936          is present.  */
5937       ts = expr->ts;
5938       declared = ts.u.derived;
5939       c = gfc_find_component (declared, "_vptr", true, true);
5940       if (c->ts.u.derived == NULL)
5941         c->ts.u.derived = gfc_find_derived_vtab (declared);
5942
5943       if (resolve_compcall (e, &name) == FAILURE)
5944         return FAILURE;
5945
5946       /* Use the generic name if it is there.  */
5947       name = name ? name : e->value.function.esym->name;
5948       e->symtree = expr->symtree;
5949       e->ref = gfc_copy_ref (expr->ref);
5950       get_declared_from_expr (&class_ref, NULL, e, false);
5951
5952       /* Trim away the extraneous references that emerge from nested
5953          use of interface.c (extend_expr).  */
5954       if (class_ref && class_ref->next)
5955         {
5956           gfc_free_ref_list (class_ref->next);
5957           class_ref->next = NULL;
5958         }
5959       else if (e->ref && !class_ref)
5960         {
5961           gfc_free_ref_list (e->ref);
5962           e->ref = NULL;
5963         }
5964
5965       gfc_add_vptr_component (e);
5966       gfc_add_component_ref (e, name);
5967       e->value.function.esym = NULL;
5968       if (expr->expr_type != EXPR_VARIABLE)
5969         e->base_expr = expr;
5970       return SUCCESS;
5971     }
5972
5973   if (st == NULL)
5974     return resolve_compcall (e, NULL);
5975
5976   if (resolve_ref (e) == FAILURE)
5977     return FAILURE;
5978
5979   /* Get the CLASS declared type.  */
5980   declared = get_declared_from_expr (&class_ref, &new_ref, e, true);
5981
5982   /* Weed out cases of the ultimate component being a derived type.  */
5983   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5984          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5985     {
5986       gfc_free_ref_list (new_ref);
5987       return resolve_compcall (e, NULL);
5988     }
5989
5990   c = gfc_find_component (declared, "_data", true, true);
5991   declared = c->ts.u.derived;
5992
5993   /* Treat the call as if it is a typebound procedure, in order to roll
5994      out the correct name for the specific function.  */
5995   if (resolve_compcall (e, &name) == FAILURE)
5996     return FAILURE;
5997   ts = e->ts;
5998
5999   if (overridable)
6000     {
6001       /* Convert the expression to a procedure pointer component call.  */
6002       e->value.function.esym = NULL;
6003       e->symtree = st;
6004
6005       if (new_ref)  
6006         e->ref = new_ref;
6007
6008       /* '_vptr' points to the vtab, which contains the procedure pointers.  */
6009       gfc_add_vptr_component (e);
6010       gfc_add_component_ref (e, name);
6011
6012       /* Recover the typespec for the expression.  This is really only
6013         necessary for generic procedures, where the additional call
6014         to gfc_add_component_ref seems to throw the collection of the
6015         correct typespec.  */
6016       e->ts = ts;
6017     }
6018
6019   return SUCCESS;
6020 }
6021
6022 /* Resolve a typebound subroutine, or 'method'. First separate all
6023    the non-CLASS references by calling resolve_typebound_call
6024    directly.  */
6025
6026 static gfc_try
6027 resolve_typebound_subroutine (gfc_code *code)
6028 {
6029   gfc_symbol *declared;
6030   gfc_component *c;
6031   gfc_ref *new_ref;
6032   gfc_ref *class_ref;
6033   gfc_symtree *st;
6034   const char *name;
6035   gfc_typespec ts;
6036   gfc_expr *expr;
6037   bool overridable;
6038
6039   st = code->expr1->symtree;
6040
6041   /* Deal with typebound operators for CLASS objects.  */
6042   expr = code->expr1->value.compcall.base_object;
6043   overridable = !code->expr1->value.compcall.tbp->non_overridable;
6044   if (expr && expr->ts.type == BT_CLASS && code->expr1->value.compcall.name)
6045     {
6046       /* If the base_object is not a variable, the corresponding actual
6047          argument expression must be stored in e->base_expression so
6048          that the corresponding tree temporary can be used as the base
6049          object in gfc_conv_procedure_call.  */
6050       if (expr->expr_type != EXPR_VARIABLE)
6051         {
6052           gfc_actual_arglist *args;
6053
6054           args= code->expr1->value.function.actual;
6055           for (; args; args = args->next)
6056             if (expr == args->expr)
6057               expr = args->expr;
6058         }
6059
6060       /* Since the typebound operators are generic, we have to ensure
6061          that any delays in resolution are corrected and that the vtab
6062          is present.  */
6063       declared = expr->ts.u.derived;
6064       c = gfc_find_component (declared, "_vptr", true, true);
6065       if (c->ts.u.derived == NULL)
6066         c->ts.u.derived = gfc_find_derived_vtab (declared);
6067
6068       if (resolve_typebound_call (code, &name) == FAILURE)
6069         return FAILURE;
6070
6071       /* Use the generic name if it is there.  */
6072       name = name ? name : code->expr1->value.function.esym->name;
6073       code->expr1->symtree = expr->symtree;
6074       code->expr1->ref = gfc_copy_ref (expr->ref);
6075
6076       /* Trim away the extraneous references that emerge from nested
6077          use of interface.c (extend_expr).  */
6078       get_declared_from_expr (&class_ref, NULL, code->expr1, false);
6079       if (class_ref && class_ref->next)
6080         {
6081           gfc_free_ref_list (class_ref->next);
6082           class_ref->next = NULL;
6083         }
6084       else if (code->expr1->ref && !class_ref)
6085         {
6086           gfc_free_ref_list (code->expr1->ref);
6087           code->expr1->ref = NULL;
6088         }
6089
6090       /* Now use the procedure in the vtable.  */
6091       gfc_add_vptr_component (code->expr1);
6092       gfc_add_component_ref (code->expr1, name);
6093       code->expr1->value.function.esym = NULL;
6094       if (expr->expr_type != EXPR_VARIABLE)
6095         code->expr1->base_expr = expr;
6096       return SUCCESS;
6097     }
6098
6099   if (st == NULL)
6100     return resolve_typebound_call (code, NULL);
6101
6102   if (resolve_ref (code->expr1) == FAILURE)
6103     return FAILURE;
6104
6105   /* Get the CLASS declared type.  */
6106   get_declared_from_expr (&class_ref, &new_ref, code->expr1, true);
6107
6108   /* Weed out cases of the ultimate component being a derived type.  */
6109   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
6110          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
6111     {
6112       gfc_free_ref_list (new_ref);
6113       return resolve_typebound_call (code, NULL);
6114     }
6115
6116   if (resolve_typebound_call (code, &name) == FAILURE)
6117     return FAILURE;
6118   ts = code->expr1->ts;
6119
6120   if (overridable)
6121     {
6122       /* Convert the expression to a procedure pointer component call.  */
6123       code->expr1->value.function.esym = NULL;
6124       code->expr1->symtree = st;
6125
6126       if (new_ref)
6127         code->expr1->ref = new_ref;
6128
6129       /* '_vptr' points to the vtab, which contains the procedure pointers.  */
6130       gfc_add_vptr_component (code->expr1);
6131       gfc_add_component_ref (code->expr1, name);
6132
6133       /* Recover the typespec for the expression.  This is really only
6134         necessary for generic procedures, where the additional call
6135         to gfc_add_component_ref seems to throw the collection of the
6136         correct typespec.  */
6137       code->expr1->ts = ts;
6138     }
6139
6140   return SUCCESS;
6141 }
6142
6143
6144 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
6145
6146 static gfc_try
6147 resolve_ppc_call (gfc_code* c)
6148 {
6149   gfc_component *comp;
6150   bool b;
6151
6152   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
6153   gcc_assert (b);
6154
6155   c->resolved_sym = c->expr1->symtree->n.sym;
6156   c->expr1->expr_type = EXPR_VARIABLE;
6157
6158   if (!comp->attr.subroutine)
6159     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
6160
6161   if (resolve_ref (c->expr1) == FAILURE)
6162     return FAILURE;
6163
6164   if (update_ppc_arglist (c->expr1) == FAILURE)
6165     return FAILURE;
6166
6167   c->ext.actual = c->expr1->value.compcall.actual;
6168
6169   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
6170                               comp->formal == NULL) == FAILURE)
6171     return FAILURE;
6172
6173   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
6174
6175   return SUCCESS;
6176 }
6177
6178
6179 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
6180
6181 static gfc_try
6182 resolve_expr_ppc (gfc_expr* e)
6183 {
6184   gfc_component *comp;
6185   bool b;
6186
6187   b = gfc_is_proc_ptr_comp (e, &comp);
6188   gcc_assert (b);
6189
6190   /* Convert to EXPR_FUNCTION.  */
6191   e->expr_type = EXPR_FUNCTION;
6192   e->value.function.isym = NULL;
6193   e->value.function.actual = e->value.compcall.actual;
6194   e->ts = comp->ts;
6195   if (comp->as != NULL)
6196     e->rank = comp->as->rank;
6197
6198   if (!comp->attr.function)
6199     gfc_add_function (&comp->attr, comp->name, &e->where);
6200
6201   if (resolve_ref (e) == FAILURE)
6202     return FAILURE;
6203
6204   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
6205                               comp->formal == NULL) == FAILURE)
6206     return FAILURE;
6207
6208   if (update_ppc_arglist (e) == FAILURE)
6209     return FAILURE;
6210
6211   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
6212
6213   return SUCCESS;
6214 }
6215
6216
6217 static bool
6218 gfc_is_expandable_expr (gfc_expr *e)
6219 {
6220   gfc_constructor *con;
6221
6222   if (e->expr_type == EXPR_ARRAY)
6223     {
6224       /* Traverse the constructor looking for variables that are flavor
6225          parameter.  Parameters must be expanded since they are fully used at
6226          compile time.  */
6227       con = gfc_constructor_first (e->value.constructor);
6228       for (; con; con = gfc_constructor_next (con))
6229         {
6230           if (con->expr->expr_type == EXPR_VARIABLE
6231               && con->expr->symtree
6232               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
6233               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
6234             return true;
6235           if (con->expr->expr_type == EXPR_ARRAY
6236               && gfc_is_expandable_expr (con->expr))
6237             return true;
6238         }
6239     }
6240
6241   return false;
6242 }
6243
6244 /* Resolve an expression.  That is, make sure that types of operands agree
6245    with their operators, intrinsic operators are converted to function calls
6246    for overloaded types and unresolved function references are resolved.  */
6247
6248 gfc_try
6249 gfc_resolve_expr (gfc_expr *e)
6250 {
6251   gfc_try t;
6252   bool inquiry_save;
6253
6254   if (e == NULL)
6255     return SUCCESS;
6256
6257   /* inquiry_argument only applies to variables.  */
6258   inquiry_save = inquiry_argument;
6259   if (e->expr_type != EXPR_VARIABLE)
6260     inquiry_argument = false;
6261
6262   switch (e->expr_type)
6263     {
6264     case EXPR_OP:
6265       t = resolve_operator (e);
6266       break;
6267
6268     case EXPR_FUNCTION:
6269     case EXPR_VARIABLE:
6270
6271       if (check_host_association (e))
6272         t = resolve_function (e);
6273       else
6274         {
6275           t = resolve_variable (e);
6276           if (t == SUCCESS)
6277             expression_rank (e);
6278         }
6279
6280       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6281           && e->ref->type != REF_SUBSTRING)
6282         gfc_resolve_substring_charlen (e);
6283
6284       break;
6285
6286     case EXPR_COMPCALL:
6287       t = resolve_typebound_function (e);
6288       break;
6289
6290     case EXPR_SUBSTRING:
6291       t = resolve_ref (e);
6292       break;
6293
6294     case EXPR_CONSTANT:
6295     case EXPR_NULL:
6296       t = SUCCESS;
6297       break;
6298
6299     case EXPR_PPC:
6300       t = resolve_expr_ppc (e);
6301       break;
6302
6303     case EXPR_ARRAY:
6304       t = FAILURE;
6305       if (resolve_ref (e) == FAILURE)
6306         break;
6307
6308       t = gfc_resolve_array_constructor (e);
6309       /* Also try to expand a constructor.  */
6310       if (t == SUCCESS)
6311         {
6312           expression_rank (e);
6313           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6314             gfc_expand_constructor (e, false);
6315         }
6316
6317       /* This provides the opportunity for the length of constructors with
6318          character valued function elements to propagate the string length
6319          to the expression.  */
6320       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
6321         {
6322           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6323              here rather then add a duplicate test for it above.  */ 
6324           gfc_expand_constructor (e, false);
6325           t = gfc_resolve_character_array_constructor (e);
6326         }
6327
6328       break;
6329
6330     case EXPR_STRUCTURE:
6331       t = resolve_ref (e);
6332       if (t == FAILURE)
6333         break;
6334
6335       t = resolve_structure_cons (e, 0);
6336       if (t == FAILURE)
6337         break;
6338
6339       t = gfc_simplify_expr (e, 0);
6340       break;
6341
6342     default:
6343       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6344     }
6345
6346   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
6347     fixup_charlen (e);
6348
6349   inquiry_argument = inquiry_save;
6350
6351   return t;
6352 }
6353
6354
6355 /* Resolve an expression from an iterator.  They must be scalar and have
6356    INTEGER or (optionally) REAL type.  */
6357
6358 static gfc_try
6359 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6360                            const char *name_msgid)
6361 {
6362   if (gfc_resolve_expr (expr) == FAILURE)
6363     return FAILURE;
6364
6365   if (expr->rank != 0)
6366     {
6367       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6368       return FAILURE;
6369     }
6370
6371   if (expr->ts.type != BT_INTEGER)
6372     {
6373       if (expr->ts.type == BT_REAL)
6374         {
6375           if (real_ok)
6376             return gfc_notify_std (GFC_STD_F95_DEL,
6377                                    "Deleted feature: %s at %L must be integer",
6378                                    _(name_msgid), &expr->where);
6379           else
6380             {
6381               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6382                          &expr->where);
6383               return FAILURE;
6384             }
6385         }
6386       else
6387         {
6388           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6389           return FAILURE;
6390         }
6391     }
6392   return SUCCESS;
6393 }
6394
6395
6396 /* Resolve the expressions in an iterator structure.  If REAL_OK is
6397    false allow only INTEGER type iterators, otherwise allow REAL types.  */
6398
6399 gfc_try
6400 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
6401 {
6402   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
6403       == FAILURE)
6404     return FAILURE;
6405
6406   if (gfc_check_vardef_context (iter->var, false, false, _("iterator variable"))
6407       == FAILURE)
6408     return FAILURE;
6409
6410   if (gfc_resolve_iterator_expr (iter->start, real_ok,
6411                                  "Start expression in DO loop") == FAILURE)
6412     return FAILURE;
6413
6414   if (gfc_resolve_iterator_expr (iter->end, real_ok,
6415                                  "End expression in DO loop") == FAILURE)
6416     return FAILURE;
6417
6418   if (gfc_resolve_iterator_expr (iter->step, real_ok,
6419                                  "Step expression in DO loop") == FAILURE)
6420     return FAILURE;
6421
6422   if (iter->step->expr_type == EXPR_CONSTANT)
6423     {
6424       if ((iter->step->ts.type == BT_INTEGER
6425            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6426           || (iter->step->ts.type == BT_REAL
6427               && mpfr_sgn (iter->step->value.real) == 0))
6428         {
6429           gfc_error ("Step expression in DO loop at %L cannot be zero",
6430                      &iter->step->where);
6431           return FAILURE;
6432         }
6433     }
6434
6435   /* Convert start, end, and step to the same type as var.  */
6436   if (iter->start->ts.kind != iter->var->ts.kind
6437       || iter->start->ts.type != iter->var->ts.type)
6438     gfc_convert_type (iter->start, &iter->var->ts, 2);
6439
6440   if (iter->end->ts.kind != iter->var->ts.kind
6441       || iter->end->ts.type != iter->var->ts.type)
6442     gfc_convert_type (iter->end, &iter->var->ts, 2);
6443
6444   if (iter->step->ts.kind != iter->var->ts.kind
6445       || iter->step->ts.type != iter->var->ts.type)
6446     gfc_convert_type (iter->step, &iter->var->ts, 2);
6447
6448   if (iter->start->expr_type == EXPR_CONSTANT
6449       && iter->end->expr_type == EXPR_CONSTANT
6450       && iter->step->expr_type == EXPR_CONSTANT)
6451     {
6452       int sgn, cmp;
6453       if (iter->start->ts.type == BT_INTEGER)
6454         {
6455           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6456           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6457         }
6458       else
6459         {
6460           sgn = mpfr_sgn (iter->step->value.real);
6461           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6462         }
6463       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
6464         gfc_warning ("DO loop at %L will be executed zero times",
6465                      &iter->step->where);
6466     }
6467
6468   return SUCCESS;
6469 }
6470
6471
6472 /* Traversal function for find_forall_index.  f == 2 signals that
6473    that variable itself is not to be checked - only the references.  */
6474
6475 static bool
6476 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6477 {
6478   if (expr->expr_type != EXPR_VARIABLE)
6479     return false;
6480   
6481   /* A scalar assignment  */
6482   if (!expr->ref || *f == 1)
6483     {
6484       if (expr->symtree->n.sym == sym)
6485         return true;
6486       else
6487         return false;
6488     }
6489
6490   if (*f == 2)
6491     *f = 1;
6492   return false;
6493 }
6494
6495
6496 /* Check whether the FORALL index appears in the expression or not.
6497    Returns SUCCESS if SYM is found in EXPR.  */
6498
6499 gfc_try
6500 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6501 {
6502   if (gfc_traverse_expr (expr, sym, forall_index, f))
6503     return SUCCESS;
6504   else
6505     return FAILURE;
6506 }
6507
6508
6509 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6510    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6511    INTEGERs, and if stride is a constant it must be nonzero.
6512    Furthermore "A subscript or stride in a forall-triplet-spec shall
6513    not contain a reference to any index-name in the
6514    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6515
6516 static void
6517 resolve_forall_iterators (gfc_forall_iterator *it)
6518 {
6519   gfc_forall_iterator *iter, *iter2;
6520
6521   for (iter = it; iter; iter = iter->next)
6522     {
6523       if (gfc_resolve_expr (iter->var) == SUCCESS
6524           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6525         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6526                    &iter->var->where);
6527
6528       if (gfc_resolve_expr (iter->start) == SUCCESS
6529           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6530         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6531                    &iter->start->where);
6532       if (iter->var->ts.kind != iter->start->ts.kind)
6533         gfc_convert_type (iter->start, &iter->var->ts, 1);
6534
6535       if (gfc_resolve_expr (iter->end) == SUCCESS
6536           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6537         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6538                    &iter->end->where);
6539       if (iter->var->ts.kind != iter->end->ts.kind)
6540         gfc_convert_type (iter->end, &iter->var->ts, 1);
6541
6542       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6543         {
6544           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6545             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6546                        &iter->stride->where, "INTEGER");
6547
6548           if (iter->stride->expr_type == EXPR_CONSTANT
6549               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6550             gfc_error ("FORALL stride expression at %L cannot be zero",
6551                        &iter->stride->where);
6552         }
6553       if (iter->var->ts.kind != iter->stride->ts.kind)
6554         gfc_convert_type (iter->stride, &iter->var->ts, 1);
6555     }
6556
6557   for (iter = it; iter; iter = iter->next)
6558     for (iter2 = iter; iter2; iter2 = iter2->next)
6559       {
6560         if (find_forall_index (iter2->start,
6561                                iter->var->symtree->n.sym, 0) == SUCCESS
6562             || find_forall_index (iter2->end,
6563                                   iter->var->symtree->n.sym, 0) == SUCCESS
6564             || find_forall_index (iter2->stride,
6565                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6566           gfc_error ("FORALL index '%s' may not appear in triplet "
6567                      "specification at %L", iter->var->symtree->name,
6568                      &iter2->start->where);
6569       }
6570 }
6571
6572
6573 /* Given a pointer to a symbol that is a derived type, see if it's
6574    inaccessible, i.e. if it's defined in another module and the components are
6575    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6576    inaccessible components are found, nonzero otherwise.  */
6577
6578 static int
6579 derived_inaccessible (gfc_symbol *sym)
6580 {
6581   gfc_component *c;
6582
6583   if (sym->attr.use_assoc && sym->attr.private_comp)
6584     return 1;
6585
6586   for (c = sym->components; c; c = c->next)
6587     {
6588         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6589           return 1;
6590     }
6591
6592   return 0;
6593 }
6594
6595
6596 /* Resolve the argument of a deallocate expression.  The expression must be
6597    a pointer or a full array.  */
6598
6599 static gfc_try
6600 resolve_deallocate_expr (gfc_expr *e)
6601 {
6602   symbol_attribute attr;
6603   int allocatable, pointer;
6604   gfc_ref *ref;
6605   gfc_symbol *sym;
6606   gfc_component *c;
6607
6608   if (gfc_resolve_expr (e) == FAILURE)
6609     return FAILURE;
6610
6611   if (e->expr_type != EXPR_VARIABLE)
6612     goto bad;
6613
6614   sym = e->symtree->n.sym;
6615
6616   if (sym->ts.type == BT_CLASS)
6617     {
6618       allocatable = CLASS_DATA (sym)->attr.allocatable;
6619       pointer = CLASS_DATA (sym)->attr.class_pointer;
6620     }
6621   else
6622     {
6623       allocatable = sym->attr.allocatable;
6624       pointer = sym->attr.pointer;
6625     }
6626   for (ref = e->ref; ref; ref = ref->next)
6627     {
6628       switch (ref->type)
6629         {
6630         case REF_ARRAY:
6631           if (ref->u.ar.type != AR_FULL
6632               && !(ref->u.ar.type == AR_ELEMENT && ref->u.ar.as->rank == 0
6633                    && ref->u.ar.codimen && gfc_ref_this_image (ref)))
6634             allocatable = 0;
6635           break;
6636
6637         case REF_COMPONENT:
6638           c = ref->u.c.component;
6639           if (c->ts.type == BT_CLASS)
6640             {
6641               allocatable = CLASS_DATA (c)->attr.allocatable;
6642               pointer = CLASS_DATA (c)->attr.class_pointer;
6643             }
6644           else
6645             {
6646               allocatable = c->attr.allocatable;
6647               pointer = c->attr.pointer;
6648             }
6649           break;
6650
6651         case REF_SUBSTRING:
6652           allocatable = 0;
6653           break;
6654         }
6655     }
6656
6657   attr = gfc_expr_attr (e);
6658
6659   if (allocatable == 0 && attr.pointer == 0)
6660     {
6661     bad:
6662       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6663                  &e->where);
6664       return FAILURE;
6665     }
6666
6667   /* F2008, C644.  */
6668   if (gfc_is_coindexed (e))
6669     {
6670       gfc_error ("Coindexed allocatable object at %L", &e->where);
6671       return FAILURE;
6672     }
6673
6674   if (pointer
6675       && gfc_check_vardef_context (e, true, true, _("DEALLOCATE object"))
6676          == FAILURE)
6677     return FAILURE;
6678   if (gfc_check_vardef_context (e, false, true, _("DEALLOCATE object"))
6679       == FAILURE)
6680     return FAILURE;
6681
6682   return SUCCESS;
6683 }
6684
6685
6686 /* Returns true if the expression e contains a reference to the symbol sym.  */
6687 static bool
6688 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6689 {
6690   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6691     return true;
6692
6693   return false;
6694 }
6695
6696 bool
6697 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6698 {
6699   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6700 }
6701
6702
6703 /* Given the expression node e for an allocatable/pointer of derived type to be
6704    allocated, get the expression node to be initialized afterwards (needed for
6705    derived types with default initializers, and derived types with allocatable
6706    components that need nullification.)  */
6707
6708 gfc_expr *
6709 gfc_expr_to_initialize (gfc_expr *e)
6710 {
6711   gfc_expr *result;
6712   gfc_ref *ref;
6713   int i;
6714
6715   result = gfc_copy_expr (e);
6716
6717   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6718   for (ref = result->ref; ref; ref = ref->next)
6719     if (ref->type == REF_ARRAY && ref->next == NULL)
6720       {
6721         ref->u.ar.type = AR_FULL;
6722
6723         for (i = 0; i < ref->u.ar.dimen; i++)
6724           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6725
6726         break;
6727       }
6728
6729   gfc_free_shape (&result->shape, result->rank);
6730
6731   /* Recalculate rank, shape, etc.  */
6732   gfc_resolve_expr (result);
6733   return result;
6734 }
6735
6736
6737 /* If the last ref of an expression is an array ref, return a copy of the
6738    expression with that one removed.  Otherwise, a copy of the original
6739    expression.  This is used for allocate-expressions and pointer assignment
6740    LHS, where there may be an array specification that needs to be stripped
6741    off when using gfc_check_vardef_context.  */
6742
6743 static gfc_expr*
6744 remove_last_array_ref (gfc_expr* e)
6745 {
6746   gfc_expr* e2;
6747   gfc_ref** r;
6748
6749   e2 = gfc_copy_expr (e);
6750   for (r = &e2->ref; *r; r = &(*r)->next)
6751     if ((*r)->type == REF_ARRAY && !(*r)->next)
6752       {
6753         gfc_free_ref_list (*r);
6754         *r = NULL;
6755         break;
6756       }
6757
6758   return e2;
6759 }
6760
6761
6762 /* Used in resolve_allocate_expr to check that a allocation-object and
6763    a source-expr are conformable.  This does not catch all possible 
6764    cases; in particular a runtime checking is needed.  */
6765
6766 static gfc_try
6767 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6768 {
6769   gfc_ref *tail;
6770   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6771   
6772   /* First compare rank.  */
6773   if (tail && e1->rank != tail->u.ar.as->rank)
6774     {
6775       gfc_error ("Source-expr at %L must be scalar or have the "
6776                  "same rank as the allocate-object at %L",
6777                  &e1->where, &e2->where);
6778       return FAILURE;
6779     }
6780
6781   if (e1->shape)
6782     {
6783       int i;
6784       mpz_t s;
6785
6786       mpz_init (s);
6787
6788       for (i = 0; i < e1->rank; i++)
6789         {
6790           if (tail->u.ar.end[i])
6791             {
6792               mpz_set (s, tail->u.ar.end[i]->value.integer);
6793               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6794               mpz_add_ui (s, s, 1);
6795             }
6796           else
6797             {
6798               mpz_set (s, tail->u.ar.start[i]->value.integer);
6799             }
6800
6801           if (mpz_cmp (e1->shape[i], s) != 0)
6802             {
6803               gfc_error ("Source-expr at %L and allocate-object at %L must "
6804                          "have the same shape", &e1->where, &e2->where);
6805               mpz_clear (s);
6806               return FAILURE;
6807             }
6808         }
6809
6810       mpz_clear (s);
6811     }
6812
6813   return SUCCESS;
6814 }
6815
6816
6817 /* Resolve the expression in an ALLOCATE statement, doing the additional
6818    checks to see whether the expression is OK or not.  The expression must
6819    have a trailing array reference that gives the size of the array.  */
6820
6821 static gfc_try
6822 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6823 {
6824   int i, pointer, allocatable, dimension, is_abstract;
6825   int codimension;
6826   bool coindexed;
6827   symbol_attribute attr;
6828   gfc_ref *ref, *ref2;
6829   gfc_expr *e2;
6830   gfc_array_ref *ar;
6831   gfc_symbol *sym = NULL;
6832   gfc_alloc *a;
6833   gfc_component *c;
6834   gfc_try t;
6835
6836   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6837      checking of coarrays.  */
6838   for (ref = e->ref; ref; ref = ref->next)
6839     if (ref->next == NULL)
6840       break;
6841
6842   if (ref && ref->type == REF_ARRAY)
6843     ref->u.ar.in_allocate = true;
6844
6845   if (gfc_resolve_expr (e) == FAILURE)
6846     goto failure;
6847
6848   /* Make sure the expression is allocatable or a pointer.  If it is
6849      pointer, the next-to-last reference must be a pointer.  */
6850
6851   ref2 = NULL;
6852   if (e->symtree)
6853     sym = e->symtree->n.sym;
6854
6855   /* Check whether ultimate component is abstract and CLASS.  */
6856   is_abstract = 0;
6857
6858   if (e->expr_type != EXPR_VARIABLE)
6859     {
6860       allocatable = 0;
6861       attr = gfc_expr_attr (e);
6862       pointer = attr.pointer;
6863       dimension = attr.dimension;
6864       codimension = attr.codimension;
6865     }
6866   else
6867     {
6868       if (sym->ts.type == BT_CLASS && CLASS_DATA (sym))
6869         {
6870           allocatable = CLASS_DATA (sym)->attr.allocatable;
6871           pointer = CLASS_DATA (sym)->attr.class_pointer;
6872           dimension = CLASS_DATA (sym)->attr.dimension;
6873           codimension = CLASS_DATA (sym)->attr.codimension;
6874           is_abstract = CLASS_DATA (sym)->attr.abstract;
6875         }
6876       else
6877         {
6878           allocatable = sym->attr.allocatable;
6879           pointer = sym->attr.pointer;
6880           dimension = sym->attr.dimension;
6881           codimension = sym->attr.codimension;
6882         }
6883
6884       coindexed = false;
6885
6886       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6887         {
6888           switch (ref->type)
6889             {
6890               case REF_ARRAY:
6891                 if (ref->u.ar.codimen > 0)
6892                   {
6893                     int n;
6894                     for (n = ref->u.ar.dimen;
6895                          n < ref->u.ar.dimen + ref->u.ar.codimen; n++)
6896                       if (ref->u.ar.dimen_type[n] != DIMEN_THIS_IMAGE)
6897                         {
6898                           coindexed = true;
6899                           break;
6900                         }
6901                    }
6902
6903                 if (ref->next != NULL)
6904                   pointer = 0;
6905                 break;
6906
6907               case REF_COMPONENT:
6908                 /* F2008, C644.  */
6909                 if (coindexed)
6910                   {
6911                     gfc_error ("Coindexed allocatable object at %L",
6912                                &e->where);
6913                     goto failure;
6914                   }
6915
6916                 c = ref->u.c.component;
6917                 if (c->ts.type == BT_CLASS)
6918                   {
6919                     allocatable = CLASS_DATA (c)->attr.allocatable;
6920                     pointer = CLASS_DATA (c)->attr.class_pointer;
6921                     dimension = CLASS_DATA (c)->attr.dimension;
6922                     codimension = CLASS_DATA (c)->attr.codimension;
6923                     is_abstract = CLASS_DATA (c)->attr.abstract;
6924                   }
6925                 else
6926                   {
6927                     allocatable = c->attr.allocatable;
6928                     pointer = c->attr.pointer;
6929                     dimension = c->attr.dimension;
6930                     codimension = c->attr.codimension;
6931                     is_abstract = c->attr.abstract;
6932                   }
6933                 break;
6934
6935               case REF_SUBSTRING:
6936                 allocatable = 0;
6937                 pointer = 0;
6938                 break;
6939             }
6940         }
6941     }
6942
6943   if (allocatable == 0 && pointer == 0)
6944     {
6945       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6946                  &e->where);
6947       goto failure;
6948     }
6949
6950   /* Some checks for the SOURCE tag.  */
6951   if (code->expr3)
6952     {
6953       /* Check F03:C631.  */
6954       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6955         {
6956           gfc_error ("Type of entity at %L is type incompatible with "
6957                       "source-expr at %L", &e->where, &code->expr3->where);
6958           goto failure;
6959         }
6960
6961       /* Check F03:C632 and restriction following Note 6.18.  */
6962       if (code->expr3->rank > 0
6963           && conformable_arrays (code->expr3, e) == FAILURE)
6964         goto failure;
6965
6966       /* Check F03:C633.  */
6967       if (code->expr3->ts.kind != e->ts.kind)
6968         {
6969           gfc_error ("The allocate-object at %L and the source-expr at %L "
6970                       "shall have the same kind type parameter",
6971                       &e->where, &code->expr3->where);
6972           goto failure;
6973         }
6974
6975       /* Check F2008, C642.  */
6976       if (code->expr3->ts.type == BT_DERIVED
6977           && ((codimension && gfc_expr_attr (code->expr3).lock_comp)
6978               || (code->expr3->ts.u.derived->from_intmod
6979                      == INTMOD_ISO_FORTRAN_ENV
6980                   && code->expr3->ts.u.derived->intmod_sym_id
6981                      == ISOFORTRAN_LOCK_TYPE)))
6982         {
6983           gfc_error ("The source-expr at %L shall neither be of type "
6984                      "LOCK_TYPE nor have a LOCK_TYPE component if "
6985                       "allocate-object at %L is a coarray",
6986                       &code->expr3->where, &e->where);
6987           goto failure;
6988         }
6989     }
6990
6991   /* Check F08:C629.  */
6992   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
6993       && !code->expr3)
6994     {
6995       gcc_assert (e->ts.type == BT_CLASS);
6996       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6997                  "type-spec or source-expr", sym->name, &e->where);
6998       goto failure;
6999     }
7000
7001   if (code->ext.alloc.ts.type == BT_CHARACTER && !e->ts.deferred)
7002     {
7003       int cmp = gfc_dep_compare_expr (e->ts.u.cl->length,
7004                                       code->ext.alloc.ts.u.cl->length);
7005       if (cmp == 1 || cmp == -1 || cmp == -3)
7006         {
7007           gfc_error ("Allocating %s at %L with type-spec requires the same "
7008                      "character-length parameter as in the declaration",
7009                      sym->name, &e->where);
7010           goto failure;
7011         }
7012     }
7013
7014   /* In the variable definition context checks, gfc_expr_attr is used
7015      on the expression.  This is fooled by the array specification
7016      present in e, thus we have to eliminate that one temporarily.  */
7017   e2 = remove_last_array_ref (e);
7018   t = SUCCESS;
7019   if (t == SUCCESS && pointer)
7020     t = gfc_check_vardef_context (e2, true, true, _("ALLOCATE object"));
7021   if (t == SUCCESS)
7022     t = gfc_check_vardef_context (e2, false, true, _("ALLOCATE object"));
7023   gfc_free_expr (e2);
7024   if (t == FAILURE)
7025     goto failure;
7026
7027   if (e->ts.type == BT_CLASS && CLASS_DATA (e)->attr.dimension
7028         && !code->expr3 && code->ext.alloc.ts.type == BT_DERIVED)
7029     {
7030       /* For class arrays, the initialization with SOURCE is done
7031          using _copy and trans_call. It is convenient to exploit that
7032          when the allocated type is different from the declared type but
7033          no SOURCE exists by setting expr3.  */
7034       code->expr3 = gfc_default_initializer (&code->ext.alloc.ts); 
7035     }
7036   else if (!code->expr3)
7037     {
7038       /* Set up default initializer if needed.  */
7039       gfc_typespec ts;
7040       gfc_expr *init_e;
7041
7042       if (code->ext.alloc.ts.type == BT_DERIVED)
7043         ts = code->ext.alloc.ts;
7044       else
7045         ts = e->ts;
7046
7047       if (ts.type == BT_CLASS)
7048         ts = ts.u.derived->components->ts;
7049
7050       if (ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&ts)))
7051         {
7052           gfc_code *init_st = gfc_get_code ();
7053           init_st->loc = code->loc;
7054           init_st->op = EXEC_INIT_ASSIGN;
7055           init_st->expr1 = gfc_expr_to_initialize (e);
7056           init_st->expr2 = init_e;
7057           init_st->next = code->next;
7058           code->next = init_st;
7059         }
7060     }
7061   else if (code->expr3->mold && code->expr3->ts.type == BT_DERIVED)
7062     {
7063       /* Default initialization via MOLD (non-polymorphic).  */
7064       gfc_expr *rhs = gfc_default_initializer (&code->expr3->ts);
7065       gfc_resolve_expr (rhs);
7066       gfc_free_expr (code->expr3);
7067       code->expr3 = rhs;
7068     }
7069
7070   if (e->ts.type == BT_CLASS)
7071     {
7072       /* Make sure the vtab symbol is present when
7073          the module variables are generated.  */
7074       gfc_typespec ts = e->ts;
7075       if (code->expr3)
7076         ts = code->expr3->ts;
7077       else if (code->ext.alloc.ts.type == BT_DERIVED)
7078         ts = code->ext.alloc.ts;
7079       gfc_find_derived_vtab (ts.u.derived);
7080       if (dimension)
7081         e = gfc_expr_to_initialize (e);
7082     }
7083
7084   if (dimension == 0 && codimension == 0)
7085     goto success;
7086
7087   /* Make sure the last reference node is an array specifiction.  */
7088
7089   if (!ref2 || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
7090       || (dimension && ref2->u.ar.dimen == 0))
7091     {
7092       gfc_error ("Array specification required in ALLOCATE statement "
7093                  "at %L", &e->where);
7094       goto failure;
7095     }
7096
7097   /* Make sure that the array section reference makes sense in the
7098     context of an ALLOCATE specification.  */
7099
7100   ar = &ref2->u.ar;
7101
7102   if (codimension)
7103     for (i = ar->dimen; i < ar->dimen + ar->codimen; i++)
7104       if (ar->dimen_type[i] == DIMEN_THIS_IMAGE)
7105         {
7106           gfc_error ("Coarray specification required in ALLOCATE statement "
7107                      "at %L", &e->where);
7108           goto failure;
7109         }
7110
7111   for (i = 0; i < ar->dimen; i++)
7112     {
7113       if (ref2->u.ar.type == AR_ELEMENT)
7114         goto check_symbols;
7115
7116       switch (ar->dimen_type[i])
7117         {
7118         case DIMEN_ELEMENT:
7119           break;
7120
7121         case DIMEN_RANGE:
7122           if (ar->start[i] != NULL
7123               && ar->end[i] != NULL
7124               && ar->stride[i] == NULL)
7125             break;
7126
7127           /* Fall Through...  */
7128
7129         case DIMEN_UNKNOWN:
7130         case DIMEN_VECTOR:
7131         case DIMEN_STAR:
7132         case DIMEN_THIS_IMAGE:
7133           gfc_error ("Bad array specification in ALLOCATE statement at %L",
7134                      &e->where);
7135           goto failure;
7136         }
7137
7138 check_symbols:
7139       for (a = code->ext.alloc.list; a; a = a->next)
7140         {
7141           sym = a->expr->symtree->n.sym;
7142
7143           /* TODO - check derived type components.  */
7144           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
7145             continue;
7146
7147           if ((ar->start[i] != NULL
7148                && gfc_find_sym_in_expr (sym, ar->start[i]))
7149               || (ar->end[i] != NULL
7150                   && gfc_find_sym_in_expr (sym, ar->end[i])))
7151             {
7152               gfc_error ("'%s' must not appear in the array specification at "
7153                          "%L in the same ALLOCATE statement where it is "
7154                          "itself allocated", sym->name, &ar->where);
7155               goto failure;
7156             }
7157         }
7158     }
7159
7160   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
7161     {
7162       if (ar->dimen_type[i] == DIMEN_ELEMENT
7163           || ar->dimen_type[i] == DIMEN_RANGE)
7164         {
7165           if (i == (ar->dimen + ar->codimen - 1))
7166             {
7167               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
7168                          "statement at %L", &e->where);
7169               goto failure;
7170             }
7171           break;
7172         }
7173
7174       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
7175           && ar->stride[i] == NULL)
7176         break;
7177
7178       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
7179                  &e->where);
7180       goto failure;
7181     }
7182
7183 success:
7184   return SUCCESS;
7185
7186 failure:
7187   return FAILURE;
7188 }
7189
7190 static void
7191 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
7192 {
7193   gfc_expr *stat, *errmsg, *pe, *qe;
7194   gfc_alloc *a, *p, *q;
7195
7196   stat = code->expr1;
7197   errmsg = code->expr2;
7198
7199   /* Check the stat variable.  */
7200   if (stat)
7201     {
7202       gfc_check_vardef_context (stat, false, false, _("STAT variable"));
7203
7204       if ((stat->ts.type != BT_INTEGER
7205            && !(stat->ref && (stat->ref->type == REF_ARRAY
7206                               || stat->ref->type == REF_COMPONENT)))
7207           || stat->rank > 0)
7208         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
7209                    "variable", &stat->where);
7210
7211       for (p = code->ext.alloc.list; p; p = p->next)
7212         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
7213           {
7214             gfc_ref *ref1, *ref2;
7215             bool found = true;
7216
7217             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
7218                  ref1 = ref1->next, ref2 = ref2->next)
7219               {
7220                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7221                   continue;
7222                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7223                   {
7224                     found = false;
7225                     break;
7226                   }
7227               }
7228
7229             if (found)
7230               {
7231                 gfc_error ("Stat-variable at %L shall not be %sd within "
7232                            "the same %s statement", &stat->where, fcn, fcn);
7233                 break;
7234               }
7235           }
7236     }
7237
7238   /* Check the errmsg variable.  */
7239   if (errmsg)
7240     {
7241       if (!stat)
7242         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
7243                      &errmsg->where);
7244
7245       gfc_check_vardef_context (errmsg, false, false, _("ERRMSG variable"));
7246
7247       if ((errmsg->ts.type != BT_CHARACTER
7248            && !(errmsg->ref
7249                 && (errmsg->ref->type == REF_ARRAY
7250                     || errmsg->ref->type == REF_COMPONENT)))
7251           || errmsg->rank > 0 )
7252         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
7253                    "variable", &errmsg->where);
7254
7255       for (p = code->ext.alloc.list; p; p = p->next)
7256         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
7257           {
7258             gfc_ref *ref1, *ref2;
7259             bool found = true;
7260
7261             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
7262                  ref1 = ref1->next, ref2 = ref2->next)
7263               {
7264                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7265                   continue;
7266                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7267                   {
7268                     found = false;
7269                     break;
7270                   }
7271               }
7272
7273             if (found)
7274               {
7275                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
7276                            "the same %s statement", &errmsg->where, fcn, fcn);
7277                 break;
7278               }
7279           }
7280     }
7281
7282   /* Check that an allocate-object appears only once in the statement.  
7283      FIXME: Checking derived types is disabled.  */
7284   for (p = code->ext.alloc.list; p; p = p->next)
7285     {
7286       pe = p->expr;
7287       for (q = p->next; q; q = q->next)
7288         {
7289           qe = q->expr;
7290           if (pe->symtree->n.sym->name == qe->symtree->n.sym->name)
7291             {
7292               /* This is a potential collision.  */
7293               gfc_ref *pr = pe->ref;
7294               gfc_ref *qr = qe->ref;
7295               
7296               /* Follow the references  until
7297                  a) They start to differ, in which case there is no error;
7298                  you can deallocate a%b and a%c in a single statement
7299                  b) Both of them stop, which is an error
7300                  c) One of them stops, which is also an error.  */
7301               while (1)
7302                 {
7303                   if (pr == NULL && qr == NULL)
7304                     {
7305                       gfc_error ("Allocate-object at %L also appears at %L",
7306                                  &pe->where, &qe->where);
7307                       break;
7308                     }
7309                   else if (pr != NULL && qr == NULL)
7310                     {
7311                       gfc_error ("Allocate-object at %L is subobject of"
7312                                  " object at %L", &pe->where, &qe->where);
7313                       break;
7314                     }
7315                   else if (pr == NULL && qr != NULL)
7316                     {
7317                       gfc_error ("Allocate-object at %L is subobject of"
7318                                  " object at %L", &qe->where, &pe->where);
7319                       break;
7320                     }
7321                   /* Here, pr != NULL && qr != NULL  */
7322                   gcc_assert(pr->type == qr->type);
7323                   if (pr->type == REF_ARRAY)
7324                     {
7325                       /* Handle cases like allocate(v(3)%x(3), v(2)%x(3)),
7326                          which are legal.  */
7327                       gcc_assert (qr->type == REF_ARRAY);
7328
7329                       if (pr->next && qr->next)
7330                         {
7331                           gfc_array_ref *par = &(pr->u.ar);
7332                           gfc_array_ref *qar = &(qr->u.ar);
7333                           if (gfc_dep_compare_expr (par->start[0],
7334                                                     qar->start[0]) != 0)
7335                               break;
7336                         }
7337                     }
7338                   else
7339                     {
7340                       if (pr->u.c.component->name != qr->u.c.component->name)
7341                         break;
7342                     }
7343                   
7344                   pr = pr->next;
7345                   qr = qr->next;
7346                 }
7347             }
7348         }
7349     }
7350
7351   if (strcmp (fcn, "ALLOCATE") == 0)
7352     {
7353       for (a = code->ext.alloc.list; a; a = a->next)
7354         resolve_allocate_expr (a->expr, code);
7355     }
7356   else
7357     {
7358       for (a = code->ext.alloc.list; a; a = a->next)
7359         resolve_deallocate_expr (a->expr);
7360     }
7361 }
7362
7363
7364 /************ SELECT CASE resolution subroutines ************/
7365
7366 /* Callback function for our mergesort variant.  Determines interval
7367    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7368    op1 > op2.  Assumes we're not dealing with the default case.  
7369    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7370    There are nine situations to check.  */
7371
7372 static int
7373 compare_cases (const gfc_case *op1, const gfc_case *op2)
7374 {
7375   int retval;
7376
7377   if (op1->low == NULL) /* op1 = (:L)  */
7378     {
7379       /* op2 = (:N), so overlap.  */
7380       retval = 0;
7381       /* op2 = (M:) or (M:N),  L < M  */
7382       if (op2->low != NULL
7383           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7384         retval = -1;
7385     }
7386   else if (op1->high == NULL) /* op1 = (K:)  */
7387     {
7388       /* op2 = (M:), so overlap.  */
7389       retval = 0;
7390       /* op2 = (:N) or (M:N), K > N  */
7391       if (op2->high != NULL
7392           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7393         retval = 1;
7394     }
7395   else /* op1 = (K:L)  */
7396     {
7397       if (op2->low == NULL)       /* op2 = (:N), K > N  */
7398         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7399                  ? 1 : 0;
7400       else if (op2->high == NULL) /* op2 = (M:), L < M  */
7401         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7402                  ? -1 : 0;
7403       else                      /* op2 = (M:N)  */
7404         {
7405           retval =  0;
7406           /* L < M  */
7407           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7408             retval =  -1;
7409           /* K > N  */
7410           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7411             retval =  1;
7412         }
7413     }
7414
7415   return retval;
7416 }
7417
7418
7419 /* Merge-sort a double linked case list, detecting overlap in the
7420    process.  LIST is the head of the double linked case list before it
7421    is sorted.  Returns the head of the sorted list if we don't see any
7422    overlap, or NULL otherwise.  */
7423
7424 static gfc_case *
7425 check_case_overlap (gfc_case *list)
7426 {
7427   gfc_case *p, *q, *e, *tail;
7428   int insize, nmerges, psize, qsize, cmp, overlap_seen;
7429
7430   /* If the passed list was empty, return immediately.  */
7431   if (!list)
7432     return NULL;
7433
7434   overlap_seen = 0;
7435   insize = 1;
7436
7437   /* Loop unconditionally.  The only exit from this loop is a return
7438      statement, when we've finished sorting the case list.  */
7439   for (;;)
7440     {
7441       p = list;
7442       list = NULL;
7443       tail = NULL;
7444
7445       /* Count the number of merges we do in this pass.  */
7446       nmerges = 0;
7447
7448       /* Loop while there exists a merge to be done.  */
7449       while (p)
7450         {
7451           int i;
7452
7453           /* Count this merge.  */
7454           nmerges++;
7455
7456           /* Cut the list in two pieces by stepping INSIZE places
7457              forward in the list, starting from P.  */
7458           psize = 0;
7459           q = p;
7460           for (i = 0; i < insize; i++)
7461             {
7462               psize++;
7463               q = q->right;
7464               if (!q)
7465                 break;
7466             }
7467           qsize = insize;
7468
7469           /* Now we have two lists.  Merge them!  */
7470           while (psize > 0 || (qsize > 0 && q != NULL))
7471             {
7472               /* See from which the next case to merge comes from.  */
7473               if (psize == 0)
7474                 {
7475                   /* P is empty so the next case must come from Q.  */
7476                   e = q;
7477                   q = q->right;
7478                   qsize--;
7479                 }
7480               else if (qsize == 0 || q == NULL)
7481                 {
7482                   /* Q is empty.  */
7483                   e = p;
7484                   p = p->right;
7485                   psize--;
7486                 }
7487               else
7488                 {
7489                   cmp = compare_cases (p, q);
7490                   if (cmp < 0)
7491                     {
7492                       /* The whole case range for P is less than the
7493                          one for Q.  */
7494                       e = p;
7495                       p = p->right;
7496                       psize--;
7497                     }
7498                   else if (cmp > 0)
7499                     {
7500                       /* The whole case range for Q is greater than
7501                          the case range for P.  */
7502                       e = q;
7503                       q = q->right;
7504                       qsize--;
7505                     }
7506                   else
7507                     {
7508                       /* The cases overlap, or they are the same
7509                          element in the list.  Either way, we must
7510                          issue an error and get the next case from P.  */
7511                       /* FIXME: Sort P and Q by line number.  */
7512                       gfc_error ("CASE label at %L overlaps with CASE "
7513                                  "label at %L", &p->where, &q->where);
7514                       overlap_seen = 1;
7515                       e = p;
7516                       p = p->right;
7517                       psize--;
7518                     }
7519                 }
7520
7521                 /* Add the next element to the merged list.  */
7522               if (tail)
7523                 tail->right = e;
7524               else
7525                 list = e;
7526               e->left = tail;
7527               tail = e;
7528             }
7529
7530           /* P has now stepped INSIZE places along, and so has Q.  So
7531              they're the same.  */
7532           p = q;
7533         }
7534       tail->right = NULL;
7535
7536       /* If we have done only one merge or none at all, we've
7537          finished sorting the cases.  */
7538       if (nmerges <= 1)
7539         {
7540           if (!overlap_seen)
7541             return list;
7542           else
7543             return NULL;
7544         }
7545
7546       /* Otherwise repeat, merging lists twice the size.  */
7547       insize *= 2;
7548     }
7549 }
7550
7551
7552 /* Check to see if an expression is suitable for use in a CASE statement.
7553    Makes sure that all case expressions are scalar constants of the same
7554    type.  Return FAILURE if anything is wrong.  */
7555
7556 static gfc_try
7557 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7558 {
7559   if (e == NULL) return SUCCESS;
7560
7561   if (e->ts.type != case_expr->ts.type)
7562     {
7563       gfc_error ("Expression in CASE statement at %L must be of type %s",
7564                  &e->where, gfc_basic_typename (case_expr->ts.type));
7565       return FAILURE;
7566     }
7567
7568   /* C805 (R808) For a given case-construct, each case-value shall be of
7569      the same type as case-expr.  For character type, length differences
7570      are allowed, but the kind type parameters shall be the same.  */
7571
7572   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7573     {
7574       gfc_error ("Expression in CASE statement at %L must be of kind %d",
7575                  &e->where, case_expr->ts.kind);
7576       return FAILURE;
7577     }
7578
7579   /* Convert the case value kind to that of case expression kind,
7580      if needed */
7581
7582   if (e->ts.kind != case_expr->ts.kind)
7583     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7584
7585   if (e->rank != 0)
7586     {
7587       gfc_error ("Expression in CASE statement at %L must be scalar",
7588                  &e->where);
7589       return FAILURE;
7590     }
7591
7592   return SUCCESS;
7593 }
7594
7595
7596 /* Given a completely parsed select statement, we:
7597
7598      - Validate all expressions and code within the SELECT.
7599      - Make sure that the selection expression is not of the wrong type.
7600      - Make sure that no case ranges overlap.
7601      - Eliminate unreachable cases and unreachable code resulting from
7602        removing case labels.
7603
7604    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7605    they are a hassle for code generation, and to prevent that, we just
7606    cut them out here.  This is not necessary for overlapping cases
7607    because they are illegal and we never even try to generate code.
7608
7609    We have the additional caveat that a SELECT construct could have
7610    been a computed GOTO in the source code. Fortunately we can fairly
7611    easily work around that here: The case_expr for a "real" SELECT CASE
7612    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7613    we have to do is make sure that the case_expr is a scalar integer
7614    expression.  */
7615
7616 static void
7617 resolve_select (gfc_code *code)
7618 {
7619   gfc_code *body;
7620   gfc_expr *case_expr;
7621   gfc_case *cp, *default_case, *tail, *head;
7622   int seen_unreachable;
7623   int seen_logical;
7624   int ncases;
7625   bt type;
7626   gfc_try t;
7627
7628   if (code->expr1 == NULL)
7629     {
7630       /* This was actually a computed GOTO statement.  */
7631       case_expr = code->expr2;
7632       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7633         gfc_error ("Selection expression in computed GOTO statement "
7634                    "at %L must be a scalar integer expression",
7635                    &case_expr->where);
7636
7637       /* Further checking is not necessary because this SELECT was built
7638          by the compiler, so it should always be OK.  Just move the
7639          case_expr from expr2 to expr so that we can handle computed
7640          GOTOs as normal SELECTs from here on.  */
7641       code->expr1 = code->expr2;
7642       code->expr2 = NULL;
7643       return;
7644     }
7645
7646   case_expr = code->expr1;
7647
7648   type = case_expr->ts.type;
7649   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7650     {
7651       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7652                  &case_expr->where, gfc_typename (&case_expr->ts));
7653
7654       /* Punt. Going on here just produce more garbage error messages.  */
7655       return;
7656     }
7657
7658   /* Raise a warning if an INTEGER case value exceeds the range of
7659      the case-expr. Later, all expressions will be promoted to the
7660      largest kind of all case-labels.  */
7661
7662   if (type == BT_INTEGER)
7663     for (body = code->block; body; body = body->block)
7664       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7665         {
7666           if (cp->low
7667               && gfc_check_integer_range (cp->low->value.integer,
7668                                           case_expr->ts.kind) != ARITH_OK)
7669             gfc_warning ("Expression in CASE statement at %L is "
7670                          "not in the range of %s", &cp->low->where,
7671                          gfc_typename (&case_expr->ts));
7672
7673           if (cp->high
7674               && cp->low != cp->high
7675               && gfc_check_integer_range (cp->high->value.integer,
7676                                           case_expr->ts.kind) != ARITH_OK)
7677             gfc_warning ("Expression in CASE statement at %L is "
7678                          "not in the range of %s", &cp->high->where,
7679                          gfc_typename (&case_expr->ts));
7680         }
7681
7682   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7683      of the SELECT CASE expression and its CASE values.  Walk the lists
7684      of case values, and if we find a mismatch, promote case_expr to
7685      the appropriate kind.  */
7686
7687   if (type == BT_LOGICAL || type == BT_INTEGER)
7688     {
7689       for (body = code->block; body; body = body->block)
7690         {
7691           /* Walk the case label list.  */
7692           for (cp = body->ext.block.case_list; cp; cp = cp->next)
7693             {
7694               /* Intercept the DEFAULT case.  It does not have a kind.  */
7695               if (cp->low == NULL && cp->high == NULL)
7696                 continue;
7697
7698               /* Unreachable case ranges are discarded, so ignore.  */
7699               if (cp->low != NULL && cp->high != NULL
7700                   && cp->low != cp->high
7701                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7702                 continue;
7703
7704               if (cp->low != NULL
7705                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7706                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7707
7708               if (cp->high != NULL
7709                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7710                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7711             }
7712          }
7713     }
7714
7715   /* Assume there is no DEFAULT case.  */
7716   default_case = NULL;
7717   head = tail = NULL;
7718   ncases = 0;
7719   seen_logical = 0;
7720
7721   for (body = code->block; body; body = body->block)
7722     {
7723       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7724       t = SUCCESS;
7725       seen_unreachable = 0;
7726
7727       /* Walk the case label list, making sure that all case labels
7728          are legal.  */
7729       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7730         {
7731           /* Count the number of cases in the whole construct.  */
7732           ncases++;
7733
7734           /* Intercept the DEFAULT case.  */
7735           if (cp->low == NULL && cp->high == NULL)
7736             {
7737               if (default_case != NULL)
7738                 {
7739                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7740                              "by a second DEFAULT CASE at %L",
7741                              &default_case->where, &cp->where);
7742                   t = FAILURE;
7743                   break;
7744                 }
7745               else
7746                 {
7747                   default_case = cp;
7748                   continue;
7749                 }
7750             }
7751
7752           /* Deal with single value cases and case ranges.  Errors are
7753              issued from the validation function.  */
7754           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7755               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7756             {
7757               t = FAILURE;
7758               break;
7759             }
7760
7761           if (type == BT_LOGICAL
7762               && ((cp->low == NULL || cp->high == NULL)
7763                   || cp->low != cp->high))
7764             {
7765               gfc_error ("Logical range in CASE statement at %L is not "
7766                          "allowed", &cp->low->where);
7767               t = FAILURE;
7768               break;
7769             }
7770
7771           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7772             {
7773               int value;
7774               value = cp->low->value.logical == 0 ? 2 : 1;
7775               if (value & seen_logical)
7776                 {
7777                   gfc_error ("Constant logical value in CASE statement "
7778                              "is repeated at %L",
7779                              &cp->low->where);
7780                   t = FAILURE;
7781                   break;
7782                 }
7783               seen_logical |= value;
7784             }
7785
7786           if (cp->low != NULL && cp->high != NULL
7787               && cp->low != cp->high
7788               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7789             {
7790               if (gfc_option.warn_surprising)
7791                 gfc_warning ("Range specification at %L can never "
7792                              "be matched", &cp->where);
7793
7794               cp->unreachable = 1;
7795               seen_unreachable = 1;
7796             }
7797           else
7798             {
7799               /* If the case range can be matched, it can also overlap with
7800                  other cases.  To make sure it does not, we put it in a
7801                  double linked list here.  We sort that with a merge sort
7802                  later on to detect any overlapping cases.  */
7803               if (!head)
7804                 {
7805                   head = tail = cp;
7806                   head->right = head->left = NULL;
7807                 }
7808               else
7809                 {
7810                   tail->right = cp;
7811                   tail->right->left = tail;
7812                   tail = tail->right;
7813                   tail->right = NULL;
7814                 }
7815             }
7816         }
7817
7818       /* It there was a failure in the previous case label, give up
7819          for this case label list.  Continue with the next block.  */
7820       if (t == FAILURE)
7821         continue;
7822
7823       /* See if any case labels that are unreachable have been seen.
7824          If so, we eliminate them.  This is a bit of a kludge because
7825          the case lists for a single case statement (label) is a
7826          single forward linked lists.  */
7827       if (seen_unreachable)
7828       {
7829         /* Advance until the first case in the list is reachable.  */
7830         while (body->ext.block.case_list != NULL
7831                && body->ext.block.case_list->unreachable)
7832           {
7833             gfc_case *n = body->ext.block.case_list;
7834             body->ext.block.case_list = body->ext.block.case_list->next;
7835             n->next = NULL;
7836             gfc_free_case_list (n);
7837           }
7838
7839         /* Strip all other unreachable cases.  */
7840         if (body->ext.block.case_list)
7841           {
7842             for (cp = body->ext.block.case_list; cp->next; cp = cp->next)
7843               {
7844                 if (cp->next->unreachable)
7845                   {
7846                     gfc_case *n = cp->next;
7847                     cp->next = cp->next->next;
7848                     n->next = NULL;
7849                     gfc_free_case_list (n);
7850                   }
7851               }
7852           }
7853       }
7854     }
7855
7856   /* See if there were overlapping cases.  If the check returns NULL,
7857      there was overlap.  In that case we don't do anything.  If head
7858      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7859      then used during code generation for SELECT CASE constructs with
7860      a case expression of a CHARACTER type.  */
7861   if (head)
7862     {
7863       head = check_case_overlap (head);
7864
7865       /* Prepend the default_case if it is there.  */
7866       if (head != NULL && default_case)
7867         {
7868           default_case->left = NULL;
7869           default_case->right = head;
7870           head->left = default_case;
7871         }
7872     }
7873
7874   /* Eliminate dead blocks that may be the result if we've seen
7875      unreachable case labels for a block.  */
7876   for (body = code; body && body->block; body = body->block)
7877     {
7878       if (body->block->ext.block.case_list == NULL)
7879         {
7880           /* Cut the unreachable block from the code chain.  */
7881           gfc_code *c = body->block;
7882           body->block = c->block;
7883
7884           /* Kill the dead block, but not the blocks below it.  */
7885           c->block = NULL;
7886           gfc_free_statements (c);
7887         }
7888     }
7889
7890   /* More than two cases is legal but insane for logical selects.
7891      Issue a warning for it.  */
7892   if (gfc_option.warn_surprising && type == BT_LOGICAL
7893       && ncases > 2)
7894     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7895                  &code->loc);
7896 }
7897
7898
7899 /* Check if a derived type is extensible.  */
7900
7901 bool
7902 gfc_type_is_extensible (gfc_symbol *sym)
7903 {
7904   return !(sym->attr.is_bind_c || sym->attr.sequence);
7905 }
7906
7907
7908 /* Resolve an associate name:  Resolve target and ensure the type-spec is
7909    correct as well as possibly the array-spec.  */
7910
7911 static void
7912 resolve_assoc_var (gfc_symbol* sym, bool resolve_target)
7913 {
7914   gfc_expr* target;
7915
7916   gcc_assert (sym->assoc);
7917   gcc_assert (sym->attr.flavor == FL_VARIABLE);
7918
7919   /* If this is for SELECT TYPE, the target may not yet be set.  In that
7920      case, return.  Resolution will be called later manually again when
7921      this is done.  */
7922   target = sym->assoc->target;
7923   if (!target)
7924     return;
7925   gcc_assert (!sym->assoc->dangling);
7926
7927   if (resolve_target && gfc_resolve_expr (target) != SUCCESS)
7928     return;
7929
7930   /* For variable targets, we get some attributes from the target.  */
7931   if (target->expr_type == EXPR_VARIABLE)
7932     {
7933       gfc_symbol* tsym;
7934
7935       gcc_assert (target->symtree);
7936       tsym = target->symtree->n.sym;
7937
7938       sym->attr.asynchronous = tsym->attr.asynchronous;
7939       sym->attr.volatile_ = tsym->attr.volatile_;
7940
7941       sym->attr.target = tsym->attr.target
7942                          || gfc_expr_attr (target).pointer;
7943     }
7944
7945   /* Get type if this was not already set.  Note that it can be
7946      some other type than the target in case this is a SELECT TYPE
7947      selector!  So we must not update when the type is already there.  */
7948   if (sym->ts.type == BT_UNKNOWN)
7949     sym->ts = target->ts;
7950   gcc_assert (sym->ts.type != BT_UNKNOWN);
7951
7952   /* See if this is a valid association-to-variable.  */
7953   sym->assoc->variable = (target->expr_type == EXPR_VARIABLE
7954                           && !gfc_has_vector_subscript (target));
7955
7956   /* Finally resolve if this is an array or not.  */
7957   if (sym->attr.dimension && target->rank == 0)
7958     {
7959       gfc_error ("Associate-name '%s' at %L is used as array",
7960                  sym->name, &sym->declared_at);
7961       sym->attr.dimension = 0;
7962       return;
7963     }
7964   if (target->rank > 0)
7965     sym->attr.dimension = 1;
7966
7967   if (sym->attr.dimension)
7968     {
7969       sym->as = gfc_get_array_spec ();
7970       sym->as->rank = target->rank;
7971       sym->as->type = AS_DEFERRED;
7972
7973       /* Target must not be coindexed, thus the associate-variable
7974          has no corank.  */
7975       sym->as->corank = 0;
7976     }
7977 }
7978
7979
7980 /* Resolve a SELECT TYPE statement.  */
7981
7982 static void
7983 resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
7984 {
7985   gfc_symbol *selector_type;
7986   gfc_code *body, *new_st, *if_st, *tail;
7987   gfc_code *class_is = NULL, *default_case = NULL;
7988   gfc_case *c;
7989   gfc_symtree *st;
7990   char name[GFC_MAX_SYMBOL_LEN];
7991   gfc_namespace *ns;
7992   int error = 0;
7993
7994   ns = code->ext.block.ns;
7995   gfc_resolve (ns);
7996
7997   /* Check for F03:C813.  */
7998   if (code->expr1->ts.type != BT_CLASS
7999       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
8000     {
8001       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
8002                  "at %L", &code->loc);
8003       return;
8004     }
8005
8006   if (!code->expr1->symtree->n.sym->attr.class_ok)
8007     return;
8008
8009   if (code->expr2)
8010     {
8011       if (code->expr1->symtree->n.sym->attr.untyped)
8012         code->expr1->symtree->n.sym->ts = code->expr2->ts;
8013       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
8014     }
8015   else
8016     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
8017
8018   /* Loop over TYPE IS / CLASS IS cases.  */
8019   for (body = code->block; body; body = body->block)
8020     {
8021       c = body->ext.block.case_list;
8022
8023       /* Check F03:C815.  */
8024       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
8025           && !gfc_type_is_extensible (c->ts.u.derived))
8026         {
8027           gfc_error ("Derived type '%s' at %L must be extensible",
8028                      c->ts.u.derived->name, &c->where);
8029           error++;
8030           continue;
8031         }
8032
8033       /* Check F03:C816.  */
8034       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
8035           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
8036         {
8037           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
8038                      c->ts.u.derived->name, &c->where, selector_type->name);
8039           error++;
8040           continue;
8041         }
8042
8043       /* Intercept the DEFAULT case.  */
8044       if (c->ts.type == BT_UNKNOWN)
8045         {
8046           /* Check F03:C818.  */
8047           if (default_case)
8048             {
8049               gfc_error ("The DEFAULT CASE at %L cannot be followed "
8050                          "by a second DEFAULT CASE at %L",
8051                          &default_case->ext.block.case_list->where, &c->where);
8052               error++;
8053               continue;
8054             }
8055
8056           default_case = body;
8057         }
8058     }
8059     
8060   if (error > 0)
8061     return;
8062
8063   /* Transform SELECT TYPE statement to BLOCK and associate selector to
8064      target if present.  If there are any EXIT statements referring to the
8065      SELECT TYPE construct, this is no problem because the gfc_code
8066      reference stays the same and EXIT is equally possible from the BLOCK
8067      it is changed to.  */
8068   code->op = EXEC_BLOCK;
8069   if (code->expr2)
8070     {
8071       gfc_association_list* assoc;
8072
8073       assoc = gfc_get_association_list ();
8074       assoc->st = code->expr1->symtree;
8075       assoc->target = gfc_copy_expr (code->expr2);
8076       assoc->target->where = code->expr2->where;
8077       /* assoc->variable will be set by resolve_assoc_var.  */
8078       
8079       code->ext.block.assoc = assoc;
8080       code->expr1->symtree->n.sym->assoc = assoc;
8081
8082       resolve_assoc_var (code->expr1->symtree->n.sym, false);
8083     }
8084   else
8085     code->ext.block.assoc = NULL;
8086
8087   /* Add EXEC_SELECT to switch on type.  */
8088   new_st = gfc_get_code ();
8089   new_st->op = code->op;
8090   new_st->expr1 = code->expr1;
8091   new_st->expr2 = code->expr2;
8092   new_st->block = code->block;
8093   code->expr1 = code->expr2 =  NULL;
8094   code->block = NULL;
8095   if (!ns->code)
8096     ns->code = new_st;
8097   else
8098     ns->code->next = new_st;
8099   code = new_st;
8100   code->op = EXEC_SELECT;
8101   gfc_add_vptr_component (code->expr1);
8102   gfc_add_hash_component (code->expr1);
8103
8104   /* Loop over TYPE IS / CLASS IS cases.  */
8105   for (body = code->block; body; body = body->block)
8106     {
8107       c = body->ext.block.case_list;
8108
8109       if (c->ts.type == BT_DERIVED)
8110         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
8111                                              c->ts.u.derived->hash_value);
8112
8113       else if (c->ts.type == BT_UNKNOWN)
8114         continue;
8115
8116       /* Associate temporary to selector.  This should only be done
8117          when this case is actually true, so build a new ASSOCIATE
8118          that does precisely this here (instead of using the
8119          'global' one).  */
8120
8121       if (c->ts.type == BT_CLASS)
8122         sprintf (name, "__tmp_class_%s", c->ts.u.derived->name);
8123       else
8124         sprintf (name, "__tmp_type_%s", c->ts.u.derived->name);
8125       st = gfc_find_symtree (ns->sym_root, name);
8126       gcc_assert (st->n.sym->assoc);
8127       st->n.sym->assoc->target = gfc_get_variable_expr (code->expr1->symtree);
8128       st->n.sym->assoc->target->where = code->expr1->where;
8129       if (c->ts.type == BT_DERIVED)
8130         gfc_add_data_component (st->n.sym->assoc->target);
8131
8132       new_st = gfc_get_code ();
8133       new_st->op = EXEC_BLOCK;
8134       new_st->ext.block.ns = gfc_build_block_ns (ns);
8135       new_st->ext.block.ns->code = body->next;
8136       body->next = new_st;
8137
8138       /* Chain in the new list only if it is marked as dangling.  Otherwise
8139          there is a CASE label overlap and this is already used.  Just ignore,
8140          the error is diagonsed elsewhere.  */
8141       if (st->n.sym->assoc->dangling)
8142         {
8143           new_st->ext.block.assoc = st->n.sym->assoc;
8144           st->n.sym->assoc->dangling = 0;
8145         }
8146
8147       resolve_assoc_var (st->n.sym, false);
8148     }
8149     
8150   /* Take out CLASS IS cases for separate treatment.  */
8151   body = code;
8152   while (body && body->block)
8153     {
8154       if (body->block->ext.block.case_list->ts.type == BT_CLASS)
8155         {
8156           /* Add to class_is list.  */
8157           if (class_is == NULL)
8158             { 
8159               class_is = body->block;
8160               tail = class_is;
8161             }
8162           else
8163             {
8164               for (tail = class_is; tail->block; tail = tail->block) ;
8165               tail->block = body->block;
8166               tail = tail->block;
8167             }
8168           /* Remove from EXEC_SELECT list.  */
8169           body->block = body->block->block;
8170           tail->block = NULL;
8171         }
8172       else
8173         body = body->block;
8174     }
8175
8176   if (class_is)
8177     {
8178       gfc_symbol *vtab;
8179       
8180       if (!default_case)
8181         {
8182           /* Add a default case to hold the CLASS IS cases.  */
8183           for (tail = code; tail->block; tail = tail->block) ;
8184           tail->block = gfc_get_code ();
8185           tail = tail->block;
8186           tail->op = EXEC_SELECT_TYPE;
8187           tail->ext.block.case_list = gfc_get_case ();
8188           tail->ext.block.case_list->ts.type = BT_UNKNOWN;
8189           tail->next = NULL;
8190           default_case = tail;
8191         }
8192
8193       /* More than one CLASS IS block?  */
8194       if (class_is->block)
8195         {
8196           gfc_code **c1,*c2;
8197           bool swapped;
8198           /* Sort CLASS IS blocks by extension level.  */
8199           do
8200             {
8201               swapped = false;
8202               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
8203                 {
8204                   c2 = (*c1)->block;
8205                   /* F03:C817 (check for doubles).  */
8206                   if ((*c1)->ext.block.case_list->ts.u.derived->hash_value
8207                       == c2->ext.block.case_list->ts.u.derived->hash_value)
8208                     {
8209                       gfc_error ("Double CLASS IS block in SELECT TYPE "
8210                                  "statement at %L",
8211                                  &c2->ext.block.case_list->where);
8212                       return;
8213                     }
8214                   if ((*c1)->ext.block.case_list->ts.u.derived->attr.extension
8215                       < c2->ext.block.case_list->ts.u.derived->attr.extension)
8216                     {
8217                       /* Swap.  */
8218                       (*c1)->block = c2->block;
8219                       c2->block = *c1;
8220                       *c1 = c2;
8221                       swapped = true;
8222                     }
8223                 }
8224             }
8225           while (swapped);
8226         }
8227         
8228       /* Generate IF chain.  */
8229       if_st = gfc_get_code ();
8230       if_st->op = EXEC_IF;
8231       new_st = if_st;
8232       for (body = class_is; body; body = body->block)
8233         {
8234           new_st->block = gfc_get_code ();
8235           new_st = new_st->block;
8236           new_st->op = EXEC_IF;
8237           /* Set up IF condition: Call _gfortran_is_extension_of.  */
8238           new_st->expr1 = gfc_get_expr ();
8239           new_st->expr1->expr_type = EXPR_FUNCTION;
8240           new_st->expr1->ts.type = BT_LOGICAL;
8241           new_st->expr1->ts.kind = 4;
8242           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
8243           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
8244           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
8245           /* Set up arguments.  */
8246           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
8247           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
8248           new_st->expr1->value.function.actual->expr->where = code->loc;
8249           gfc_add_vptr_component (new_st->expr1->value.function.actual->expr);
8250           vtab = gfc_find_derived_vtab (body->ext.block.case_list->ts.u.derived);
8251           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
8252           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
8253           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
8254           new_st->next = body->next;
8255         }
8256         if (default_case->next)
8257           {
8258             new_st->block = gfc_get_code ();
8259             new_st = new_st->block;
8260             new_st->op = EXEC_IF;
8261             new_st->next = default_case->next;
8262           }
8263           
8264         /* Replace CLASS DEFAULT code by the IF chain.  */
8265         default_case->next = if_st;
8266     }
8267
8268   /* Resolve the internal code.  This can not be done earlier because
8269      it requires that the sym->assoc of selectors is set already.  */
8270   gfc_current_ns = ns;
8271   gfc_resolve_blocks (code->block, gfc_current_ns);
8272   gfc_current_ns = old_ns;
8273
8274   resolve_select (code);
8275 }
8276
8277
8278 /* Resolve a transfer statement. This is making sure that:
8279    -- a derived type being transferred has only non-pointer components
8280    -- a derived type being transferred doesn't have private components, unless 
8281       it's being transferred from the module where the type was defined
8282    -- we're not trying to transfer a whole assumed size array.  */
8283
8284 static void
8285 resolve_transfer (gfc_code *code)
8286 {
8287   gfc_typespec *ts;
8288   gfc_symbol *sym;
8289   gfc_ref *ref;
8290   gfc_expr *exp;
8291
8292   exp = code->expr1;
8293
8294   while (exp != NULL && exp->expr_type == EXPR_OP
8295          && exp->value.op.op == INTRINSIC_PARENTHESES)
8296     exp = exp->value.op.op1;
8297
8298   if (exp && exp->expr_type == EXPR_NULL && exp->ts.type == BT_UNKNOWN)
8299     {
8300       gfc_error ("NULL intrinsic at %L in data transfer statement requires "
8301                  "MOLD=", &exp->where);
8302       return;
8303     }
8304
8305   if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
8306                       && exp->expr_type != EXPR_FUNCTION))
8307     return;
8308
8309   /* If we are reading, the variable will be changed.  Note that
8310      code->ext.dt may be NULL if the TRANSFER is related to
8311      an INQUIRE statement -- but in this case, we are not reading, either.  */
8312   if (code->ext.dt && code->ext.dt->dt_io_kind->value.iokind == M_READ
8313       && gfc_check_vardef_context (exp, false, false, _("item in READ"))
8314          == FAILURE)
8315     return;
8316
8317   sym = exp->symtree->n.sym;
8318   ts = &sym->ts;
8319
8320   /* Go to actual component transferred.  */
8321   for (ref = exp->ref; ref; ref = ref->next)
8322     if (ref->type == REF_COMPONENT)
8323       ts = &ref->u.c.component->ts;
8324
8325   if (ts->type == BT_CLASS)
8326     {
8327       /* FIXME: Test for defined input/output.  */
8328       gfc_error ("Data transfer element at %L cannot be polymorphic unless "
8329                 "it is processed by a defined input/output procedure",
8330                 &code->loc);
8331       return;
8332     }
8333
8334   if (ts->type == BT_DERIVED)
8335     {
8336       /* Check that transferred derived type doesn't contain POINTER
8337          components.  */
8338       if (ts->u.derived->attr.pointer_comp)
8339         {
8340           gfc_error ("Data transfer element at %L cannot have POINTER "
8341                      "components unless it is processed by a defined "
8342                      "input/output procedure", &code->loc);
8343           return;
8344         }
8345
8346       /* F08:C935.  */
8347       if (ts->u.derived->attr.proc_pointer_comp)
8348         {
8349           gfc_error ("Data transfer element at %L cannot have "
8350                      "procedure pointer components", &code->loc);
8351           return;
8352         }
8353
8354       if (ts->u.derived->attr.alloc_comp)
8355         {
8356           gfc_error ("Data transfer element at %L cannot have ALLOCATABLE "
8357                      "components unless it is processed by a defined "
8358                      "input/output procedure", &code->loc);
8359           return;
8360         }
8361
8362       if (derived_inaccessible (ts->u.derived))
8363         {
8364           gfc_error ("Data transfer element at %L cannot have "
8365                      "PRIVATE components",&code->loc);
8366           return;
8367         }
8368     }
8369
8370   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE && exp->ref
8371       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
8372     {
8373       gfc_error ("Data transfer element at %L cannot be a full reference to "
8374                  "an assumed-size array", &code->loc);
8375       return;
8376     }
8377 }
8378
8379
8380 /*********** Toplevel code resolution subroutines ***********/
8381
8382 /* Find the set of labels that are reachable from this block.  We also
8383    record the last statement in each block.  */
8384      
8385 static void
8386 find_reachable_labels (gfc_code *block)
8387 {
8388   gfc_code *c;
8389
8390   if (!block)
8391     return;
8392
8393   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
8394
8395   /* Collect labels in this block.  We don't keep those corresponding
8396      to END {IF|SELECT}, these are checked in resolve_branch by going
8397      up through the code_stack.  */
8398   for (c = block; c; c = c->next)
8399     {
8400       if (c->here && c->op != EXEC_END_NESTED_BLOCK)
8401         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
8402     }
8403
8404   /* Merge with labels from parent block.  */
8405   if (cs_base->prev)
8406     {
8407       gcc_assert (cs_base->prev->reachable_labels);
8408       bitmap_ior_into (cs_base->reachable_labels,
8409                        cs_base->prev->reachable_labels);
8410     }
8411 }
8412
8413
8414 static void
8415 resolve_lock_unlock (gfc_code *code)
8416 {
8417   if (code->expr1->ts.type != BT_DERIVED
8418       || code->expr1->expr_type != EXPR_VARIABLE
8419       || code->expr1->ts.u.derived->from_intmod != INTMOD_ISO_FORTRAN_ENV
8420       || code->expr1->ts.u.derived->intmod_sym_id != ISOFORTRAN_LOCK_TYPE
8421       || code->expr1->rank != 0
8422       || (!gfc_is_coarray (code->expr1) && !gfc_is_coindexed (code->expr1)))
8423     gfc_error ("Lock variable at %L must be a scalar of type LOCK_TYPE",
8424                &code->expr1->where);
8425
8426   /* Check STAT.  */
8427   if (code->expr2
8428       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8429           || code->expr2->expr_type != EXPR_VARIABLE))
8430     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8431                &code->expr2->where);
8432
8433   if (code->expr2
8434       && gfc_check_vardef_context (code->expr2, false, false,
8435                                    _("STAT variable")) == FAILURE)
8436     return;
8437
8438   /* Check ERRMSG.  */
8439   if (code->expr3
8440       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8441           || code->expr3->expr_type != EXPR_VARIABLE))
8442     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8443                &code->expr3->where);
8444
8445   if (code->expr3
8446       && gfc_check_vardef_context (code->expr3, false, false,
8447                                    _("ERRMSG variable")) == FAILURE)
8448     return;
8449
8450   /* Check ACQUIRED_LOCK.  */
8451   if (code->expr4
8452       && (code->expr4->ts.type != BT_LOGICAL || code->expr4->rank != 0
8453           || code->expr4->expr_type != EXPR_VARIABLE))
8454     gfc_error ("ACQUIRED_LOCK= argument at %L must be a scalar LOGICAL "
8455                "variable", &code->expr4->where);
8456
8457   if (code->expr4
8458       && gfc_check_vardef_context (code->expr4, false, false,
8459                                    _("ACQUIRED_LOCK variable")) == FAILURE)
8460     return;
8461 }
8462
8463
8464 static void
8465 resolve_sync (gfc_code *code)
8466 {
8467   /* Check imageset. The * case matches expr1 == NULL.  */
8468   if (code->expr1)
8469     {
8470       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
8471         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
8472                    "INTEGER expression", &code->expr1->where);
8473       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
8474           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
8475         gfc_error ("Imageset argument at %L must between 1 and num_images()",
8476                    &code->expr1->where);
8477       else if (code->expr1->expr_type == EXPR_ARRAY
8478                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
8479         {
8480            gfc_constructor *cons;
8481            cons = gfc_constructor_first (code->expr1->value.constructor);
8482            for (; cons; cons = gfc_constructor_next (cons))
8483              if (cons->expr->expr_type == EXPR_CONSTANT
8484                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
8485                gfc_error ("Imageset argument at %L must between 1 and "
8486                           "num_images()", &cons->expr->where);
8487         }
8488     }
8489
8490   /* Check STAT.  */
8491   if (code->expr2
8492       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8493           || code->expr2->expr_type != EXPR_VARIABLE))
8494     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8495                &code->expr2->where);
8496
8497   /* Check ERRMSG.  */
8498   if (code->expr3
8499       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8500           || code->expr3->expr_type != EXPR_VARIABLE))
8501     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8502                &code->expr3->where);
8503 }
8504
8505
8506 /* Given a branch to a label, see if the branch is conforming.
8507    The code node describes where the branch is located.  */
8508
8509 static void
8510 resolve_branch (gfc_st_label *label, gfc_code *code)
8511 {
8512   code_stack *stack;
8513
8514   if (label == NULL)
8515     return;
8516
8517   /* Step one: is this a valid branching target?  */
8518
8519   if (label->defined == ST_LABEL_UNKNOWN)
8520     {
8521       gfc_error ("Label %d referenced at %L is never defined", label->value,
8522                  &label->where);
8523       return;
8524     }
8525
8526   if (label->defined != ST_LABEL_TARGET)
8527     {
8528       gfc_error ("Statement at %L is not a valid branch target statement "
8529                  "for the branch statement at %L", &label->where, &code->loc);
8530       return;
8531     }
8532
8533   /* Step two: make sure this branch is not a branch to itself ;-)  */
8534
8535   if (code->here == label)
8536     {
8537       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
8538       return;
8539     }
8540
8541   /* Step three:  See if the label is in the same block as the
8542      branching statement.  The hard work has been done by setting up
8543      the bitmap reachable_labels.  */
8544
8545   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8546     {
8547       /* Check now whether there is a CRITICAL construct; if so, check
8548          whether the label is still visible outside of the CRITICAL block,
8549          which is invalid.  */
8550       for (stack = cs_base; stack; stack = stack->prev)
8551         {
8552           if (stack->current->op == EXEC_CRITICAL
8553               && bitmap_bit_p (stack->reachable_labels, label->value))
8554             gfc_error ("GOTO statement at %L leaves CRITICAL construct for "
8555                       "label at %L", &code->loc, &label->where);
8556           else if (stack->current->op == EXEC_DO_CONCURRENT
8557                    && bitmap_bit_p (stack->reachable_labels, label->value))
8558             gfc_error ("GOTO statement at %L leaves DO CONCURRENT construct "
8559                       "for label at %L", &code->loc, &label->where);
8560         }
8561
8562       return;
8563     }
8564
8565   /* Step four:  If we haven't found the label in the bitmap, it may
8566     still be the label of the END of the enclosing block, in which
8567     case we find it by going up the code_stack.  */
8568
8569   for (stack = cs_base; stack; stack = stack->prev)
8570     {
8571       if (stack->current->next && stack->current->next->here == label)
8572         break;
8573       if (stack->current->op == EXEC_CRITICAL)
8574         {
8575           /* Note: A label at END CRITICAL does not leave the CRITICAL
8576              construct as END CRITICAL is still part of it.  */
8577           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8578                       " at %L", &code->loc, &label->where);
8579           return;
8580         }
8581       else if (stack->current->op == EXEC_DO_CONCURRENT)
8582         {
8583           gfc_error ("GOTO statement at %L leaves DO CONCURRENT construct for "
8584                      "label at %L", &code->loc, &label->where);
8585           return;
8586         }
8587     }
8588
8589   if (stack)
8590     {
8591       gcc_assert (stack->current->next->op == EXEC_END_NESTED_BLOCK);
8592       return;
8593     }
8594
8595   /* The label is not in an enclosing block, so illegal.  This was
8596      allowed in Fortran 66, so we allow it as extension.  No
8597      further checks are necessary in this case.  */
8598   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
8599                   "as the GOTO statement at %L", &label->where,
8600                   &code->loc);
8601   return;
8602 }
8603
8604
8605 /* Check whether EXPR1 has the same shape as EXPR2.  */
8606
8607 static gfc_try
8608 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8609 {
8610   mpz_t shape[GFC_MAX_DIMENSIONS];
8611   mpz_t shape2[GFC_MAX_DIMENSIONS];
8612   gfc_try result = FAILURE;
8613   int i;
8614
8615   /* Compare the rank.  */
8616   if (expr1->rank != expr2->rank)
8617     return result;
8618
8619   /* Compare the size of each dimension.  */
8620   for (i=0; i<expr1->rank; i++)
8621     {
8622       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
8623         goto ignore;
8624
8625       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
8626         goto ignore;
8627
8628       if (mpz_cmp (shape[i], shape2[i]))
8629         goto over;
8630     }
8631
8632   /* When either of the two expression is an assumed size array, we
8633      ignore the comparison of dimension sizes.  */
8634 ignore:
8635   result = SUCCESS;
8636
8637 over:
8638   gfc_clear_shape (shape, i);
8639   gfc_clear_shape (shape2, i);
8640   return result;
8641 }
8642
8643
8644 /* Check whether a WHERE assignment target or a WHERE mask expression
8645    has the same shape as the outmost WHERE mask expression.  */
8646
8647 static void
8648 resolve_where (gfc_code *code, gfc_expr *mask)
8649 {
8650   gfc_code *cblock;
8651   gfc_code *cnext;
8652   gfc_expr *e = NULL;
8653
8654   cblock = code->block;
8655
8656   /* Store the first WHERE mask-expr of the WHERE statement or construct.
8657      In case of nested WHERE, only the outmost one is stored.  */
8658   if (mask == NULL) /* outmost WHERE */
8659     e = cblock->expr1;
8660   else /* inner WHERE */
8661     e = mask;
8662
8663   while (cblock)
8664     {
8665       if (cblock->expr1)
8666         {
8667           /* Check if the mask-expr has a consistent shape with the
8668              outmost WHERE mask-expr.  */
8669           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
8670             gfc_error ("WHERE mask at %L has inconsistent shape",
8671                        &cblock->expr1->where);
8672          }
8673
8674       /* the assignment statement of a WHERE statement, or the first
8675          statement in where-body-construct of a WHERE construct */
8676       cnext = cblock->next;
8677       while (cnext)
8678         {
8679           switch (cnext->op)
8680             {
8681             /* WHERE assignment statement */
8682             case EXEC_ASSIGN:
8683
8684               /* Check shape consistent for WHERE assignment target.  */
8685               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
8686                gfc_error ("WHERE assignment target at %L has "
8687                           "inconsistent shape", &cnext->expr1->where);
8688               break;
8689
8690   
8691             case EXEC_ASSIGN_CALL:
8692               resolve_call (cnext);
8693               if (!cnext->resolved_sym->attr.elemental)
8694                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8695                           &cnext->ext.actual->expr->where);
8696               break;
8697
8698             /* WHERE or WHERE construct is part of a where-body-construct */
8699             case EXEC_WHERE:
8700               resolve_where (cnext, e);
8701               break;
8702
8703             default:
8704               gfc_error ("Unsupported statement inside WHERE at %L",
8705                          &cnext->loc);
8706             }
8707          /* the next statement within the same where-body-construct */
8708          cnext = cnext->next;
8709        }
8710     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8711     cblock = cblock->block;
8712   }
8713 }
8714
8715
8716 /* Resolve assignment in FORALL construct.
8717    NVAR is the number of FORALL index variables, and VAR_EXPR records the
8718    FORALL index variables.  */
8719
8720 static void
8721 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8722 {
8723   int n;
8724
8725   for (n = 0; n < nvar; n++)
8726     {
8727       gfc_symbol *forall_index;
8728
8729       forall_index = var_expr[n]->symtree->n.sym;
8730
8731       /* Check whether the assignment target is one of the FORALL index
8732          variable.  */
8733       if ((code->expr1->expr_type == EXPR_VARIABLE)
8734           && (code->expr1->symtree->n.sym == forall_index))
8735         gfc_error ("Assignment to a FORALL index variable at %L",
8736                    &code->expr1->where);
8737       else
8738         {
8739           /* If one of the FORALL index variables doesn't appear in the
8740              assignment variable, then there could be a many-to-one
8741              assignment.  Emit a warning rather than an error because the
8742              mask could be resolving this problem.  */
8743           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
8744             gfc_warning ("The FORALL with index '%s' is not used on the "
8745                          "left side of the assignment at %L and so might "
8746                          "cause multiple assignment to this object",
8747                          var_expr[n]->symtree->name, &code->expr1->where);
8748         }
8749     }
8750 }
8751
8752
8753 /* Resolve WHERE statement in FORALL construct.  */
8754
8755 static void
8756 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
8757                                   gfc_expr **var_expr)
8758 {
8759   gfc_code *cblock;
8760   gfc_code *cnext;
8761
8762   cblock = code->block;
8763   while (cblock)
8764     {
8765       /* the assignment statement of a WHERE statement, or the first
8766          statement in where-body-construct of a WHERE construct */
8767       cnext = cblock->next;
8768       while (cnext)
8769         {
8770           switch (cnext->op)
8771             {
8772             /* WHERE assignment statement */
8773             case EXEC_ASSIGN:
8774               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
8775               break;
8776   
8777             /* WHERE operator assignment statement */
8778             case EXEC_ASSIGN_CALL:
8779               resolve_call (cnext);
8780               if (!cnext->resolved_sym->attr.elemental)
8781                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8782                           &cnext->ext.actual->expr->where);
8783               break;
8784
8785             /* WHERE or WHERE construct is part of a where-body-construct */
8786             case EXEC_WHERE:
8787               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
8788               break;
8789
8790             default:
8791               gfc_error ("Unsupported statement inside WHERE at %L",
8792                          &cnext->loc);
8793             }
8794           /* the next statement within the same where-body-construct */
8795           cnext = cnext->next;
8796         }
8797       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8798       cblock = cblock->block;
8799     }
8800 }
8801
8802
8803 /* Traverse the FORALL body to check whether the following errors exist:
8804    1. For assignment, check if a many-to-one assignment happens.
8805    2. For WHERE statement, check the WHERE body to see if there is any
8806       many-to-one assignment.  */
8807
8808 static void
8809 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
8810 {
8811   gfc_code *c;
8812
8813   c = code->block->next;
8814   while (c)
8815     {
8816       switch (c->op)
8817         {
8818         case EXEC_ASSIGN:
8819         case EXEC_POINTER_ASSIGN:
8820           gfc_resolve_assign_in_forall (c, nvar, var_expr);
8821           break;
8822
8823         case EXEC_ASSIGN_CALL:
8824           resolve_call (c);
8825           break;
8826
8827         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
8828            there is no need to handle it here.  */
8829         case EXEC_FORALL:
8830           break;
8831         case EXEC_WHERE:
8832           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
8833           break;
8834         default:
8835           break;
8836         }
8837       /* The next statement in the FORALL body.  */
8838       c = c->next;
8839     }
8840 }
8841
8842
8843 /* Counts the number of iterators needed inside a forall construct, including
8844    nested forall constructs. This is used to allocate the needed memory 
8845    in gfc_resolve_forall.  */
8846
8847 static int 
8848 gfc_count_forall_iterators (gfc_code *code)
8849 {
8850   int max_iters, sub_iters, current_iters;
8851   gfc_forall_iterator *fa;
8852
8853   gcc_assert(code->op == EXEC_FORALL);
8854   max_iters = 0;
8855   current_iters = 0;
8856
8857   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8858     current_iters ++;
8859   
8860   code = code->block->next;
8861
8862   while (code)
8863     {          
8864       if (code->op == EXEC_FORALL)
8865         {
8866           sub_iters = gfc_count_forall_iterators (code);
8867           if (sub_iters > max_iters)
8868             max_iters = sub_iters;
8869         }
8870       code = code->next;
8871     }
8872
8873   return current_iters + max_iters;
8874 }
8875
8876
8877 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8878    gfc_resolve_forall_body to resolve the FORALL body.  */
8879
8880 static void
8881 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8882 {
8883   static gfc_expr **var_expr;
8884   static int total_var = 0;
8885   static int nvar = 0;
8886   int old_nvar, tmp;
8887   gfc_forall_iterator *fa;
8888   int i;
8889
8890   old_nvar = nvar;
8891
8892   /* Start to resolve a FORALL construct   */
8893   if (forall_save == 0)
8894     {
8895       /* Count the total number of FORALL index in the nested FORALL
8896          construct in order to allocate the VAR_EXPR with proper size.  */
8897       total_var = gfc_count_forall_iterators (code);
8898
8899       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8900       var_expr = XCNEWVEC (gfc_expr *, total_var);
8901     }
8902
8903   /* The information about FORALL iterator, including FORALL index start, end
8904      and stride. The FORALL index can not appear in start, end or stride.  */
8905   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8906     {
8907       /* Check if any outer FORALL index name is the same as the current
8908          one.  */
8909       for (i = 0; i < nvar; i++)
8910         {
8911           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8912             {
8913               gfc_error ("An outer FORALL construct already has an index "
8914                          "with this name %L", &fa->var->where);
8915             }
8916         }
8917
8918       /* Record the current FORALL index.  */
8919       var_expr[nvar] = gfc_copy_expr (fa->var);
8920
8921       nvar++;
8922
8923       /* No memory leak.  */
8924       gcc_assert (nvar <= total_var);
8925     }
8926
8927   /* Resolve the FORALL body.  */
8928   gfc_resolve_forall_body (code, nvar, var_expr);
8929
8930   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8931   gfc_resolve_blocks (code->block, ns);
8932
8933   tmp = nvar;
8934   nvar = old_nvar;
8935   /* Free only the VAR_EXPRs allocated in this frame.  */
8936   for (i = nvar; i < tmp; i++)
8937      gfc_free_expr (var_expr[i]);
8938
8939   if (nvar == 0)
8940     {
8941       /* We are in the outermost FORALL construct.  */
8942       gcc_assert (forall_save == 0);
8943
8944       /* VAR_EXPR is not needed any more.  */
8945       free (var_expr);
8946       total_var = 0;
8947     }
8948 }
8949
8950
8951 /* Resolve a BLOCK construct statement.  */
8952
8953 static void
8954 resolve_block_construct (gfc_code* code)
8955 {
8956   /* Resolve the BLOCK's namespace.  */
8957   gfc_resolve (code->ext.block.ns);
8958
8959   /* For an ASSOCIATE block, the associations (and their targets) are already
8960      resolved during resolve_symbol.  */
8961 }
8962
8963
8964 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
8965    DO code nodes.  */
8966
8967 static void resolve_code (gfc_code *, gfc_namespace *);
8968
8969 void
8970 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8971 {
8972   gfc_try t;
8973
8974   for (; b; b = b->block)
8975     {
8976       t = gfc_resolve_expr (b->expr1);
8977       if (gfc_resolve_expr (b->expr2) == FAILURE)
8978         t = FAILURE;
8979
8980       switch (b->op)
8981         {
8982         case EXEC_IF:
8983           if (t == SUCCESS && b->expr1 != NULL
8984               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8985             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8986                        &b->expr1->where);
8987           break;
8988
8989         case EXEC_WHERE:
8990           if (t == SUCCESS
8991               && b->expr1 != NULL
8992               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8993             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8994                        &b->expr1->where);
8995           break;
8996
8997         case EXEC_GOTO:
8998           resolve_branch (b->label1, b);
8999           break;
9000
9001         case EXEC_BLOCK:
9002           resolve_block_construct (b);
9003           break;
9004
9005         case EXEC_SELECT:
9006         case EXEC_SELECT_TYPE:
9007         case EXEC_FORALL:
9008         case EXEC_DO:
9009         case EXEC_DO_WHILE:
9010         case EXEC_DO_CONCURRENT:
9011         case EXEC_CRITICAL:
9012         case EXEC_READ:
9013         case EXEC_WRITE:
9014         case EXEC_IOLENGTH:
9015         case EXEC_WAIT:
9016           break;
9017
9018         case EXEC_OMP_ATOMIC:
9019         case EXEC_OMP_CRITICAL:
9020         case EXEC_OMP_DO:
9021         case EXEC_OMP_MASTER:
9022         case EXEC_OMP_ORDERED:
9023         case EXEC_OMP_PARALLEL:
9024         case EXEC_OMP_PARALLEL_DO:
9025         case EXEC_OMP_PARALLEL_SECTIONS:
9026         case EXEC_OMP_PARALLEL_WORKSHARE:
9027         case EXEC_OMP_SECTIONS:
9028         case EXEC_OMP_SINGLE:
9029         case EXEC_OMP_TASK:
9030         case EXEC_OMP_TASKWAIT:
9031         case EXEC_OMP_TASKYIELD:
9032         case EXEC_OMP_WORKSHARE:
9033           break;
9034
9035         default:
9036           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
9037         }
9038
9039       resolve_code (b->next, ns);
9040     }
9041 }
9042
9043
9044 /* Does everything to resolve an ordinary assignment.  Returns true
9045    if this is an interface assignment.  */
9046 static bool
9047 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
9048 {
9049   bool rval = false;
9050   gfc_expr *lhs;
9051   gfc_expr *rhs;
9052   int llen = 0;
9053   int rlen = 0;
9054   int n;
9055   gfc_ref *ref;
9056
9057   if (gfc_extend_assign (code, ns) == SUCCESS)
9058     {
9059       gfc_expr** rhsptr;
9060
9061       if (code->op == EXEC_ASSIGN_CALL)
9062         {
9063           lhs = code->ext.actual->expr;
9064           rhsptr = &code->ext.actual->next->expr;
9065         }
9066       else
9067         {
9068           gfc_actual_arglist* args;
9069           gfc_typebound_proc* tbp;
9070
9071           gcc_assert (code->op == EXEC_COMPCALL);
9072
9073           args = code->expr1->value.compcall.actual;
9074           lhs = args->expr;
9075           rhsptr = &args->next->expr;
9076
9077           tbp = code->expr1->value.compcall.tbp;
9078           gcc_assert (!tbp->is_generic);
9079         }
9080
9081       /* Make a temporary rhs when there is a default initializer
9082          and rhs is the same symbol as the lhs.  */
9083       if ((*rhsptr)->expr_type == EXPR_VARIABLE
9084             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
9085             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
9086             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
9087         *rhsptr = gfc_get_parentheses (*rhsptr);
9088
9089       return true;
9090     }
9091
9092   lhs = code->expr1;
9093   rhs = code->expr2;
9094
9095   if (rhs->is_boz
9096       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
9097                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
9098                          &code->loc) == FAILURE)
9099     return false;
9100
9101   /* Handle the case of a BOZ literal on the RHS.  */
9102   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
9103     {
9104       int rc;
9105       if (gfc_option.warn_surprising)
9106         gfc_warning ("BOZ literal at %L is bitwise transferred "
9107                      "non-integer symbol '%s'", &code->loc,
9108                      lhs->symtree->n.sym->name);
9109
9110       if (!gfc_convert_boz (rhs, &lhs->ts))
9111         return false;
9112       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
9113         {
9114           if (rc == ARITH_UNDERFLOW)
9115             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
9116                        ". This check can be disabled with the option "
9117                        "-fno-range-check", &rhs->where);
9118           else if (rc == ARITH_OVERFLOW)
9119             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
9120                        ". This check can be disabled with the option "
9121                        "-fno-range-check", &rhs->where);
9122           else if (rc == ARITH_NAN)
9123             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
9124                        ". This check can be disabled with the option "
9125                        "-fno-range-check", &rhs->where);
9126           return false;
9127         }
9128     }
9129
9130   if (lhs->ts.type == BT_CHARACTER
9131         && gfc_option.warn_character_truncation)
9132     {
9133       if (lhs->ts.u.cl != NULL
9134             && lhs->ts.u.cl->length != NULL
9135             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9136         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
9137
9138       if (rhs->expr_type == EXPR_CONSTANT)
9139         rlen = rhs->value.character.length;
9140
9141       else if (rhs->ts.u.cl != NULL
9142                  && rhs->ts.u.cl->length != NULL
9143                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9144         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
9145
9146       if (rlen && llen && rlen > llen)
9147         gfc_warning_now ("CHARACTER expression will be truncated "
9148                          "in assignment (%d/%d) at %L",
9149                          llen, rlen, &code->loc);
9150     }
9151
9152   /* Ensure that a vector index expression for the lvalue is evaluated
9153      to a temporary if the lvalue symbol is referenced in it.  */
9154   if (lhs->rank)
9155     {
9156       for (ref = lhs->ref; ref; ref= ref->next)
9157         if (ref->type == REF_ARRAY)
9158           {
9159             for (n = 0; n < ref->u.ar.dimen; n++)
9160               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
9161                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
9162                                            ref->u.ar.start[n]))
9163                 ref->u.ar.start[n]
9164                         = gfc_get_parentheses (ref->u.ar.start[n]);
9165           }
9166     }
9167
9168   if (gfc_pure (NULL))
9169     {
9170       if (lhs->ts.type == BT_DERIVED
9171             && lhs->expr_type == EXPR_VARIABLE
9172             && lhs->ts.u.derived->attr.pointer_comp
9173             && rhs->expr_type == EXPR_VARIABLE
9174             && (gfc_impure_variable (rhs->symtree->n.sym)
9175                 || gfc_is_coindexed (rhs)))
9176         {
9177           /* F2008, C1283.  */
9178           if (gfc_is_coindexed (rhs))
9179             gfc_error ("Coindexed expression at %L is assigned to "
9180                         "a derived type variable with a POINTER "
9181                         "component in a PURE procedure",
9182                         &rhs->where);
9183           else
9184             gfc_error ("The impure variable at %L is assigned to "
9185                         "a derived type variable with a POINTER "
9186                         "component in a PURE procedure (12.6)",
9187                         &rhs->where);
9188           return rval;
9189         }
9190
9191       /* Fortran 2008, C1283.  */
9192       if (gfc_is_coindexed (lhs))
9193         {
9194           gfc_error ("Assignment to coindexed variable at %L in a PURE "
9195                      "procedure", &rhs->where);
9196           return rval;
9197         }
9198     }
9199
9200   if (gfc_implicit_pure (NULL))
9201     {
9202       if (lhs->expr_type == EXPR_VARIABLE
9203             && lhs->symtree->n.sym != gfc_current_ns->proc_name
9204             && lhs->symtree->n.sym->ns != gfc_current_ns)
9205         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9206
9207       if (lhs->ts.type == BT_DERIVED
9208             && lhs->expr_type == EXPR_VARIABLE
9209             && lhs->ts.u.derived->attr.pointer_comp
9210             && rhs->expr_type == EXPR_VARIABLE
9211             && (gfc_impure_variable (rhs->symtree->n.sym)
9212                 || gfc_is_coindexed (rhs)))
9213         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9214
9215       /* Fortran 2008, C1283.  */
9216       if (gfc_is_coindexed (lhs))
9217         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9218     }
9219
9220   /* F03:7.4.1.2.  */
9221   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
9222      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
9223   if (lhs->ts.type == BT_CLASS)
9224     {
9225       gfc_error ("Variable must not be polymorphic in intrinsic assignment at "
9226                  "%L - check that there is a matching specific subroutine "
9227                  "for '=' operator", &lhs->where);
9228       return false;
9229     }
9230
9231   /* F2008, Section 7.2.1.2.  */
9232   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
9233     {
9234       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
9235                  "component in assignment at %L", &lhs->where);
9236       return false;
9237     }
9238
9239   gfc_check_assign (lhs, rhs, 1);
9240   return false;
9241 }
9242
9243
9244 /* Given a block of code, recursively resolve everything pointed to by this
9245    code block.  */
9246
9247 static void
9248 resolve_code (gfc_code *code, gfc_namespace *ns)
9249 {
9250   int omp_workshare_save;
9251   int forall_save, do_concurrent_save;
9252   code_stack frame;
9253   gfc_try t;
9254
9255   frame.prev = cs_base;
9256   frame.head = code;
9257   cs_base = &frame;
9258
9259   find_reachable_labels (code);
9260
9261   for (; code; code = code->next)
9262     {
9263       frame.current = code;
9264       forall_save = forall_flag;
9265       do_concurrent_save = do_concurrent_flag;
9266
9267       if (code->op == EXEC_FORALL)
9268         {
9269           forall_flag = 1;
9270           gfc_resolve_forall (code, ns, forall_save);
9271           forall_flag = 2;
9272         }
9273       else if (code->block)
9274         {
9275           omp_workshare_save = -1;
9276           switch (code->op)
9277             {
9278             case EXEC_OMP_PARALLEL_WORKSHARE:
9279               omp_workshare_save = omp_workshare_flag;
9280               omp_workshare_flag = 1;
9281               gfc_resolve_omp_parallel_blocks (code, ns);
9282               break;
9283             case EXEC_OMP_PARALLEL:
9284             case EXEC_OMP_PARALLEL_DO:
9285             case EXEC_OMP_PARALLEL_SECTIONS:
9286             case EXEC_OMP_TASK:
9287               omp_workshare_save = omp_workshare_flag;
9288               omp_workshare_flag = 0;
9289               gfc_resolve_omp_parallel_blocks (code, ns);
9290               break;
9291             case EXEC_OMP_DO:
9292               gfc_resolve_omp_do_blocks (code, ns);
9293               break;
9294             case EXEC_SELECT_TYPE:
9295               /* Blocks are handled in resolve_select_type because we have
9296                  to transform the SELECT TYPE into ASSOCIATE first.  */
9297               break;
9298             case EXEC_DO_CONCURRENT:
9299               do_concurrent_flag = 1;
9300               gfc_resolve_blocks (code->block, ns);
9301               do_concurrent_flag = 2;
9302               break;
9303             case EXEC_OMP_WORKSHARE:
9304               omp_workshare_save = omp_workshare_flag;
9305               omp_workshare_flag = 1;
9306               /* FALLTHROUGH */
9307             default:
9308               gfc_resolve_blocks (code->block, ns);
9309               break;
9310             }
9311
9312           if (omp_workshare_save != -1)
9313             omp_workshare_flag = omp_workshare_save;
9314         }
9315
9316       t = SUCCESS;
9317       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
9318         t = gfc_resolve_expr (code->expr1);
9319       forall_flag = forall_save;
9320       do_concurrent_flag = do_concurrent_save;
9321
9322       if (gfc_resolve_expr (code->expr2) == FAILURE)
9323         t = FAILURE;
9324
9325       if (code->op == EXEC_ALLOCATE
9326           && gfc_resolve_expr (code->expr3) == FAILURE)
9327         t = FAILURE;
9328
9329       switch (code->op)
9330         {
9331         case EXEC_NOP:
9332         case EXEC_END_BLOCK:
9333         case EXEC_END_NESTED_BLOCK:
9334         case EXEC_CYCLE:
9335         case EXEC_PAUSE:
9336         case EXEC_STOP:
9337         case EXEC_ERROR_STOP:
9338         case EXEC_EXIT:
9339         case EXEC_CONTINUE:
9340         case EXEC_DT_END:
9341         case EXEC_ASSIGN_CALL:
9342         case EXEC_CRITICAL:
9343           break;
9344
9345         case EXEC_SYNC_ALL:
9346         case EXEC_SYNC_IMAGES:
9347         case EXEC_SYNC_MEMORY:
9348           resolve_sync (code);
9349           break;
9350
9351         case EXEC_LOCK:
9352         case EXEC_UNLOCK:
9353           resolve_lock_unlock (code);
9354           break;
9355
9356         case EXEC_ENTRY:
9357           /* Keep track of which entry we are up to.  */
9358           current_entry_id = code->ext.entry->id;
9359           break;
9360
9361         case EXEC_WHERE:
9362           resolve_where (code, NULL);
9363           break;
9364
9365         case EXEC_GOTO:
9366           if (code->expr1 != NULL)
9367             {
9368               if (code->expr1->ts.type != BT_INTEGER)
9369                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
9370                            "INTEGER variable", &code->expr1->where);
9371               else if (code->expr1->symtree->n.sym->attr.assign != 1)
9372                 gfc_error ("Variable '%s' has not been assigned a target "
9373                            "label at %L", code->expr1->symtree->n.sym->name,
9374                            &code->expr1->where);
9375             }
9376           else
9377             resolve_branch (code->label1, code);
9378           break;
9379
9380         case EXEC_RETURN:
9381           if (code->expr1 != NULL
9382                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
9383             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
9384                        "INTEGER return specifier", &code->expr1->where);
9385           break;
9386
9387         case EXEC_INIT_ASSIGN:
9388         case EXEC_END_PROCEDURE:
9389           break;
9390
9391         case EXEC_ASSIGN:
9392           if (t == FAILURE)
9393             break;
9394
9395           if (gfc_check_vardef_context (code->expr1, false, false,
9396                                         _("assignment")) == FAILURE)
9397             break;
9398
9399           if (resolve_ordinary_assign (code, ns))
9400             {
9401               if (code->op == EXEC_COMPCALL)
9402                 goto compcall;
9403               else
9404                 goto call;
9405             }
9406           break;
9407
9408         case EXEC_LABEL_ASSIGN:
9409           if (code->label1->defined == ST_LABEL_UNKNOWN)
9410             gfc_error ("Label %d referenced at %L is never defined",
9411                        code->label1->value, &code->label1->where);
9412           if (t == SUCCESS
9413               && (code->expr1->expr_type != EXPR_VARIABLE
9414                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
9415                   || code->expr1->symtree->n.sym->ts.kind
9416                      != gfc_default_integer_kind
9417                   || code->expr1->symtree->n.sym->as != NULL))
9418             gfc_error ("ASSIGN statement at %L requires a scalar "
9419                        "default INTEGER variable", &code->expr1->where);
9420           break;
9421
9422         case EXEC_POINTER_ASSIGN:
9423           {
9424             gfc_expr* e;
9425
9426             if (t == FAILURE)
9427               break;
9428
9429             /* This is both a variable definition and pointer assignment
9430                context, so check both of them.  For rank remapping, a final
9431                array ref may be present on the LHS and fool gfc_expr_attr
9432                used in gfc_check_vardef_context.  Remove it.  */
9433             e = remove_last_array_ref (code->expr1);
9434             t = gfc_check_vardef_context (e, true, false,
9435                                           _("pointer assignment"));
9436             if (t == SUCCESS)
9437               t = gfc_check_vardef_context (e, false, false,
9438                                             _("pointer assignment"));
9439             gfc_free_expr (e);
9440             if (t == FAILURE)
9441               break;
9442
9443             gfc_check_pointer_assign (code->expr1, code->expr2);
9444             break;
9445           }
9446
9447         case EXEC_ARITHMETIC_IF:
9448           if (t == SUCCESS
9449               && code->expr1->ts.type != BT_INTEGER
9450               && code->expr1->ts.type != BT_REAL)
9451             gfc_error ("Arithmetic IF statement at %L requires a numeric "
9452                        "expression", &code->expr1->where);
9453
9454           resolve_branch (code->label1, code);
9455           resolve_branch (code->label2, code);
9456           resolve_branch (code->label3, code);
9457           break;
9458
9459         case EXEC_IF:
9460           if (t == SUCCESS && code->expr1 != NULL
9461               && (code->expr1->ts.type != BT_LOGICAL
9462                   || code->expr1->rank != 0))
9463             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9464                        &code->expr1->where);
9465           break;
9466
9467         case EXEC_CALL:
9468         call:
9469           resolve_call (code);
9470           break;
9471
9472         case EXEC_COMPCALL:
9473         compcall:
9474           resolve_typebound_subroutine (code);
9475           break;
9476
9477         case EXEC_CALL_PPC:
9478           resolve_ppc_call (code);
9479           break;
9480
9481         case EXEC_SELECT:
9482           /* Select is complicated. Also, a SELECT construct could be
9483              a transformed computed GOTO.  */
9484           resolve_select (code);
9485           break;
9486
9487         case EXEC_SELECT_TYPE:
9488           resolve_select_type (code, ns);
9489           break;
9490
9491         case EXEC_BLOCK:
9492           resolve_block_construct (code);
9493           break;
9494
9495         case EXEC_DO:
9496           if (code->ext.iterator != NULL)
9497             {
9498               gfc_iterator *iter = code->ext.iterator;
9499               if (gfc_resolve_iterator (iter, true) != FAILURE)
9500                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
9501             }
9502           break;
9503
9504         case EXEC_DO_WHILE:
9505           if (code->expr1 == NULL)
9506             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
9507           if (t == SUCCESS
9508               && (code->expr1->rank != 0
9509                   || code->expr1->ts.type != BT_LOGICAL))
9510             gfc_error ("Exit condition of DO WHILE loop at %L must be "
9511                        "a scalar LOGICAL expression", &code->expr1->where);
9512           break;
9513
9514         case EXEC_ALLOCATE:
9515           if (t == SUCCESS)
9516             resolve_allocate_deallocate (code, "ALLOCATE");
9517
9518           break;
9519
9520         case EXEC_DEALLOCATE:
9521           if (t == SUCCESS)
9522             resolve_allocate_deallocate (code, "DEALLOCATE");
9523
9524           break;
9525
9526         case EXEC_OPEN:
9527           if (gfc_resolve_open (code->ext.open) == FAILURE)
9528             break;
9529
9530           resolve_branch (code->ext.open->err, code);
9531           break;
9532
9533         case EXEC_CLOSE:
9534           if (gfc_resolve_close (code->ext.close) == FAILURE)
9535             break;
9536
9537           resolve_branch (code->ext.close->err, code);
9538           break;
9539
9540         case EXEC_BACKSPACE:
9541         case EXEC_ENDFILE:
9542         case EXEC_REWIND:
9543         case EXEC_FLUSH:
9544           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
9545             break;
9546
9547           resolve_branch (code->ext.filepos->err, code);
9548           break;
9549
9550         case EXEC_INQUIRE:
9551           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9552               break;
9553
9554           resolve_branch (code->ext.inquire->err, code);
9555           break;
9556
9557         case EXEC_IOLENGTH:
9558           gcc_assert (code->ext.inquire != NULL);
9559           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9560             break;
9561
9562           resolve_branch (code->ext.inquire->err, code);
9563           break;
9564
9565         case EXEC_WAIT:
9566           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
9567             break;
9568
9569           resolve_branch (code->ext.wait->err, code);
9570           resolve_branch (code->ext.wait->end, code);
9571           resolve_branch (code->ext.wait->eor, code);
9572           break;
9573
9574         case EXEC_READ:
9575         case EXEC_WRITE:
9576           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
9577             break;
9578
9579           resolve_branch (code->ext.dt->err, code);
9580           resolve_branch (code->ext.dt->end, code);
9581           resolve_branch (code->ext.dt->eor, code);
9582           break;
9583
9584         case EXEC_TRANSFER:
9585           resolve_transfer (code);
9586           break;
9587
9588         case EXEC_DO_CONCURRENT:
9589         case EXEC_FORALL:
9590           resolve_forall_iterators (code->ext.forall_iterator);
9591
9592           if (code->expr1 != NULL
9593               && (code->expr1->ts.type != BT_LOGICAL || code->expr1->rank))
9594             gfc_error ("FORALL mask clause at %L requires a scalar LOGICAL "
9595                        "expression", &code->expr1->where);
9596           break;
9597
9598         case EXEC_OMP_ATOMIC:
9599         case EXEC_OMP_BARRIER:
9600         case EXEC_OMP_CRITICAL:
9601         case EXEC_OMP_FLUSH:
9602         case EXEC_OMP_DO:
9603         case EXEC_OMP_MASTER:
9604         case EXEC_OMP_ORDERED:
9605         case EXEC_OMP_SECTIONS:
9606         case EXEC_OMP_SINGLE:
9607         case EXEC_OMP_TASKWAIT:
9608         case EXEC_OMP_TASKYIELD:
9609         case EXEC_OMP_WORKSHARE:
9610           gfc_resolve_omp_directive (code, ns);
9611           break;
9612
9613         case EXEC_OMP_PARALLEL:
9614         case EXEC_OMP_PARALLEL_DO:
9615         case EXEC_OMP_PARALLEL_SECTIONS:
9616         case EXEC_OMP_PARALLEL_WORKSHARE:
9617         case EXEC_OMP_TASK:
9618           omp_workshare_save = omp_workshare_flag;
9619           omp_workshare_flag = 0;
9620           gfc_resolve_omp_directive (code, ns);
9621           omp_workshare_flag = omp_workshare_save;
9622           break;
9623
9624         default:
9625           gfc_internal_error ("resolve_code(): Bad statement code");
9626         }
9627     }
9628
9629   cs_base = frame.prev;
9630 }
9631
9632
9633 /* Resolve initial values and make sure they are compatible with
9634    the variable.  */
9635
9636 static void
9637 resolve_values (gfc_symbol *sym)
9638 {
9639   gfc_try t;
9640
9641   if (sym->value == NULL)
9642     return;
9643
9644   if (sym->value->expr_type == EXPR_STRUCTURE)
9645     t= resolve_structure_cons (sym->value, 1);
9646   else 
9647     t = gfc_resolve_expr (sym->value);
9648
9649   if (t == FAILURE)
9650     return;
9651
9652   gfc_check_assign_symbol (sym, sym->value);
9653 }
9654
9655
9656 /* Verify the binding labels for common blocks that are BIND(C).  The label
9657    for a BIND(C) common block must be identical in all scoping units in which
9658    the common block is declared.  Further, the binding label can not collide
9659    with any other global entity in the program.  */
9660
9661 static void
9662 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
9663 {
9664   if (comm_block_tree->n.common->is_bind_c == 1)
9665     {
9666       gfc_gsymbol *binding_label_gsym;
9667       gfc_gsymbol *comm_name_gsym;
9668       const char * bind_label = comm_block_tree->n.common->binding_label 
9669         ? comm_block_tree->n.common->binding_label : "";
9670
9671       /* See if a global symbol exists by the common block's name.  It may
9672          be NULL if the common block is use-associated.  */
9673       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
9674                                          comm_block_tree->n.common->name);
9675       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
9676         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
9677                    "with the global entity '%s' at %L",
9678                    bind_label,
9679                    comm_block_tree->n.common->name,
9680                    &(comm_block_tree->n.common->where),
9681                    comm_name_gsym->name, &(comm_name_gsym->where));
9682       else if (comm_name_gsym != NULL
9683                && strcmp (comm_name_gsym->name,
9684                           comm_block_tree->n.common->name) == 0)
9685         {
9686           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
9687              as expected.  */
9688           if (comm_name_gsym->binding_label == NULL)
9689             /* No binding label for common block stored yet; save this one.  */
9690             comm_name_gsym->binding_label = bind_label;
9691           else if (strcmp (comm_name_gsym->binding_label, bind_label) != 0)
9692               {
9693                 /* Common block names match but binding labels do not.  */
9694                 gfc_error ("Binding label '%s' for common block '%s' at %L "
9695                            "does not match the binding label '%s' for common "
9696                            "block '%s' at %L",
9697                            bind_label,
9698                            comm_block_tree->n.common->name,
9699                            &(comm_block_tree->n.common->where),
9700                            comm_name_gsym->binding_label,
9701                            comm_name_gsym->name,
9702                            &(comm_name_gsym->where));
9703                 return;
9704               }
9705         }
9706
9707       /* There is no binding label (NAME="") so we have nothing further to
9708          check and nothing to add as a global symbol for the label.  */
9709       if (!comm_block_tree->n.common->binding_label)
9710         return;
9711       
9712       binding_label_gsym =
9713         gfc_find_gsymbol (gfc_gsym_root,
9714                           comm_block_tree->n.common->binding_label);
9715       if (binding_label_gsym == NULL)
9716         {
9717           /* Need to make a global symbol for the binding label to prevent
9718              it from colliding with another.  */
9719           binding_label_gsym =
9720             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
9721           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
9722           binding_label_gsym->type = GSYM_COMMON;
9723         }
9724       else
9725         {
9726           /* If comm_name_gsym is NULL, the name common block is use
9727              associated and the name could be colliding.  */
9728           if (binding_label_gsym->type != GSYM_COMMON)
9729             gfc_error ("Binding label '%s' for common block '%s' at %L "
9730                        "collides with the global entity '%s' at %L",
9731                        comm_block_tree->n.common->binding_label,
9732                        comm_block_tree->n.common->name,
9733                        &(comm_block_tree->n.common->where),
9734                        binding_label_gsym->name,
9735                        &(binding_label_gsym->where));
9736           else if (comm_name_gsym != NULL
9737                    && (strcmp (binding_label_gsym->name,
9738                                comm_name_gsym->binding_label) != 0)
9739                    && (strcmp (binding_label_gsym->sym_name,
9740                                comm_name_gsym->name) != 0))
9741             gfc_error ("Binding label '%s' for common block '%s' at %L "
9742                        "collides with global entity '%s' at %L",
9743                        binding_label_gsym->name, binding_label_gsym->sym_name,
9744                        &(comm_block_tree->n.common->where),
9745                        comm_name_gsym->name, &(comm_name_gsym->where));
9746         }
9747     }
9748   
9749   return;
9750 }
9751
9752
9753 /* Verify any BIND(C) derived types in the namespace so we can report errors
9754    for them once, rather than for each variable declared of that type.  */
9755
9756 static void
9757 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
9758 {
9759   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
9760       && derived_sym->attr.is_bind_c == 1)
9761     verify_bind_c_derived_type (derived_sym);
9762   
9763   return;
9764 }
9765
9766
9767 /* Verify that any binding labels used in a given namespace do not collide 
9768    with the names or binding labels of any global symbols.  */
9769
9770 static void
9771 gfc_verify_binding_labels (gfc_symbol *sym)
9772 {
9773   int has_error = 0;
9774   
9775   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
9776       && sym->attr.flavor != FL_DERIVED && sym->binding_label)
9777     {
9778       gfc_gsymbol *bind_c_sym;
9779
9780       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
9781       if (bind_c_sym != NULL 
9782           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
9783         {
9784           if (sym->attr.if_source == IFSRC_DECL 
9785               && (bind_c_sym->type != GSYM_SUBROUTINE 
9786                   && bind_c_sym->type != GSYM_FUNCTION) 
9787               && ((sym->attr.contained == 1 
9788                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
9789                   || (sym->attr.use_assoc == 1 
9790                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
9791             {
9792               /* Make sure global procedures don't collide with anything.  */
9793               gfc_error ("Binding label '%s' at %L collides with the global "
9794                          "entity '%s' at %L", sym->binding_label,
9795                          &(sym->declared_at), bind_c_sym->name,
9796                          &(bind_c_sym->where));
9797               has_error = 1;
9798             }
9799           else if (sym->attr.contained == 0 
9800                    && (sym->attr.if_source == IFSRC_IFBODY 
9801                        && sym->attr.flavor == FL_PROCEDURE) 
9802                    && (bind_c_sym->sym_name != NULL 
9803                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
9804             {
9805               /* Make sure procedures in interface bodies don't collide.  */
9806               gfc_error ("Binding label '%s' in interface body at %L collides "
9807                          "with the global entity '%s' at %L",
9808                          sym->binding_label,
9809                          &(sym->declared_at), bind_c_sym->name,
9810                          &(bind_c_sym->where));
9811               has_error = 1;
9812             }
9813           else if (sym->attr.contained == 0 
9814                    && sym->attr.if_source == IFSRC_UNKNOWN)
9815             if ((sym->attr.use_assoc && bind_c_sym->mod_name
9816                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
9817                 || sym->attr.use_assoc == 0)
9818               {
9819                 gfc_error ("Binding label '%s' at %L collides with global "
9820                            "entity '%s' at %L", sym->binding_label,
9821                            &(sym->declared_at), bind_c_sym->name,
9822                            &(bind_c_sym->where));
9823                 has_error = 1;
9824               }
9825
9826           if (has_error != 0)
9827             /* Clear the binding label to prevent checking multiple times.  */
9828             sym->binding_label = NULL;
9829         }
9830       else if (bind_c_sym == NULL)
9831         {
9832           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
9833           bind_c_sym->where = sym->declared_at;
9834           bind_c_sym->sym_name = sym->name;
9835
9836           if (sym->attr.use_assoc == 1)
9837             bind_c_sym->mod_name = sym->module;
9838           else
9839             if (sym->ns->proc_name != NULL)
9840               bind_c_sym->mod_name = sym->ns->proc_name->name;
9841
9842           if (sym->attr.contained == 0)
9843             {
9844               if (sym->attr.subroutine)
9845                 bind_c_sym->type = GSYM_SUBROUTINE;
9846               else if (sym->attr.function)
9847                 bind_c_sym->type = GSYM_FUNCTION;
9848             }
9849         }
9850     }
9851   return;
9852 }
9853
9854
9855 /* Resolve an index expression.  */
9856
9857 static gfc_try
9858 resolve_index_expr (gfc_expr *e)
9859 {
9860   if (gfc_resolve_expr (e) == FAILURE)
9861     return FAILURE;
9862
9863   if (gfc_simplify_expr (e, 0) == FAILURE)
9864     return FAILURE;
9865
9866   if (gfc_specification_expr (e) == FAILURE)
9867     return FAILURE;
9868
9869   return SUCCESS;
9870 }
9871
9872
9873 /* Resolve a charlen structure.  */
9874
9875 static gfc_try
9876 resolve_charlen (gfc_charlen *cl)
9877 {
9878   int i, k;
9879
9880   if (cl->resolved)
9881     return SUCCESS;
9882
9883   cl->resolved = 1;
9884
9885   specification_expr = 1;
9886
9887   if (resolve_index_expr (cl->length) == FAILURE)
9888     {
9889       specification_expr = 0;
9890       return FAILURE;
9891     }
9892
9893   /* "If the character length parameter value evaluates to a negative
9894      value, the length of character entities declared is zero."  */
9895   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
9896     {
9897       if (gfc_option.warn_surprising)
9898         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
9899                          " the length has been set to zero",
9900                          &cl->length->where, i);
9901       gfc_replace_expr (cl->length,
9902                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
9903     }
9904
9905   /* Check that the character length is not too large.  */
9906   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
9907   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
9908       && cl->length->ts.type == BT_INTEGER
9909       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
9910     {
9911       gfc_error ("String length at %L is too large", &cl->length->where);
9912       return FAILURE;
9913     }
9914
9915   return SUCCESS;
9916 }
9917
9918
9919 /* Test for non-constant shape arrays.  */
9920
9921 static bool
9922 is_non_constant_shape_array (gfc_symbol *sym)
9923 {
9924   gfc_expr *e;
9925   int i;
9926   bool not_constant;
9927
9928   not_constant = false;
9929   if (sym->as != NULL)
9930     {
9931       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
9932          has not been simplified; parameter array references.  Do the
9933          simplification now.  */
9934       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
9935         {
9936           e = sym->as->lower[i];
9937           if (e && (resolve_index_expr (e) == FAILURE
9938                     || !gfc_is_constant_expr (e)))
9939             not_constant = true;
9940           e = sym->as->upper[i];
9941           if (e && (resolve_index_expr (e) == FAILURE
9942                     || !gfc_is_constant_expr (e)))
9943             not_constant = true;
9944         }
9945     }
9946   return not_constant;
9947 }
9948
9949 /* Given a symbol and an initialization expression, add code to initialize
9950    the symbol to the function entry.  */
9951 static void
9952 build_init_assign (gfc_symbol *sym, gfc_expr *init)
9953 {
9954   gfc_expr *lval;
9955   gfc_code *init_st;
9956   gfc_namespace *ns = sym->ns;
9957
9958   /* Search for the function namespace if this is a contained
9959      function without an explicit result.  */
9960   if (sym->attr.function && sym == sym->result
9961       && sym->name != sym->ns->proc_name->name)
9962     {
9963       ns = ns->contained;
9964       for (;ns; ns = ns->sibling)
9965         if (strcmp (ns->proc_name->name, sym->name) == 0)
9966           break;
9967     }
9968
9969   if (ns == NULL)
9970     {
9971       gfc_free_expr (init);
9972       return;
9973     }
9974
9975   /* Build an l-value expression for the result.  */
9976   lval = gfc_lval_expr_from_sym (sym);
9977
9978   /* Add the code at scope entry.  */
9979   init_st = gfc_get_code ();
9980   init_st->next = ns->code;
9981   ns->code = init_st;
9982
9983   /* Assign the default initializer to the l-value.  */
9984   init_st->loc = sym->declared_at;
9985   init_st->op = EXEC_INIT_ASSIGN;
9986   init_st->expr1 = lval;
9987   init_st->expr2 = init;
9988 }
9989
9990 /* Assign the default initializer to a derived type variable or result.  */
9991
9992 static void
9993 apply_default_init (gfc_symbol *sym)
9994 {
9995   gfc_expr *init = NULL;
9996
9997   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9998     return;
9999
10000   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
10001     init = gfc_default_initializer (&sym->ts);
10002
10003   if (init == NULL && sym->ts.type != BT_CLASS)
10004     return;
10005
10006   build_init_assign (sym, init);
10007   sym->attr.referenced = 1;
10008 }
10009
10010 /* Build an initializer for a local integer, real, complex, logical, or
10011    character variable, based on the command line flags finit-local-zero,
10012    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
10013    null if the symbol should not have a default initialization.  */
10014 static gfc_expr *
10015 build_default_init_expr (gfc_symbol *sym)
10016 {
10017   int char_len;
10018   gfc_expr *init_expr;
10019   int i;
10020
10021   /* These symbols should never have a default initialization.  */
10022   if (sym->attr.allocatable
10023       || sym->attr.external
10024       || sym->attr.dummy
10025       || sym->attr.pointer
10026       || sym->attr.in_equivalence
10027       || sym->attr.in_common
10028       || sym->attr.data
10029       || sym->module
10030       || sym->attr.cray_pointee
10031       || sym->attr.cray_pointer)
10032     return NULL;
10033
10034   /* Now we'll try to build an initializer expression.  */
10035   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
10036                                      &sym->declared_at);
10037
10038   /* We will only initialize integers, reals, complex, logicals, and
10039      characters, and only if the corresponding command-line flags
10040      were set.  Otherwise, we free init_expr and return null.  */
10041   switch (sym->ts.type)
10042     {    
10043     case BT_INTEGER:
10044       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
10045         mpz_set_si (init_expr->value.integer, 
10046                          gfc_option.flag_init_integer_value);
10047       else
10048         {
10049           gfc_free_expr (init_expr);
10050           init_expr = NULL;
10051         }
10052       break;
10053
10054     case BT_REAL:
10055       switch (gfc_option.flag_init_real)
10056         {
10057         case GFC_INIT_REAL_SNAN:
10058           init_expr->is_snan = 1;
10059           /* Fall through.  */
10060         case GFC_INIT_REAL_NAN:
10061           mpfr_set_nan (init_expr->value.real);
10062           break;
10063
10064         case GFC_INIT_REAL_INF:
10065           mpfr_set_inf (init_expr->value.real, 1);
10066           break;
10067
10068         case GFC_INIT_REAL_NEG_INF:
10069           mpfr_set_inf (init_expr->value.real, -1);
10070           break;
10071
10072         case GFC_INIT_REAL_ZERO:
10073           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
10074           break;
10075
10076         default:
10077           gfc_free_expr (init_expr);
10078           init_expr = NULL;
10079           break;
10080         }
10081       break;
10082           
10083     case BT_COMPLEX:
10084       switch (gfc_option.flag_init_real)
10085         {
10086         case GFC_INIT_REAL_SNAN:
10087           init_expr->is_snan = 1;
10088           /* Fall through.  */
10089         case GFC_INIT_REAL_NAN:
10090           mpfr_set_nan (mpc_realref (init_expr->value.complex));
10091           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
10092           break;
10093
10094         case GFC_INIT_REAL_INF:
10095           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
10096           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
10097           break;
10098
10099         case GFC_INIT_REAL_NEG_INF:
10100           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
10101           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
10102           break;
10103
10104         case GFC_INIT_REAL_ZERO:
10105           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
10106           break;
10107
10108         default:
10109           gfc_free_expr (init_expr);
10110           init_expr = NULL;
10111           break;
10112         }
10113       break;
10114           
10115     case BT_LOGICAL:
10116       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
10117         init_expr->value.logical = 0;
10118       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
10119         init_expr->value.logical = 1;
10120       else
10121         {
10122           gfc_free_expr (init_expr);
10123           init_expr = NULL;
10124         }
10125       break;
10126           
10127     case BT_CHARACTER:
10128       /* For characters, the length must be constant in order to 
10129          create a default initializer.  */
10130       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
10131           && sym->ts.u.cl->length
10132           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
10133         {
10134           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
10135           init_expr->value.character.length = char_len;
10136           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
10137           for (i = 0; i < char_len; i++)
10138             init_expr->value.character.string[i]
10139               = (unsigned char) gfc_option.flag_init_character_value;
10140         }
10141       else
10142         {
10143           gfc_free_expr (init_expr);
10144           init_expr = NULL;
10145         }
10146       if (!init_expr && gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
10147           && sym->ts.u.cl->length)
10148         {
10149           gfc_actual_arglist *arg;
10150           init_expr = gfc_get_expr ();
10151           init_expr->where = sym->declared_at;
10152           init_expr->ts = sym->ts;
10153           init_expr->expr_type = EXPR_FUNCTION;
10154           init_expr->value.function.isym =
10155                 gfc_intrinsic_function_by_id (GFC_ISYM_REPEAT);
10156           init_expr->value.function.name = "repeat";
10157           arg = gfc_get_actual_arglist ();
10158           arg->expr = gfc_get_character_expr (sym->ts.kind, &sym->declared_at,
10159                                               NULL, 1);
10160           arg->expr->value.character.string[0]
10161                 = gfc_option.flag_init_character_value;
10162           arg->next = gfc_get_actual_arglist ();
10163           arg->next->expr = gfc_copy_expr (sym->ts.u.cl->length);
10164           init_expr->value.function.actual = arg;
10165         }
10166       break;
10167           
10168     default:
10169      gfc_free_expr (init_expr);
10170      init_expr = NULL;
10171     }
10172   return init_expr;
10173 }
10174
10175 /* Add an initialization expression to a local variable.  */
10176 static void
10177 apply_default_init_local (gfc_symbol *sym)
10178 {
10179   gfc_expr *init = NULL;
10180
10181   /* The symbol should be a variable or a function return value.  */
10182   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
10183       || (sym->attr.function && sym->result != sym))
10184     return;
10185
10186   /* Try to build the initializer expression.  If we can't initialize
10187      this symbol, then init will be NULL.  */
10188   init = build_default_init_expr (sym);
10189   if (init == NULL)
10190     return;
10191
10192   /* For saved variables, we don't want to add an initializer at function
10193      entry, so we just add a static initializer. Note that automatic variables
10194      are stack allocated even with -fno-automatic.  */
10195   if (sym->attr.save || sym->ns->save_all 
10196       || (gfc_option.flag_max_stack_var_size == 0
10197           && (!sym->attr.dimension || !is_non_constant_shape_array (sym))))
10198     {
10199       /* Don't clobber an existing initializer!  */
10200       gcc_assert (sym->value == NULL);
10201       sym->value = init;
10202       return;
10203     }
10204
10205   build_init_assign (sym, init);
10206 }
10207
10208
10209 /* Resolution of common features of flavors variable and procedure.  */
10210
10211 static gfc_try
10212 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
10213 {
10214   gfc_array_spec *as;
10215
10216   /* Avoid double diagnostics for function result symbols.  */
10217   if ((sym->result || sym->attr.result) && !sym->attr.dummy
10218       && (sym->ns != gfc_current_ns))
10219     return SUCCESS;
10220
10221   if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
10222     as = CLASS_DATA (sym)->as;
10223   else
10224     as = sym->as;
10225
10226   /* Constraints on deferred shape variable.  */
10227   if (as == NULL || as->type != AS_DEFERRED)
10228     {
10229       bool pointer, allocatable, dimension;
10230
10231       if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
10232         {
10233           pointer = CLASS_DATA (sym)->attr.class_pointer;
10234           allocatable = CLASS_DATA (sym)->attr.allocatable;
10235           dimension = CLASS_DATA (sym)->attr.dimension;
10236         }
10237       else
10238         {
10239           pointer = sym->attr.pointer;
10240           allocatable = sym->attr.allocatable;
10241           dimension = sym->attr.dimension;
10242         }
10243
10244       if (allocatable)
10245         {
10246           if (dimension)
10247             {
10248               gfc_error ("Allocatable array '%s' at %L must have "
10249                          "a deferred shape", sym->name, &sym->declared_at);
10250               return FAILURE;
10251             }
10252           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
10253                                    "may not be ALLOCATABLE", sym->name,
10254                                    &sym->declared_at) == FAILURE)
10255             return FAILURE;
10256         }
10257
10258       if (pointer && dimension)
10259         {
10260           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
10261                      sym->name, &sym->declared_at);
10262           return FAILURE;
10263         }
10264     }
10265   else
10266     {
10267       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
10268           && sym->ts.type != BT_CLASS && !sym->assoc)
10269         {
10270           gfc_error ("Array '%s' at %L cannot have a deferred shape",
10271                      sym->name, &sym->declared_at);
10272           return FAILURE;
10273          }
10274     }
10275
10276   /* Constraints on polymorphic variables.  */
10277   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
10278     {
10279       /* F03:C502.  */
10280       if (sym->attr.class_ok
10281           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
10282         {
10283           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
10284                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
10285                      &sym->declared_at);
10286           return FAILURE;
10287         }
10288
10289       /* F03:C509.  */
10290       /* Assume that use associated symbols were checked in the module ns.
10291          Class-variables that are associate-names are also something special
10292          and excepted from the test.  */
10293       if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
10294         {
10295           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
10296                      "or pointer", sym->name, &sym->declared_at);
10297           return FAILURE;
10298         }
10299     }
10300     
10301   return SUCCESS;
10302 }
10303
10304
10305 /* Additional checks for symbols with flavor variable and derived
10306    type.  To be called from resolve_fl_variable.  */
10307
10308 static gfc_try
10309 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
10310 {
10311   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
10312
10313   /* Check to see if a derived type is blocked from being host
10314      associated by the presence of another class I symbol in the same
10315      namespace.  14.6.1.3 of the standard and the discussion on
10316      comp.lang.fortran.  */
10317   if (sym->ns != sym->ts.u.derived->ns
10318       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
10319     {
10320       gfc_symbol *s;
10321       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
10322       if (s && s->attr.generic)
10323         s = gfc_find_dt_in_generic (s);
10324       if (s && s->attr.flavor != FL_DERIVED)
10325         {
10326           gfc_error ("The type '%s' cannot be host associated at %L "
10327                      "because it is blocked by an incompatible object "
10328                      "of the same name declared at %L",
10329                      sym->ts.u.derived->name, &sym->declared_at,
10330                      &s->declared_at);
10331           return FAILURE;
10332         }
10333     }
10334
10335   /* 4th constraint in section 11.3: "If an object of a type for which
10336      component-initialization is specified (R429) appears in the
10337      specification-part of a module and does not have the ALLOCATABLE
10338      or POINTER attribute, the object shall have the SAVE attribute."
10339
10340      The check for initializers is performed with
10341      gfc_has_default_initializer because gfc_default_initializer generates
10342      a hidden default for allocatable components.  */
10343   if (!(sym->value || no_init_flag) && sym->ns->proc_name
10344       && sym->ns->proc_name->attr.flavor == FL_MODULE
10345       && !sym->ns->save_all && !sym->attr.save
10346       && !sym->attr.pointer && !sym->attr.allocatable
10347       && gfc_has_default_initializer (sym->ts.u.derived)
10348       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
10349                          "module variable '%s' at %L, needed due to "
10350                          "the default initialization", sym->name,
10351                          &sym->declared_at) == FAILURE)
10352     return FAILURE;
10353
10354   /* Assign default initializer.  */
10355   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
10356       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
10357     {
10358       sym->value = gfc_default_initializer (&sym->ts);
10359     }
10360
10361   return SUCCESS;
10362 }
10363
10364
10365 /* Resolve symbols with flavor variable.  */
10366
10367 static gfc_try
10368 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
10369 {
10370   int no_init_flag, automatic_flag;
10371   gfc_expr *e;
10372   const char *auto_save_msg;
10373
10374   auto_save_msg = "Automatic object '%s' at %L cannot have the "
10375                   "SAVE attribute";
10376
10377   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10378     return FAILURE;
10379
10380   /* Set this flag to check that variables are parameters of all entries.
10381      This check is effected by the call to gfc_resolve_expr through
10382      is_non_constant_shape_array.  */
10383   specification_expr = 1;
10384
10385   if (sym->ns->proc_name
10386       && (sym->ns->proc_name->attr.flavor == FL_MODULE
10387           || sym->ns->proc_name->attr.is_main_program)
10388       && !sym->attr.use_assoc
10389       && !sym->attr.allocatable
10390       && !sym->attr.pointer
10391       && is_non_constant_shape_array (sym))
10392     {
10393       /* The shape of a main program or module array needs to be
10394          constant.  */
10395       gfc_error ("The module or main program array '%s' at %L must "
10396                  "have constant shape", sym->name, &sym->declared_at);
10397       specification_expr = 0;
10398       return FAILURE;
10399     }
10400
10401   /* Constraints on deferred type parameter.  */
10402   if (sym->ts.deferred && !(sym->attr.pointer || sym->attr.allocatable))
10403     {
10404       gfc_error ("Entity '%s' at %L has a deferred type parameter and "
10405                  "requires either the pointer or allocatable attribute",
10406                      sym->name, &sym->declared_at);
10407       return FAILURE;
10408     }
10409
10410   if (sym->ts.type == BT_CHARACTER)
10411     {
10412       /* Make sure that character string variables with assumed length are
10413          dummy arguments.  */
10414       e = sym->ts.u.cl->length;
10415       if (e == NULL && !sym->attr.dummy && !sym->attr.result
10416           && !sym->ts.deferred)
10417         {
10418           gfc_error ("Entity with assumed character length at %L must be a "
10419                      "dummy argument or a PARAMETER", &sym->declared_at);
10420           return FAILURE;
10421         }
10422
10423       if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
10424         {
10425           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10426           return FAILURE;
10427         }
10428
10429       if (!gfc_is_constant_expr (e)
10430           && !(e->expr_type == EXPR_VARIABLE
10431                && e->symtree->n.sym->attr.flavor == FL_PARAMETER))
10432         {
10433           if (!sym->attr.use_assoc && sym->ns->proc_name
10434               && (sym->ns->proc_name->attr.flavor == FL_MODULE
10435                   || sym->ns->proc_name->attr.is_main_program))
10436             {
10437               gfc_error ("'%s' at %L must have constant character length "
10438                         "in this context", sym->name, &sym->declared_at);
10439               return FAILURE;
10440             }
10441           if (sym->attr.in_common)
10442             {
10443               gfc_error ("COMMON variable '%s' at %L must have constant "
10444                          "character length", sym->name, &sym->declared_at);
10445               return FAILURE;
10446             }
10447         }
10448     }
10449
10450   if (sym->value == NULL && sym->attr.referenced)
10451     apply_default_init_local (sym); /* Try to apply a default initialization.  */
10452
10453   /* Determine if the symbol may not have an initializer.  */
10454   no_init_flag = automatic_flag = 0;
10455   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
10456       || sym->attr.intrinsic || sym->attr.result)
10457     no_init_flag = 1;
10458   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
10459            && is_non_constant_shape_array (sym))
10460     {
10461       no_init_flag = automatic_flag = 1;
10462
10463       /* Also, they must not have the SAVE attribute.
10464          SAVE_IMPLICIT is checked below.  */
10465       if (sym->as && sym->attr.codimension)
10466         {
10467           int corank = sym->as->corank;
10468           sym->as->corank = 0;
10469           no_init_flag = automatic_flag = is_non_constant_shape_array (sym);
10470           sym->as->corank = corank;
10471         }
10472       if (automatic_flag && sym->attr.save == SAVE_EXPLICIT)
10473         {
10474           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10475           return FAILURE;
10476         }
10477     }
10478
10479   /* Ensure that any initializer is simplified.  */
10480   if (sym->value)
10481     gfc_simplify_expr (sym->value, 1);
10482
10483   /* Reject illegal initializers.  */
10484   if (!sym->mark && sym->value)
10485     {
10486       if (sym->attr.allocatable || (sym->ts.type == BT_CLASS
10487                                     && CLASS_DATA (sym)->attr.allocatable))
10488         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
10489                    sym->name, &sym->declared_at);
10490       else if (sym->attr.external)
10491         gfc_error ("External '%s' at %L cannot have an initializer",
10492                    sym->name, &sym->declared_at);
10493       else if (sym->attr.dummy
10494         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
10495         gfc_error ("Dummy '%s' at %L cannot have an initializer",
10496                    sym->name, &sym->declared_at);
10497       else if (sym->attr.intrinsic)
10498         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
10499                    sym->name, &sym->declared_at);
10500       else if (sym->attr.result)
10501         gfc_error ("Function result '%s' at %L cannot have an initializer",
10502                    sym->name, &sym->declared_at);
10503       else if (automatic_flag)
10504         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
10505                    sym->name, &sym->declared_at);
10506       else
10507         goto no_init_error;
10508       return FAILURE;
10509     }
10510
10511 no_init_error:
10512   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
10513     return resolve_fl_variable_derived (sym, no_init_flag);
10514
10515   return SUCCESS;
10516 }
10517
10518
10519 /* Resolve a procedure.  */
10520
10521 static gfc_try
10522 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
10523 {
10524   gfc_formal_arglist *arg;
10525
10526   if (sym->attr.function
10527       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10528     return FAILURE;
10529
10530   if (sym->ts.type == BT_CHARACTER)
10531     {
10532       gfc_charlen *cl = sym->ts.u.cl;
10533
10534       if (cl && cl->length && gfc_is_constant_expr (cl->length)
10535              && resolve_charlen (cl) == FAILURE)
10536         return FAILURE;
10537
10538       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
10539           && sym->attr.proc == PROC_ST_FUNCTION)
10540         {
10541           gfc_error ("Character-valued statement function '%s' at %L must "
10542                      "have constant length", sym->name, &sym->declared_at);
10543           return FAILURE;
10544         }
10545     }
10546
10547   /* Ensure that derived type for are not of a private type.  Internal
10548      module procedures are excluded by 2.2.3.3 - i.e., they are not
10549      externally accessible and can access all the objects accessible in
10550      the host.  */
10551   if (!(sym->ns->parent
10552         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
10553       && gfc_check_symbol_access (sym))
10554     {
10555       gfc_interface *iface;
10556
10557       for (arg = sym->formal; arg; arg = arg->next)
10558         {
10559           if (arg->sym
10560               && arg->sym->ts.type == BT_DERIVED
10561               && !arg->sym->ts.u.derived->attr.use_assoc
10562               && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10563               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
10564                                  "PRIVATE type and cannot be a dummy argument"
10565                                  " of '%s', which is PUBLIC at %L",
10566                                  arg->sym->name, sym->name, &sym->declared_at)
10567                  == FAILURE)
10568             {
10569               /* Stop this message from recurring.  */
10570               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10571               return FAILURE;
10572             }
10573         }
10574
10575       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10576          PRIVATE to the containing module.  */
10577       for (iface = sym->generic; iface; iface = iface->next)
10578         {
10579           for (arg = iface->sym->formal; arg; arg = arg->next)
10580             {
10581               if (arg->sym
10582                   && arg->sym->ts.type == BT_DERIVED
10583                   && !arg->sym->ts.u.derived->attr.use_assoc
10584                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10585                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10586                                      "'%s' in PUBLIC interface '%s' at %L "
10587                                      "takes dummy arguments of '%s' which is "
10588                                      "PRIVATE", iface->sym->name, sym->name,
10589                                      &iface->sym->declared_at,
10590                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10591                 {
10592                   /* Stop this message from recurring.  */
10593                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10594                   return FAILURE;
10595                 }
10596              }
10597         }
10598
10599       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10600          PRIVATE to the containing module.  */
10601       for (iface = sym->generic; iface; iface = iface->next)
10602         {
10603           for (arg = iface->sym->formal; arg; arg = arg->next)
10604             {
10605               if (arg->sym
10606                   && arg->sym->ts.type == BT_DERIVED
10607                   && !arg->sym->ts.u.derived->attr.use_assoc
10608                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10609                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10610                                      "'%s' in PUBLIC interface '%s' at %L "
10611                                      "takes dummy arguments of '%s' which is "
10612                                      "PRIVATE", iface->sym->name, sym->name,
10613                                      &iface->sym->declared_at,
10614                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10615                 {
10616                   /* Stop this message from recurring.  */
10617                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10618                   return FAILURE;
10619                 }
10620              }
10621         }
10622     }
10623
10624   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
10625       && !sym->attr.proc_pointer)
10626     {
10627       gfc_error ("Function '%s' at %L cannot have an initializer",
10628                  sym->name, &sym->declared_at);
10629       return FAILURE;
10630     }
10631
10632   /* An external symbol may not have an initializer because it is taken to be
10633      a procedure. Exception: Procedure Pointers.  */
10634   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
10635     {
10636       gfc_error ("External object '%s' at %L may not have an initializer",
10637                  sym->name, &sym->declared_at);
10638       return FAILURE;
10639     }
10640
10641   /* An elemental function is required to return a scalar 12.7.1  */
10642   if (sym->attr.elemental && sym->attr.function && sym->as)
10643     {
10644       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
10645                  "result", sym->name, &sym->declared_at);
10646       /* Reset so that the error only occurs once.  */
10647       sym->attr.elemental = 0;
10648       return FAILURE;
10649     }
10650
10651   if (sym->attr.proc == PROC_ST_FUNCTION
10652       && (sym->attr.allocatable || sym->attr.pointer))
10653     {
10654       gfc_error ("Statement function '%s' at %L may not have pointer or "
10655                  "allocatable attribute", sym->name, &sym->declared_at);
10656       return FAILURE;
10657     }
10658
10659   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
10660      char-len-param shall not be array-valued, pointer-valued, recursive
10661      or pure.  ....snip... A character value of * may only be used in the
10662      following ways: (i) Dummy arg of procedure - dummy associates with
10663      actual length; (ii) To declare a named constant; or (iii) External
10664      function - but length must be declared in calling scoping unit.  */
10665   if (sym->attr.function
10666       && sym->ts.type == BT_CHARACTER
10667       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
10668     {
10669       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
10670           || (sym->attr.recursive) || (sym->attr.pure))
10671         {
10672           if (sym->as && sym->as->rank)
10673             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10674                        "array-valued", sym->name, &sym->declared_at);
10675
10676           if (sym->attr.pointer)
10677             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10678                        "pointer-valued", sym->name, &sym->declared_at);
10679
10680           if (sym->attr.pure)
10681             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10682                        "pure", sym->name, &sym->declared_at);
10683
10684           if (sym->attr.recursive)
10685             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10686                        "recursive", sym->name, &sym->declared_at);
10687
10688           return FAILURE;
10689         }
10690
10691       /* Appendix B.2 of the standard.  Contained functions give an
10692          error anyway.  Fixed-form is likely to be F77/legacy. Deferred
10693          character length is an F2003 feature.  */
10694       if (!sym->attr.contained
10695             && gfc_current_form != FORM_FIXED
10696             && !sym->ts.deferred)
10697         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
10698                         "CHARACTER(*) function '%s' at %L",
10699                         sym->name, &sym->declared_at);
10700     }
10701
10702   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
10703     {
10704       gfc_formal_arglist *curr_arg;
10705       int has_non_interop_arg = 0;
10706
10707       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10708                              sym->common_block) == FAILURE)
10709         {
10710           /* Clear these to prevent looking at them again if there was an
10711              error.  */
10712           sym->attr.is_bind_c = 0;
10713           sym->attr.is_c_interop = 0;
10714           sym->ts.is_c_interop = 0;
10715         }
10716       else
10717         {
10718           /* So far, no errors have been found.  */
10719           sym->attr.is_c_interop = 1;
10720           sym->ts.is_c_interop = 1;
10721         }
10722       
10723       curr_arg = sym->formal;
10724       while (curr_arg != NULL)
10725         {
10726           /* Skip implicitly typed dummy args here.  */
10727           if (curr_arg->sym->attr.implicit_type == 0)
10728             if (gfc_verify_c_interop_param (curr_arg->sym) == FAILURE)
10729               /* If something is found to fail, record the fact so we
10730                  can mark the symbol for the procedure as not being
10731                  BIND(C) to try and prevent multiple errors being
10732                  reported.  */
10733               has_non_interop_arg = 1;
10734           
10735           curr_arg = curr_arg->next;
10736         }
10737
10738       /* See if any of the arguments were not interoperable and if so, clear
10739          the procedure symbol to prevent duplicate error messages.  */
10740       if (has_non_interop_arg != 0)
10741         {
10742           sym->attr.is_c_interop = 0;
10743           sym->ts.is_c_interop = 0;
10744           sym->attr.is_bind_c = 0;
10745         }
10746     }
10747   
10748   if (!sym->attr.proc_pointer)
10749     {
10750       if (sym->attr.save == SAVE_EXPLICIT)
10751         {
10752           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
10753                      "in '%s' at %L", sym->name, &sym->declared_at);
10754           return FAILURE;
10755         }
10756       if (sym->attr.intent)
10757         {
10758           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
10759                      "in '%s' at %L", sym->name, &sym->declared_at);
10760           return FAILURE;
10761         }
10762       if (sym->attr.subroutine && sym->attr.result)
10763         {
10764           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
10765                      "in '%s' at %L", sym->name, &sym->declared_at);
10766           return FAILURE;
10767         }
10768       if (sym->attr.external && sym->attr.function
10769           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
10770               || sym->attr.contained))
10771         {
10772           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
10773                      "in '%s' at %L", sym->name, &sym->declared_at);
10774           return FAILURE;
10775         }
10776       if (strcmp ("ppr@", sym->name) == 0)
10777         {
10778           gfc_error ("Procedure pointer result '%s' at %L "
10779                      "is missing the pointer attribute",
10780                      sym->ns->proc_name->name, &sym->declared_at);
10781           return FAILURE;
10782         }
10783     }
10784
10785   return SUCCESS;
10786 }
10787
10788
10789 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
10790    been defined and we now know their defined arguments, check that they fulfill
10791    the requirements of the standard for procedures used as finalizers.  */
10792
10793 static gfc_try
10794 gfc_resolve_finalizers (gfc_symbol* derived)
10795 {
10796   gfc_finalizer* list;
10797   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
10798   gfc_try result = SUCCESS;
10799   bool seen_scalar = false;
10800
10801   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
10802     return SUCCESS;
10803
10804   /* Walk over the list of finalizer-procedures, check them, and if any one
10805      does not fit in with the standard's definition, print an error and remove
10806      it from the list.  */
10807   prev_link = &derived->f2k_derived->finalizers;
10808   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
10809     {
10810       gfc_symbol* arg;
10811       gfc_finalizer* i;
10812       int my_rank;
10813
10814       /* Skip this finalizer if we already resolved it.  */
10815       if (list->proc_tree)
10816         {
10817           prev_link = &(list->next);
10818           continue;
10819         }
10820
10821       /* Check this exists and is a SUBROUTINE.  */
10822       if (!list->proc_sym->attr.subroutine)
10823         {
10824           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
10825                      list->proc_sym->name, &list->where);
10826           goto error;
10827         }
10828
10829       /* We should have exactly one argument.  */
10830       if (!list->proc_sym->formal || list->proc_sym->formal->next)
10831         {
10832           gfc_error ("FINAL procedure at %L must have exactly one argument",
10833                      &list->where);
10834           goto error;
10835         }
10836       arg = list->proc_sym->formal->sym;
10837
10838       /* This argument must be of our type.  */
10839       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
10840         {
10841           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
10842                      &arg->declared_at, derived->name);
10843           goto error;
10844         }
10845
10846       /* It must neither be a pointer nor allocatable nor optional.  */
10847       if (arg->attr.pointer)
10848         {
10849           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
10850                      &arg->declared_at);
10851           goto error;
10852         }
10853       if (arg->attr.allocatable)
10854         {
10855           gfc_error ("Argument of FINAL procedure at %L must not be"
10856                      " ALLOCATABLE", &arg->declared_at);
10857           goto error;
10858         }
10859       if (arg->attr.optional)
10860         {
10861           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
10862                      &arg->declared_at);
10863           goto error;
10864         }
10865
10866       /* It must not be INTENT(OUT).  */
10867       if (arg->attr.intent == INTENT_OUT)
10868         {
10869           gfc_error ("Argument of FINAL procedure at %L must not be"
10870                      " INTENT(OUT)", &arg->declared_at);
10871           goto error;
10872         }
10873
10874       /* Warn if the procedure is non-scalar and not assumed shape.  */
10875       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
10876           && arg->as->type != AS_ASSUMED_SHAPE)
10877         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
10878                      " shape argument", &arg->declared_at);
10879
10880       /* Check that it does not match in kind and rank with a FINAL procedure
10881          defined earlier.  To really loop over the *earlier* declarations,
10882          we need to walk the tail of the list as new ones were pushed at the
10883          front.  */
10884       /* TODO: Handle kind parameters once they are implemented.  */
10885       my_rank = (arg->as ? arg->as->rank : 0);
10886       for (i = list->next; i; i = i->next)
10887         {
10888           /* Argument list might be empty; that is an error signalled earlier,
10889              but we nevertheless continued resolving.  */
10890           if (i->proc_sym->formal)
10891             {
10892               gfc_symbol* i_arg = i->proc_sym->formal->sym;
10893               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
10894               if (i_rank == my_rank)
10895                 {
10896                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
10897                              " rank (%d) as '%s'",
10898                              list->proc_sym->name, &list->where, my_rank, 
10899                              i->proc_sym->name);
10900                   goto error;
10901                 }
10902             }
10903         }
10904
10905         /* Is this the/a scalar finalizer procedure?  */
10906         if (!arg->as || arg->as->rank == 0)
10907           seen_scalar = true;
10908
10909         /* Find the symtree for this procedure.  */
10910         gcc_assert (!list->proc_tree);
10911         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
10912
10913         prev_link = &list->next;
10914         continue;
10915
10916         /* Remove wrong nodes immediately from the list so we don't risk any
10917            troubles in the future when they might fail later expectations.  */
10918 error:
10919         result = FAILURE;
10920         i = list;
10921         *prev_link = list->next;
10922         gfc_free_finalizer (i);
10923     }
10924
10925   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
10926      were nodes in the list, must have been for arrays.  It is surely a good
10927      idea to have a scalar version there if there's something to finalize.  */
10928   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
10929     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
10930                  " defined at %L, suggest also scalar one",
10931                  derived->name, &derived->declared_at);
10932
10933   /* TODO:  Remove this error when finalization is finished.  */
10934   gfc_error ("Finalization at %L is not yet implemented",
10935              &derived->declared_at);
10936
10937   return result;
10938 }
10939
10940
10941 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10942
10943 static gfc_try
10944 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10945                              const char* generic_name, locus where)
10946 {
10947   gfc_symbol* sym1;
10948   gfc_symbol* sym2;
10949
10950   gcc_assert (t1->specific && t2->specific);
10951   gcc_assert (!t1->specific->is_generic);
10952   gcc_assert (!t2->specific->is_generic);
10953
10954   sym1 = t1->specific->u.specific->n.sym;
10955   sym2 = t2->specific->u.specific->n.sym;
10956
10957   if (sym1 == sym2)
10958     return SUCCESS;
10959
10960   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10961   if (sym1->attr.subroutine != sym2->attr.subroutine
10962       || sym1->attr.function != sym2->attr.function)
10963     {
10964       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10965                  " GENERIC '%s' at %L",
10966                  sym1->name, sym2->name, generic_name, &where);
10967       return FAILURE;
10968     }
10969
10970   /* Compare the interfaces.  */
10971   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10972     {
10973       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10974                  sym1->name, sym2->name, generic_name, &where);
10975       return FAILURE;
10976     }
10977
10978   return SUCCESS;
10979 }
10980
10981
10982 /* Worker function for resolving a generic procedure binding; this is used to
10983    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10984
10985    The difference between those cases is finding possible inherited bindings
10986    that are overridden, as one has to look for them in tb_sym_root,
10987    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10988    the super-type and set p->overridden correctly.  */
10989
10990 static gfc_try
10991 resolve_tb_generic_targets (gfc_symbol* super_type,
10992                             gfc_typebound_proc* p, const char* name)
10993 {
10994   gfc_tbp_generic* target;
10995   gfc_symtree* first_target;
10996   gfc_symtree* inherited;
10997
10998   gcc_assert (p && p->is_generic);
10999
11000   /* Try to find the specific bindings for the symtrees in our target-list.  */
11001   gcc_assert (p->u.generic);
11002   for (target = p->u.generic; target; target = target->next)
11003     if (!target->specific)
11004       {
11005         gfc_typebound_proc* overridden_tbp;
11006         gfc_tbp_generic* g;
11007         const char* target_name;
11008
11009         target_name = target->specific_st->name;
11010
11011         /* Defined for this type directly.  */
11012         if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
11013           {
11014             target->specific = target->specific_st->n.tb;
11015             goto specific_found;
11016           }
11017
11018         /* Look for an inherited specific binding.  */
11019         if (super_type)
11020           {
11021             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
11022                                                  true, NULL);
11023
11024             if (inherited)
11025               {
11026                 gcc_assert (inherited->n.tb);
11027                 target->specific = inherited->n.tb;
11028                 goto specific_found;
11029               }
11030           }
11031
11032         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
11033                    " at %L", target_name, name, &p->where);
11034         return FAILURE;
11035
11036         /* Once we've found the specific binding, check it is not ambiguous with
11037            other specifics already found or inherited for the same GENERIC.  */
11038 specific_found:
11039         gcc_assert (target->specific);
11040
11041         /* This must really be a specific binding!  */
11042         if (target->specific->is_generic)
11043           {
11044             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
11045                        " '%s' is GENERIC, too", name, &p->where, target_name);
11046             return FAILURE;
11047           }
11048
11049         /* Check those already resolved on this type directly.  */
11050         for (g = p->u.generic; g; g = g->next)
11051           if (g != target && g->specific
11052               && check_generic_tbp_ambiguity (target, g, name, p->where)
11053                   == FAILURE)
11054             return FAILURE;
11055
11056         /* Check for ambiguity with inherited specific targets.  */
11057         for (overridden_tbp = p->overridden; overridden_tbp;
11058              overridden_tbp = overridden_tbp->overridden)
11059           if (overridden_tbp->is_generic)
11060             {
11061               for (g = overridden_tbp->u.generic; g; g = g->next)
11062                 {
11063                   gcc_assert (g->specific);
11064                   if (check_generic_tbp_ambiguity (target, g,
11065                                                    name, p->where) == FAILURE)
11066                     return FAILURE;
11067                 }
11068             }
11069       }
11070
11071   /* If we attempt to "overwrite" a specific binding, this is an error.  */
11072   if (p->overridden && !p->overridden->is_generic)
11073     {
11074       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
11075                  " the same name", name, &p->where);
11076       return FAILURE;
11077     }
11078
11079   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
11080      all must have the same attributes here.  */
11081   first_target = p->u.generic->specific->u.specific;
11082   gcc_assert (first_target);
11083   p->subroutine = first_target->n.sym->attr.subroutine;
11084   p->function = first_target->n.sym->attr.function;
11085
11086   return SUCCESS;
11087 }
11088
11089
11090 /* Resolve a GENERIC procedure binding for a derived type.  */
11091
11092 static gfc_try
11093 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
11094 {
11095   gfc_symbol* super_type;
11096
11097   /* Find the overridden binding if any.  */
11098   st->n.tb->overridden = NULL;
11099   super_type = gfc_get_derived_super_type (derived);
11100   if (super_type)
11101     {
11102       gfc_symtree* overridden;
11103       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
11104                                             true, NULL);
11105
11106       if (overridden && overridden->n.tb)
11107         st->n.tb->overridden = overridden->n.tb;
11108     }
11109
11110   /* Resolve using worker function.  */
11111   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
11112 }
11113
11114
11115 /* Retrieve the target-procedure of an operator binding and do some checks in
11116    common for intrinsic and user-defined type-bound operators.  */
11117
11118 static gfc_symbol*
11119 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
11120 {
11121   gfc_symbol* target_proc;
11122
11123   gcc_assert (target->specific && !target->specific->is_generic);
11124   target_proc = target->specific->u.specific->n.sym;
11125   gcc_assert (target_proc);
11126
11127   /* All operator bindings must have a passed-object dummy argument.  */
11128   if (target->specific->nopass)
11129     {
11130       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
11131       return NULL;
11132     }
11133
11134   return target_proc;
11135 }
11136
11137
11138 /* Resolve a type-bound intrinsic operator.  */
11139
11140 static gfc_try
11141 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
11142                                 gfc_typebound_proc* p)
11143 {
11144   gfc_symbol* super_type;
11145   gfc_tbp_generic* target;
11146   
11147   /* If there's already an error here, do nothing (but don't fail again).  */
11148   if (p->error)
11149     return SUCCESS;
11150
11151   /* Operators should always be GENERIC bindings.  */
11152   gcc_assert (p->is_generic);
11153
11154   /* Look for an overridden binding.  */
11155   super_type = gfc_get_derived_super_type (derived);
11156   if (super_type && super_type->f2k_derived)
11157     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
11158                                                      op, true, NULL);
11159   else
11160     p->overridden = NULL;
11161
11162   /* Resolve general GENERIC properties using worker function.  */
11163   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
11164     goto error;
11165
11166   /* Check the targets to be procedures of correct interface.  */
11167   for (target = p->u.generic; target; target = target->next)
11168     {
11169       gfc_symbol* target_proc;
11170
11171       target_proc = get_checked_tb_operator_target (target, p->where);
11172       if (!target_proc)
11173         goto error;
11174
11175       if (!gfc_check_operator_interface (target_proc, op, p->where))
11176         goto error;
11177     }
11178
11179   return SUCCESS;
11180
11181 error:
11182   p->error = 1;
11183   return FAILURE;
11184 }
11185
11186
11187 /* Resolve a type-bound user operator (tree-walker callback).  */
11188
11189 static gfc_symbol* resolve_bindings_derived;
11190 static gfc_try resolve_bindings_result;
11191
11192 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
11193
11194 static void
11195 resolve_typebound_user_op (gfc_symtree* stree)
11196 {
11197   gfc_symbol* super_type;
11198   gfc_tbp_generic* target;
11199
11200   gcc_assert (stree && stree->n.tb);
11201
11202   if (stree->n.tb->error)
11203     return;
11204
11205   /* Operators should always be GENERIC bindings.  */
11206   gcc_assert (stree->n.tb->is_generic);
11207
11208   /* Find overridden procedure, if any.  */
11209   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11210   if (super_type && super_type->f2k_derived)
11211     {
11212       gfc_symtree* overridden;
11213       overridden = gfc_find_typebound_user_op (super_type, NULL,
11214                                                stree->name, true, NULL);
11215
11216       if (overridden && overridden->n.tb)
11217         stree->n.tb->overridden = overridden->n.tb;
11218     }
11219   else
11220     stree->n.tb->overridden = NULL;
11221
11222   /* Resolve basically using worker function.  */
11223   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
11224         == FAILURE)
11225     goto error;
11226
11227   /* Check the targets to be functions of correct interface.  */
11228   for (target = stree->n.tb->u.generic; target; target = target->next)
11229     {
11230       gfc_symbol* target_proc;
11231
11232       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
11233       if (!target_proc)
11234         goto error;
11235
11236       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
11237         goto error;
11238     }
11239
11240   return;
11241
11242 error:
11243   resolve_bindings_result = FAILURE;
11244   stree->n.tb->error = 1;
11245 }
11246
11247
11248 /* Resolve the type-bound procedures for a derived type.  */
11249
11250 static void
11251 resolve_typebound_procedure (gfc_symtree* stree)
11252 {
11253   gfc_symbol* proc;
11254   locus where;
11255   gfc_symbol* me_arg;
11256   gfc_symbol* super_type;
11257   gfc_component* comp;
11258
11259   gcc_assert (stree);
11260
11261   /* Undefined specific symbol from GENERIC target definition.  */
11262   if (!stree->n.tb)
11263     return;
11264
11265   if (stree->n.tb->error)
11266     return;
11267
11268   /* If this is a GENERIC binding, use that routine.  */
11269   if (stree->n.tb->is_generic)
11270     {
11271       if (resolve_typebound_generic (resolve_bindings_derived, stree)
11272             == FAILURE)
11273         goto error;
11274       return;
11275     }
11276
11277   /* Get the target-procedure to check it.  */
11278   gcc_assert (!stree->n.tb->is_generic);
11279   gcc_assert (stree->n.tb->u.specific);
11280   proc = stree->n.tb->u.specific->n.sym;
11281   where = stree->n.tb->where;
11282
11283   /* Default access should already be resolved from the parser.  */
11284   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
11285
11286   /* It should be a module procedure or an external procedure with explicit
11287      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
11288   if ((!proc->attr.subroutine && !proc->attr.function)
11289       || (proc->attr.proc != PROC_MODULE
11290           && proc->attr.if_source != IFSRC_IFBODY)
11291       || (proc->attr.abstract && !stree->n.tb->deferred))
11292     {
11293       gfc_error ("'%s' must be a module procedure or an external procedure with"
11294                  " an explicit interface at %L", proc->name, &where);
11295       goto error;
11296     }
11297   stree->n.tb->subroutine = proc->attr.subroutine;
11298   stree->n.tb->function = proc->attr.function;
11299
11300   /* Find the super-type of the current derived type.  We could do this once and
11301      store in a global if speed is needed, but as long as not I believe this is
11302      more readable and clearer.  */
11303   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11304
11305   /* If PASS, resolve and check arguments if not already resolved / loaded
11306      from a .mod file.  */
11307   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
11308     {
11309       if (stree->n.tb->pass_arg)
11310         {
11311           gfc_formal_arglist* i;
11312
11313           /* If an explicit passing argument name is given, walk the arg-list
11314              and look for it.  */
11315
11316           me_arg = NULL;
11317           stree->n.tb->pass_arg_num = 1;
11318           for (i = proc->formal; i; i = i->next)
11319             {
11320               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
11321                 {
11322                   me_arg = i->sym;
11323                   break;
11324                 }
11325               ++stree->n.tb->pass_arg_num;
11326             }
11327
11328           if (!me_arg)
11329             {
11330               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
11331                          " argument '%s'",
11332                          proc->name, stree->n.tb->pass_arg, &where,
11333                          stree->n.tb->pass_arg);
11334               goto error;
11335             }
11336         }
11337       else
11338         {
11339           /* Otherwise, take the first one; there should in fact be at least
11340              one.  */
11341           stree->n.tb->pass_arg_num = 1;
11342           if (!proc->formal)
11343             {
11344               gfc_error ("Procedure '%s' with PASS at %L must have at"
11345                          " least one argument", proc->name, &where);
11346               goto error;
11347             }
11348           me_arg = proc->formal->sym;
11349         }
11350
11351       /* Now check that the argument-type matches and the passed-object
11352          dummy argument is generally fine.  */
11353
11354       gcc_assert (me_arg);
11355
11356       if (me_arg->ts.type != BT_CLASS)
11357         {
11358           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11359                      " at %L", proc->name, &where);
11360           goto error;
11361         }
11362
11363       if (CLASS_DATA (me_arg)->ts.u.derived
11364           != resolve_bindings_derived)
11365         {
11366           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11367                      " the derived-type '%s'", me_arg->name, proc->name,
11368                      me_arg->name, &where, resolve_bindings_derived->name);
11369           goto error;
11370         }
11371   
11372       gcc_assert (me_arg->ts.type == BT_CLASS);
11373       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
11374         {
11375           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
11376                      " scalar", proc->name, &where);
11377           goto error;
11378         }
11379       if (CLASS_DATA (me_arg)->attr.allocatable)
11380         {
11381           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11382                      " be ALLOCATABLE", proc->name, &where);
11383           goto error;
11384         }
11385       if (CLASS_DATA (me_arg)->attr.class_pointer)
11386         {
11387           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11388                      " be POINTER", proc->name, &where);
11389           goto error;
11390         }
11391     }
11392
11393   /* If we are extending some type, check that we don't override a procedure
11394      flagged NON_OVERRIDABLE.  */
11395   stree->n.tb->overridden = NULL;
11396   if (super_type)
11397     {
11398       gfc_symtree* overridden;
11399       overridden = gfc_find_typebound_proc (super_type, NULL,
11400                                             stree->name, true, NULL);
11401
11402       if (overridden)
11403         {
11404           if (overridden->n.tb)
11405             stree->n.tb->overridden = overridden->n.tb;
11406
11407           if (gfc_check_typebound_override (stree, overridden) == FAILURE)
11408             goto error;
11409         }
11410     }
11411
11412   /* See if there's a name collision with a component directly in this type.  */
11413   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
11414     if (!strcmp (comp->name, stree->name))
11415       {
11416         gfc_error ("Procedure '%s' at %L has the same name as a component of"
11417                    " '%s'",
11418                    stree->name, &where, resolve_bindings_derived->name);
11419         goto error;
11420       }
11421
11422   /* Try to find a name collision with an inherited component.  */
11423   if (super_type && gfc_find_component (super_type, stree->name, true, true))
11424     {
11425       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
11426                  " component of '%s'",
11427                  stree->name, &where, resolve_bindings_derived->name);
11428       goto error;
11429     }
11430
11431   stree->n.tb->error = 0;
11432   return;
11433
11434 error:
11435   resolve_bindings_result = FAILURE;
11436   stree->n.tb->error = 1;
11437 }
11438
11439
11440 static gfc_try
11441 resolve_typebound_procedures (gfc_symbol* derived)
11442 {
11443   int op;
11444   gfc_symbol* super_type;
11445
11446   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
11447     return SUCCESS;
11448   
11449   super_type = gfc_get_derived_super_type (derived);
11450   if (super_type)
11451     resolve_typebound_procedures (super_type);
11452
11453   resolve_bindings_derived = derived;
11454   resolve_bindings_result = SUCCESS;
11455
11456   /* Make sure the vtab has been generated.  */
11457   gfc_find_derived_vtab (derived);
11458
11459   if (derived->f2k_derived->tb_sym_root)
11460     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
11461                           &resolve_typebound_procedure);
11462
11463   if (derived->f2k_derived->tb_uop_root)
11464     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
11465                           &resolve_typebound_user_op);
11466
11467   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
11468     {
11469       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
11470       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
11471                                                p) == FAILURE)
11472         resolve_bindings_result = FAILURE;
11473     }
11474
11475   return resolve_bindings_result;
11476 }
11477
11478
11479 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
11480    to give all identical derived types the same backend_decl.  */
11481 static void
11482 add_dt_to_dt_list (gfc_symbol *derived)
11483 {
11484   gfc_dt_list *dt_list;
11485
11486   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
11487     if (derived == dt_list->derived)
11488       return;
11489
11490   dt_list = gfc_get_dt_list ();
11491   dt_list->next = gfc_derived_types;
11492   dt_list->derived = derived;
11493   gfc_derived_types = dt_list;
11494 }
11495
11496
11497 /* Ensure that a derived-type is really not abstract, meaning that every
11498    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
11499
11500 static gfc_try
11501 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
11502 {
11503   if (!st)
11504     return SUCCESS;
11505
11506   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
11507     return FAILURE;
11508   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
11509     return FAILURE;
11510
11511   if (st->n.tb && st->n.tb->deferred)
11512     {
11513       gfc_symtree* overriding;
11514       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
11515       if (!overriding)
11516         return FAILURE;
11517       gcc_assert (overriding->n.tb);
11518       if (overriding->n.tb->deferred)
11519         {
11520           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
11521                      " '%s' is DEFERRED and not overridden",
11522                      sub->name, &sub->declared_at, st->name);
11523           return FAILURE;
11524         }
11525     }
11526
11527   return SUCCESS;
11528 }
11529
11530 static gfc_try
11531 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
11532 {
11533   /* The algorithm used here is to recursively travel up the ancestry of sub
11534      and for each ancestor-type, check all bindings.  If any of them is
11535      DEFERRED, look it up starting from sub and see if the found (overriding)
11536      binding is not DEFERRED.
11537      This is not the most efficient way to do this, but it should be ok and is
11538      clearer than something sophisticated.  */
11539
11540   gcc_assert (ancestor && !sub->attr.abstract);
11541   
11542   if (!ancestor->attr.abstract)
11543     return SUCCESS;
11544
11545   /* Walk bindings of this ancestor.  */
11546   if (ancestor->f2k_derived)
11547     {
11548       gfc_try t;
11549       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
11550       if (t == FAILURE)
11551         return FAILURE;
11552     }
11553
11554   /* Find next ancestor type and recurse on it.  */
11555   ancestor = gfc_get_derived_super_type (ancestor);
11556   if (ancestor)
11557     return ensure_not_abstract (sub, ancestor);
11558
11559   return SUCCESS;
11560 }
11561
11562
11563 /* Resolve the components of a derived type. This does not have to wait until
11564    resolution stage, but can be done as soon as the dt declaration has been
11565    parsed.  */
11566
11567 static gfc_try
11568 resolve_fl_derived0 (gfc_symbol *sym)
11569 {
11570   gfc_symbol* super_type;
11571   gfc_component *c;
11572
11573   super_type = gfc_get_derived_super_type (sym);
11574
11575   /* F2008, C432. */
11576   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
11577     {
11578       gfc_error ("As extending type '%s' at %L has a coarray component, "
11579                  "parent type '%s' shall also have one", sym->name,
11580                  &sym->declared_at, super_type->name);
11581       return FAILURE;
11582     }
11583
11584   /* Ensure the extended type gets resolved before we do.  */
11585   if (super_type && resolve_fl_derived0 (super_type) == FAILURE)
11586     return FAILURE;
11587
11588   /* An ABSTRACT type must be extensible.  */
11589   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
11590     {
11591       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
11592                  sym->name, &sym->declared_at);
11593       return FAILURE;
11594     }
11595
11596   c = (sym->attr.is_class) ? sym->components->ts.u.derived->components
11597                            : sym->components;
11598
11599   for ( ; c != NULL; c = c->next)
11600     {
11601       /* See PRs 51550, 47545, 48654, 49050, 51075 - and 45170.  */
11602       if (c->ts.type == BT_CHARACTER && c->ts.deferred)
11603         {
11604           gfc_error ("Deferred-length character component '%s' at %L is not "
11605                      "yet supported", c->name, &c->loc);
11606           return FAILURE;
11607         }
11608
11609       /* F2008, C442.  */
11610       if ((!sym->attr.is_class || c != sym->components)
11611           && c->attr.codimension
11612           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
11613         {
11614           gfc_error ("Coarray component '%s' at %L must be allocatable with "
11615                      "deferred shape", c->name, &c->loc);
11616           return FAILURE;
11617         }
11618
11619       /* F2008, C443.  */
11620       if (c->attr.codimension && c->ts.type == BT_DERIVED
11621           && c->ts.u.derived->ts.is_iso_c)
11622         {
11623           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11624                      "shall not be a coarray", c->name, &c->loc);
11625           return FAILURE;
11626         }
11627
11628       /* F2008, C444.  */
11629       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
11630           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
11631               || c->attr.allocatable))
11632         {
11633           gfc_error ("Component '%s' at %L with coarray component "
11634                      "shall be a nonpointer, nonallocatable scalar",
11635                      c->name, &c->loc);
11636           return FAILURE;
11637         }
11638
11639       /* F2008, C448.  */
11640       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
11641         {
11642           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
11643                      "is not an array pointer", c->name, &c->loc);
11644           return FAILURE;
11645         }
11646
11647       if (c->attr.proc_pointer && c->ts.interface)
11648         {
11649           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
11650             gfc_error ("Interface '%s', used by procedure pointer component "
11651                        "'%s' at %L, is declared in a later PROCEDURE statement",
11652                        c->ts.interface->name, c->name, &c->loc);
11653
11654           /* Get the attributes from the interface (now resolved).  */
11655           if (c->ts.interface->attr.if_source
11656               || c->ts.interface->attr.intrinsic)
11657             {
11658               gfc_symbol *ifc = c->ts.interface;
11659
11660               if (ifc->formal && !ifc->formal_ns)
11661                 resolve_symbol (ifc);
11662
11663               if (ifc->attr.intrinsic)
11664                 resolve_intrinsic (ifc, &ifc->declared_at);
11665
11666               if (ifc->result)
11667                 {
11668                   c->ts = ifc->result->ts;
11669                   c->attr.allocatable = ifc->result->attr.allocatable;
11670                   c->attr.pointer = ifc->result->attr.pointer;
11671                   c->attr.dimension = ifc->result->attr.dimension;
11672                   c->as = gfc_copy_array_spec (ifc->result->as);
11673                 }
11674               else
11675                 {   
11676                   c->ts = ifc->ts;
11677                   c->attr.allocatable = ifc->attr.allocatable;
11678                   c->attr.pointer = ifc->attr.pointer;
11679                   c->attr.dimension = ifc->attr.dimension;
11680                   c->as = gfc_copy_array_spec (ifc->as);
11681                 }
11682               c->ts.interface = ifc;
11683               c->attr.function = ifc->attr.function;
11684               c->attr.subroutine = ifc->attr.subroutine;
11685               gfc_copy_formal_args_ppc (c, ifc);
11686
11687               c->attr.pure = ifc->attr.pure;
11688               c->attr.elemental = ifc->attr.elemental;
11689               c->attr.recursive = ifc->attr.recursive;
11690               c->attr.always_explicit = ifc->attr.always_explicit;
11691               c->attr.ext_attr |= ifc->attr.ext_attr;
11692               /* Replace symbols in array spec.  */
11693               if (c->as)
11694                 {
11695                   int i;
11696                   for (i = 0; i < c->as->rank; i++)
11697                     {
11698                       gfc_expr_replace_comp (c->as->lower[i], c);
11699                       gfc_expr_replace_comp (c->as->upper[i], c);
11700                     }
11701                 }
11702               /* Copy char length.  */
11703               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11704                 {
11705                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11706                   gfc_expr_replace_comp (cl->length, c);
11707                   if (cl->length && !cl->resolved
11708                         && gfc_resolve_expr (cl->length) == FAILURE)
11709                     return FAILURE;
11710                   c->ts.u.cl = cl;
11711                 }
11712             }
11713           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
11714             {
11715               gfc_error ("Interface '%s' of procedure pointer component "
11716                          "'%s' at %L must be explicit", c->ts.interface->name,
11717                          c->name, &c->loc);
11718               return FAILURE;
11719             }
11720         }
11721       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
11722         {
11723           /* Since PPCs are not implicitly typed, a PPC without an explicit
11724              interface must be a subroutine.  */
11725           gfc_add_subroutine (&c->attr, c->name, &c->loc);
11726         }
11727
11728       /* Procedure pointer components: Check PASS arg.  */
11729       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
11730           && !sym->attr.vtype)
11731         {
11732           gfc_symbol* me_arg;
11733
11734           if (c->tb->pass_arg)
11735             {
11736               gfc_formal_arglist* i;
11737
11738               /* If an explicit passing argument name is given, walk the arg-list
11739                 and look for it.  */
11740
11741               me_arg = NULL;
11742               c->tb->pass_arg_num = 1;
11743               for (i = c->formal; i; i = i->next)
11744                 {
11745                   if (!strcmp (i->sym->name, c->tb->pass_arg))
11746                     {
11747                       me_arg = i->sym;
11748                       break;
11749                     }
11750                   c->tb->pass_arg_num++;
11751                 }
11752
11753               if (!me_arg)
11754                 {
11755                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
11756                              "at %L has no argument '%s'", c->name,
11757                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
11758                   c->tb->error = 1;
11759                   return FAILURE;
11760                 }
11761             }
11762           else
11763             {
11764               /* Otherwise, take the first one; there should in fact be at least
11765                 one.  */
11766               c->tb->pass_arg_num = 1;
11767               if (!c->formal)
11768                 {
11769                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
11770                              "must have at least one argument",
11771                              c->name, &c->loc);
11772                   c->tb->error = 1;
11773                   return FAILURE;
11774                 }
11775               me_arg = c->formal->sym;
11776             }
11777
11778           /* Now check that the argument-type matches.  */
11779           gcc_assert (me_arg);
11780           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
11781               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
11782               || (me_arg->ts.type == BT_CLASS
11783                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
11784             {
11785               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11786                          " the derived type '%s'", me_arg->name, c->name,
11787                          me_arg->name, &c->loc, sym->name);
11788               c->tb->error = 1;
11789               return FAILURE;
11790             }
11791
11792           /* Check for C453.  */
11793           if (me_arg->attr.dimension)
11794             {
11795               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11796                          "must be scalar", me_arg->name, c->name, me_arg->name,
11797                          &c->loc);
11798               c->tb->error = 1;
11799               return FAILURE;
11800             }
11801
11802           if (me_arg->attr.pointer)
11803             {
11804               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11805                          "may not have the POINTER attribute", me_arg->name,
11806                          c->name, me_arg->name, &c->loc);
11807               c->tb->error = 1;
11808               return FAILURE;
11809             }
11810
11811           if (me_arg->attr.allocatable)
11812             {
11813               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11814                          "may not be ALLOCATABLE", me_arg->name, c->name,
11815                          me_arg->name, &c->loc);
11816               c->tb->error = 1;
11817               return FAILURE;
11818             }
11819
11820           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11821             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11822                        " at %L", c->name, &c->loc);
11823
11824         }
11825
11826       /* Check type-spec if this is not the parent-type component.  */
11827       if (((sym->attr.is_class
11828             && (!sym->components->ts.u.derived->attr.extension
11829                 || c != sym->components->ts.u.derived->components))
11830            || (!sym->attr.is_class
11831                && (!sym->attr.extension || c != sym->components)))
11832           && !sym->attr.vtype
11833           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11834         return FAILURE;
11835
11836       /* If this type is an extension, set the accessibility of the parent
11837          component.  */
11838       if (super_type
11839           && ((sym->attr.is_class
11840                && c == sym->components->ts.u.derived->components)
11841               || (!sym->attr.is_class && c == sym->components))
11842           && strcmp (super_type->name, c->name) == 0)
11843         c->attr.access = super_type->attr.access;
11844       
11845       /* If this type is an extension, see if this component has the same name
11846          as an inherited type-bound procedure.  */
11847       if (super_type && !sym->attr.is_class
11848           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11849         {
11850           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11851                      " inherited type-bound procedure",
11852                      c->name, sym->name, &c->loc);
11853           return FAILURE;
11854         }
11855
11856       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer
11857             && !c->ts.deferred)
11858         {
11859          if (c->ts.u.cl->length == NULL
11860              || (resolve_charlen (c->ts.u.cl) == FAILURE)
11861              || !gfc_is_constant_expr (c->ts.u.cl->length))
11862            {
11863              gfc_error ("Character length of component '%s' needs to "
11864                         "be a constant specification expression at %L",
11865                         c->name,
11866                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
11867              return FAILURE;
11868            }
11869         }
11870
11871       if (c->ts.type == BT_CHARACTER && c->ts.deferred
11872           && !c->attr.pointer && !c->attr.allocatable)
11873         {
11874           gfc_error ("Character component '%s' of '%s' at %L with deferred "
11875                      "length must be a POINTER or ALLOCATABLE",
11876                      c->name, sym->name, &c->loc);
11877           return FAILURE;
11878         }
11879
11880       if (c->ts.type == BT_DERIVED
11881           && sym->component_access != ACCESS_PRIVATE
11882           && gfc_check_symbol_access (sym)
11883           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11884           && !c->ts.u.derived->attr.use_assoc
11885           && !gfc_check_symbol_access (c->ts.u.derived)
11886           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11887                              "is a PRIVATE type and cannot be a component of "
11888                              "'%s', which is PUBLIC at %L", c->name,
11889                              sym->name, &sym->declared_at) == FAILURE)
11890         return FAILURE;
11891
11892       if ((sym->attr.sequence || sym->attr.is_bind_c) && c->ts.type == BT_CLASS)
11893         {
11894           gfc_error ("Polymorphic component %s at %L in SEQUENCE or BIND(C) "
11895                      "type %s", c->name, &c->loc, sym->name);
11896           return FAILURE;
11897         }
11898
11899       if (sym->attr.sequence)
11900         {
11901           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
11902             {
11903               gfc_error ("Component %s of SEQUENCE type declared at %L does "
11904                          "not have the SEQUENCE attribute",
11905                          c->ts.u.derived->name, &sym->declared_at);
11906               return FAILURE;
11907             }
11908         }
11909
11910       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.generic)
11911         c->ts.u.derived = gfc_find_dt_in_generic (c->ts.u.derived);
11912       else if (c->ts.type == BT_CLASS && c->attr.class_ok
11913                && CLASS_DATA (c)->ts.u.derived->attr.generic)
11914         CLASS_DATA (c)->ts.u.derived
11915                         = gfc_find_dt_in_generic (CLASS_DATA (c)->ts.u.derived);
11916
11917       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && !sym->attr.vtype
11918           && c->attr.pointer && c->ts.u.derived->components == NULL
11919           && !c->ts.u.derived->attr.zero_comp)
11920         {
11921           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11922                      "that has not been declared", c->name, sym->name,
11923                      &c->loc);
11924           return FAILURE;
11925         }
11926
11927       if (c->ts.type == BT_CLASS && c->attr.class_ok
11928           && CLASS_DATA (c)->attr.class_pointer
11929           && CLASS_DATA (c)->ts.u.derived->components == NULL
11930           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
11931         {
11932           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11933                      "that has not been declared", c->name, sym->name,
11934                      &c->loc);
11935           return FAILURE;
11936         }
11937
11938       /* C437.  */
11939       if (c->ts.type == BT_CLASS && c->attr.flavor != FL_PROCEDURE
11940           && (!c->attr.class_ok
11941               || !(CLASS_DATA (c)->attr.class_pointer
11942                    || CLASS_DATA (c)->attr.allocatable)))
11943         {
11944           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
11945                      "or pointer", c->name, &c->loc);
11946           return FAILURE;
11947         }
11948
11949       /* Ensure that all the derived type components are put on the
11950          derived type list; even in formal namespaces, where derived type
11951          pointer components might not have been declared.  */
11952       if (c->ts.type == BT_DERIVED
11953             && c->ts.u.derived
11954             && c->ts.u.derived->components
11955             && c->attr.pointer
11956             && sym != c->ts.u.derived)
11957         add_dt_to_dt_list (c->ts.u.derived);
11958
11959       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
11960                                            || c->attr.proc_pointer
11961                                            || c->attr.allocatable)) == FAILURE)
11962         return FAILURE;
11963     }
11964
11965   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11966      all DEFERRED bindings are overridden.  */
11967   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11968       && !sym->attr.is_class
11969       && ensure_not_abstract (sym, super_type) == FAILURE)
11970     return FAILURE;
11971
11972   /* Add derived type to the derived type list.  */
11973   add_dt_to_dt_list (sym);
11974
11975   return SUCCESS;
11976 }
11977
11978
11979 /* The following procedure does the full resolution of a derived type,
11980    including resolution of all type-bound procedures (if present). In contrast
11981    to 'resolve_fl_derived0' this can only be done after the module has been
11982    parsed completely.  */
11983
11984 static gfc_try
11985 resolve_fl_derived (gfc_symbol *sym)
11986 {
11987   gfc_symbol *gen_dt = NULL;
11988
11989   if (!sym->attr.is_class)
11990     gfc_find_symbol (sym->name, sym->ns, 0, &gen_dt);
11991   if (gen_dt && gen_dt->generic && gen_dt->generic->next
11992       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Generic name '%s' of "
11993                          "function '%s' at %L being the same name as derived "
11994                          "type at %L", sym->name,
11995                          gen_dt->generic->sym == sym
11996                            ? gen_dt->generic->next->sym->name
11997                            : gen_dt->generic->sym->name,
11998                          gen_dt->generic->sym == sym
11999                            ? &gen_dt->generic->next->sym->declared_at
12000                            : &gen_dt->generic->sym->declared_at,
12001                          &sym->declared_at) == FAILURE)
12002     return FAILURE;
12003
12004   if (sym->attr.is_class && sym->ts.u.derived == NULL)
12005     {
12006       /* Fix up incomplete CLASS symbols.  */
12007       gfc_component *data = gfc_find_component (sym, "_data", true, true);
12008       gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true);
12009       if (vptr->ts.u.derived == NULL)
12010         {
12011           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
12012           gcc_assert (vtab);
12013           vptr->ts.u.derived = vtab->ts.u.derived;
12014         }
12015     }
12016   
12017   if (resolve_fl_derived0 (sym) == FAILURE)
12018     return FAILURE;
12019   
12020   /* Resolve the type-bound procedures.  */
12021   if (resolve_typebound_procedures (sym) == FAILURE)
12022     return FAILURE;
12023
12024   /* Resolve the finalizer procedures.  */
12025   if (gfc_resolve_finalizers (sym) == FAILURE)
12026     return FAILURE;
12027   
12028   return SUCCESS;
12029 }
12030
12031
12032 static gfc_try
12033 resolve_fl_namelist (gfc_symbol *sym)
12034 {
12035   gfc_namelist *nl;
12036   gfc_symbol *nlsym;
12037
12038   for (nl = sym->namelist; nl; nl = nl->next)
12039     {
12040       /* Check again, the check in match only works if NAMELIST comes
12041          after the decl.  */
12042       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SIZE)
12043         {
12044           gfc_error ("Assumed size array '%s' in namelist '%s' at %L is not "
12045                      "allowed", nl->sym->name, sym->name, &sym->declared_at);
12046           return FAILURE;
12047         }
12048
12049       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
12050           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: NAMELIST array "
12051                              "object '%s' with assumed shape in namelist "
12052                              "'%s' at %L", nl->sym->name, sym->name,
12053                              &sym->declared_at) == FAILURE)
12054         return FAILURE;
12055
12056       if (is_non_constant_shape_array (nl->sym)
12057           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST array "
12058                              "object '%s' with nonconstant shape in namelist "
12059                              "'%s' at %L", nl->sym->name, sym->name,
12060                              &sym->declared_at) == FAILURE)
12061         return FAILURE;
12062
12063       if (nl->sym->ts.type == BT_CHARACTER
12064           && (nl->sym->ts.u.cl->length == NULL
12065               || !gfc_is_constant_expr (nl->sym->ts.u.cl->length))
12066           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
12067                              "'%s' with nonconstant character length in "
12068                              "namelist '%s' at %L", nl->sym->name, sym->name,
12069                              &sym->declared_at) == FAILURE)
12070         return FAILURE;
12071
12072       /* FIXME: Once UDDTIO is implemented, the following can be
12073          removed.  */
12074       if (nl->sym->ts.type == BT_CLASS)
12075         {
12076           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L is "
12077                      "polymorphic and requires a defined input/output "
12078                      "procedure", nl->sym->name, sym->name, &sym->declared_at);
12079           return FAILURE;
12080         }
12081
12082       if (nl->sym->ts.type == BT_DERIVED
12083           && (nl->sym->ts.u.derived->attr.alloc_comp
12084               || nl->sym->ts.u.derived->attr.pointer_comp))
12085         {
12086           if (gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
12087                               "'%s' in namelist '%s' at %L with ALLOCATABLE "
12088                               "or POINTER components", nl->sym->name,
12089                               sym->name, &sym->declared_at) == FAILURE)
12090             return FAILURE;
12091
12092          /* FIXME: Once UDDTIO is implemented, the following can be
12093             removed.  */
12094           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L has "
12095                      "ALLOCATABLE or POINTER components and thus requires "
12096                      "a defined input/output procedure", nl->sym->name,
12097                      sym->name, &sym->declared_at);
12098           return FAILURE;
12099         }
12100     }
12101
12102   /* Reject PRIVATE objects in a PUBLIC namelist.  */
12103   if (gfc_check_symbol_access (sym))
12104     {
12105       for (nl = sym->namelist; nl; nl = nl->next)
12106         {
12107           if (!nl->sym->attr.use_assoc
12108               && !is_sym_host_assoc (nl->sym, sym->ns)
12109               && !gfc_check_symbol_access (nl->sym))
12110             {
12111               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
12112                          "cannot be member of PUBLIC namelist '%s' at %L",
12113                          nl->sym->name, sym->name, &sym->declared_at);
12114               return FAILURE;
12115             }
12116
12117           /* Types with private components that came here by USE-association.  */
12118           if (nl->sym->ts.type == BT_DERIVED
12119               && derived_inaccessible (nl->sym->ts.u.derived))
12120             {
12121               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
12122                          "components and cannot be member of namelist '%s' at %L",
12123                          nl->sym->name, sym->name, &sym->declared_at);
12124               return FAILURE;
12125             }
12126
12127           /* Types with private components that are defined in the same module.  */
12128           if (nl->sym->ts.type == BT_DERIVED
12129               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
12130               && nl->sym->ts.u.derived->attr.private_comp)
12131             {
12132               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
12133                          "cannot be a member of PUBLIC namelist '%s' at %L",
12134                          nl->sym->name, sym->name, &sym->declared_at);
12135               return FAILURE;
12136             }
12137         }
12138     }
12139
12140
12141   /* 14.1.2 A module or internal procedure represent local entities
12142      of the same type as a namelist member and so are not allowed.  */
12143   for (nl = sym->namelist; nl; nl = nl->next)
12144     {
12145       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
12146         continue;
12147
12148       if (nl->sym->attr.function && nl->sym == nl->sym->result)
12149         if ((nl->sym == sym->ns->proc_name)
12150                ||
12151             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
12152           continue;
12153
12154       nlsym = NULL;
12155       if (nl->sym && nl->sym->name)
12156         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
12157       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
12158         {
12159           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
12160                      "attribute in '%s' at %L", nlsym->name,
12161                      &sym->declared_at);
12162           return FAILURE;
12163         }
12164     }
12165
12166   return SUCCESS;
12167 }
12168
12169
12170 static gfc_try
12171 resolve_fl_parameter (gfc_symbol *sym)
12172 {
12173   /* A parameter array's shape needs to be constant.  */
12174   if (sym->as != NULL 
12175       && (sym->as->type == AS_DEFERRED
12176           || is_non_constant_shape_array (sym)))
12177     {
12178       gfc_error ("Parameter array '%s' at %L cannot be automatic "
12179                  "or of deferred shape", sym->name, &sym->declared_at);
12180       return FAILURE;
12181     }
12182
12183   /* Make sure a parameter that has been implicitly typed still
12184      matches the implicit type, since PARAMETER statements can precede
12185      IMPLICIT statements.  */
12186   if (sym->attr.implicit_type
12187       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
12188                                                              sym->ns)))
12189     {
12190       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
12191                  "later IMPLICIT type", sym->name, &sym->declared_at);
12192       return FAILURE;
12193     }
12194
12195   /* Make sure the types of derived parameters are consistent.  This
12196      type checking is deferred until resolution because the type may
12197      refer to a derived type from the host.  */
12198   if (sym->ts.type == BT_DERIVED
12199       && !gfc_compare_types (&sym->ts, &sym->value->ts))
12200     {
12201       gfc_error ("Incompatible derived type in PARAMETER at %L",
12202                  &sym->value->where);
12203       return FAILURE;
12204     }
12205   return SUCCESS;
12206 }
12207
12208
12209 /* Do anything necessary to resolve a symbol.  Right now, we just
12210    assume that an otherwise unknown symbol is a variable.  This sort
12211    of thing commonly happens for symbols in module.  */
12212
12213 static void
12214 resolve_symbol (gfc_symbol *sym)
12215 {
12216   int check_constant, mp_flag;
12217   gfc_symtree *symtree;
12218   gfc_symtree *this_symtree;
12219   gfc_namespace *ns;
12220   gfc_component *c;
12221   symbol_attribute class_attr;
12222   gfc_array_spec *as;
12223
12224   if (sym->attr.flavor == FL_UNKNOWN)
12225     {
12226
12227     /* If we find that a flavorless symbol is an interface in one of the
12228        parent namespaces, find its symtree in this namespace, free the
12229        symbol and set the symtree to point to the interface symbol.  */
12230       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
12231         {
12232           symtree = gfc_find_symtree (ns->sym_root, sym->name);
12233           if (symtree && (symtree->n.sym->generic ||
12234                           (symtree->n.sym->attr.flavor == FL_PROCEDURE
12235                            && sym->ns->construct_entities)))
12236             {
12237               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
12238                                                sym->name);
12239               gfc_release_symbol (sym);
12240               symtree->n.sym->refs++;
12241               this_symtree->n.sym = symtree->n.sym;
12242               return;
12243             }
12244         }
12245
12246       /* Otherwise give it a flavor according to such attributes as
12247          it has.  */
12248       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
12249         sym->attr.flavor = FL_VARIABLE;
12250       else
12251         {
12252           sym->attr.flavor = FL_PROCEDURE;
12253           if (sym->attr.dimension)
12254             sym->attr.function = 1;
12255         }
12256     }
12257
12258   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
12259     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
12260
12261   if (sym->attr.procedure && sym->ts.interface
12262       && sym->attr.if_source != IFSRC_DECL
12263       && resolve_procedure_interface (sym) == FAILURE)
12264     return;
12265
12266   if (sym->attr.is_protected && !sym->attr.proc_pointer
12267       && (sym->attr.procedure || sym->attr.external))
12268     {
12269       if (sym->attr.external)
12270         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
12271                    "at %L", &sym->declared_at);
12272       else
12273         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
12274                    "at %L", &sym->declared_at);
12275
12276       return;
12277     }
12278
12279   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
12280     return;
12281
12282   /* Symbols that are module procedures with results (functions) have
12283      the types and array specification copied for type checking in
12284      procedures that call them, as well as for saving to a module
12285      file.  These symbols can't stand the scrutiny that their results
12286      can.  */
12287   mp_flag = (sym->result != NULL && sym->result != sym);
12288
12289   /* Make sure that the intrinsic is consistent with its internal 
12290      representation. This needs to be done before assigning a default 
12291      type to avoid spurious warnings.  */
12292   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
12293       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
12294     return;
12295
12296   /* Resolve associate names.  */
12297   if (sym->assoc)
12298     resolve_assoc_var (sym, true);
12299
12300   /* Assign default type to symbols that need one and don't have one.  */
12301   if (sym->ts.type == BT_UNKNOWN)
12302     {
12303       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
12304         {
12305           gfc_set_default_type (sym, 1, NULL);
12306         }
12307
12308       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
12309           && !sym->attr.function && !sym->attr.subroutine
12310           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
12311         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
12312
12313       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12314         {
12315           /* The specific case of an external procedure should emit an error
12316              in the case that there is no implicit type.  */
12317           if (!mp_flag)
12318             gfc_set_default_type (sym, sym->attr.external, NULL);
12319           else
12320             {
12321               /* Result may be in another namespace.  */
12322               resolve_symbol (sym->result);
12323
12324               if (!sym->result->attr.proc_pointer)
12325                 {
12326                   sym->ts = sym->result->ts;
12327                   sym->as = gfc_copy_array_spec (sym->result->as);
12328                   sym->attr.dimension = sym->result->attr.dimension;
12329                   sym->attr.pointer = sym->result->attr.pointer;
12330                   sym->attr.allocatable = sym->result->attr.allocatable;
12331                   sym->attr.contiguous = sym->result->attr.contiguous;
12332                 }
12333             }
12334         }
12335     }
12336   else if (mp_flag && sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12337     gfc_resolve_array_spec (sym->result->as, false);
12338
12339   if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
12340     {
12341       as = CLASS_DATA (sym)->as;
12342       class_attr = CLASS_DATA (sym)->attr;
12343       class_attr.pointer = class_attr.class_pointer;
12344     }
12345   else
12346     {
12347       class_attr = sym->attr;
12348       as = sym->as;
12349     }
12350
12351   /* F2008, C530. */
12352   if (sym->attr.contiguous
12353       && (!class_attr.dimension
12354           || (as->type != AS_ASSUMED_SHAPE && !class_attr.pointer)))
12355     {
12356       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
12357                   "array pointer or an assumed-shape array", sym->name,
12358                   &sym->declared_at);
12359       return;
12360     }
12361
12362   /* Assumed size arrays and assumed shape arrays must be dummy
12363      arguments.  Array-spec's of implied-shape should have been resolved to
12364      AS_EXPLICIT already.  */
12365
12366   if (as)
12367     {
12368       gcc_assert (as->type != AS_IMPLIED_SHAPE);
12369       if (((as->type == AS_ASSUMED_SIZE && !as->cp_was_assumed)
12370            || as->type == AS_ASSUMED_SHAPE)
12371           && sym->attr.dummy == 0)
12372         {
12373           if (as->type == AS_ASSUMED_SIZE)
12374             gfc_error ("Assumed size array at %L must be a dummy argument",
12375                        &sym->declared_at);
12376           else
12377             gfc_error ("Assumed shape array at %L must be a dummy argument",
12378                        &sym->declared_at);
12379           return;
12380         }
12381     }
12382
12383   /* Make sure symbols with known intent or optional are really dummy
12384      variable.  Because of ENTRY statement, this has to be deferred
12385      until resolution time.  */
12386
12387   if (!sym->attr.dummy
12388       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
12389     {
12390       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
12391       return;
12392     }
12393
12394   if (sym->attr.value && !sym->attr.dummy)
12395     {
12396       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
12397                  "it is not a dummy argument", sym->name, &sym->declared_at);
12398       return;
12399     }
12400
12401   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
12402     {
12403       gfc_charlen *cl = sym->ts.u.cl;
12404       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
12405         {
12406           gfc_error ("Character dummy variable '%s' at %L with VALUE "
12407                      "attribute must have constant length",
12408                      sym->name, &sym->declared_at);
12409           return;
12410         }
12411
12412       if (sym->ts.is_c_interop
12413           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
12414         {
12415           gfc_error ("C interoperable character dummy variable '%s' at %L "
12416                      "with VALUE attribute must have length one",
12417                      sym->name, &sym->declared_at);
12418           return;
12419         }
12420     }
12421
12422   if (sym->ts.type == BT_DERIVED && !sym->attr.is_iso_c
12423       && sym->ts.u.derived->attr.generic)
12424     {
12425       sym->ts.u.derived = gfc_find_dt_in_generic (sym->ts.u.derived);
12426       if (!sym->ts.u.derived)
12427         {
12428           gfc_error ("The derived type '%s' at %L is of type '%s', "
12429                      "which has not been defined", sym->name,
12430                      &sym->declared_at, sym->ts.u.derived->name);
12431           sym->ts.type = BT_UNKNOWN;
12432           return;
12433         }
12434     }
12435
12436   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
12437      do this for something that was implicitly typed because that is handled
12438      in gfc_set_default_type.  Handle dummy arguments and procedure
12439      definitions separately.  Also, anything that is use associated is not
12440      handled here but instead is handled in the module it is declared in.
12441      Finally, derived type definitions are allowed to be BIND(C) since that
12442      only implies that they're interoperable, and they are checked fully for
12443      interoperability when a variable is declared of that type.  */
12444   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
12445       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
12446       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
12447     {
12448       gfc_try t = SUCCESS;
12449       
12450       /* First, make sure the variable is declared at the
12451          module-level scope (J3/04-007, Section 15.3).  */
12452       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
12453           sym->attr.in_common == 0)
12454         {
12455           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
12456                      "is neither a COMMON block nor declared at the "
12457                      "module level scope", sym->name, &(sym->declared_at));
12458           t = FAILURE;
12459         }
12460       else if (sym->common_head != NULL)
12461         {
12462           t = verify_com_block_vars_c_interop (sym->common_head);
12463         }
12464       else
12465         {
12466           /* If type() declaration, we need to verify that the components
12467              of the given type are all C interoperable, etc.  */
12468           if (sym->ts.type == BT_DERIVED &&
12469               sym->ts.u.derived->attr.is_c_interop != 1)
12470             {
12471               /* Make sure the user marked the derived type as BIND(C).  If
12472                  not, call the verify routine.  This could print an error
12473                  for the derived type more than once if multiple variables
12474                  of that type are declared.  */
12475               if (sym->ts.u.derived->attr.is_bind_c != 1)
12476                 verify_bind_c_derived_type (sym->ts.u.derived);
12477               t = FAILURE;
12478             }
12479           
12480           /* Verify the variable itself as C interoperable if it
12481              is BIND(C).  It is not possible for this to succeed if
12482              the verify_bind_c_derived_type failed, so don't have to handle
12483              any error returned by verify_bind_c_derived_type.  */
12484           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
12485                                  sym->common_block);
12486         }
12487
12488       if (t == FAILURE)
12489         {
12490           /* clear the is_bind_c flag to prevent reporting errors more than
12491              once if something failed.  */
12492           sym->attr.is_bind_c = 0;
12493           return;
12494         }
12495     }
12496
12497   /* If a derived type symbol has reached this point, without its
12498      type being declared, we have an error.  Notice that most
12499      conditions that produce undefined derived types have already
12500      been dealt with.  However, the likes of:
12501      implicit type(t) (t) ..... call foo (t) will get us here if
12502      the type is not declared in the scope of the implicit
12503      statement. Change the type to BT_UNKNOWN, both because it is so
12504      and to prevent an ICE.  */
12505   if (sym->ts.type == BT_DERIVED && !sym->attr.is_iso_c
12506       && sym->ts.u.derived->components == NULL
12507       && !sym->ts.u.derived->attr.zero_comp)
12508     {
12509       gfc_error ("The derived type '%s' at %L is of type '%s', "
12510                  "which has not been defined", sym->name,
12511                   &sym->declared_at, sym->ts.u.derived->name);
12512       sym->ts.type = BT_UNKNOWN;
12513       return;
12514     }
12515
12516   /* Make sure that the derived type has been resolved and that the
12517      derived type is visible in the symbol's namespace, if it is a
12518      module function and is not PRIVATE.  */
12519   if (sym->ts.type == BT_DERIVED
12520         && sym->ts.u.derived->attr.use_assoc
12521         && sym->ns->proc_name
12522         && sym->ns->proc_name->attr.flavor == FL_MODULE
12523         && resolve_fl_derived (sym->ts.u.derived) == FAILURE)
12524     return;
12525
12526   /* Unless the derived-type declaration is use associated, Fortran 95
12527      does not allow public entries of private derived types.
12528      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
12529      161 in 95-006r3.  */
12530   if (sym->ts.type == BT_DERIVED
12531       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
12532       && !sym->ts.u.derived->attr.use_assoc
12533       && gfc_check_symbol_access (sym)
12534       && !gfc_check_symbol_access (sym->ts.u.derived)
12535       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
12536                          "of PRIVATE derived type '%s'",
12537                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
12538                          : "variable", sym->name, &sym->declared_at,
12539                          sym->ts.u.derived->name) == FAILURE)
12540     return;
12541
12542   /* F2008, C1302.  */
12543   if (sym->ts.type == BT_DERIVED
12544       && ((sym->ts.u.derived->from_intmod == INTMOD_ISO_FORTRAN_ENV
12545            && sym->ts.u.derived->intmod_sym_id == ISOFORTRAN_LOCK_TYPE)
12546           || sym->ts.u.derived->attr.lock_comp)
12547       && !sym->attr.codimension && !sym->ts.u.derived->attr.coarray_comp)
12548     {
12549       gfc_error ("Variable %s at %L of type LOCK_TYPE or with subcomponent of "
12550                  "type LOCK_TYPE must be a coarray", sym->name,
12551                  &sym->declared_at);
12552       return;
12553     }
12554
12555   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
12556      default initialization is defined (5.1.2.4.4).  */
12557   if (sym->ts.type == BT_DERIVED
12558       && sym->attr.dummy
12559       && sym->attr.intent == INTENT_OUT
12560       && sym->as
12561       && sym->as->type == AS_ASSUMED_SIZE)
12562     {
12563       for (c = sym->ts.u.derived->components; c; c = c->next)
12564         {
12565           if (c->initializer)
12566             {
12567               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
12568                          "ASSUMED SIZE and so cannot have a default initializer",
12569                          sym->name, &sym->declared_at);
12570               return;
12571             }
12572         }
12573     }
12574
12575   /* F2008, C542.  */
12576   if (sym->ts.type == BT_DERIVED && sym->attr.dummy
12577       && sym->attr.intent == INTENT_OUT && sym->attr.lock_comp)
12578     {
12579       gfc_error ("Dummy argument '%s' at %L of LOCK_TYPE shall not be "
12580                  "INTENT(OUT)", sym->name, &sym->declared_at);
12581       return;
12582     }
12583
12584   /* F2008, C525.  */
12585   if ((((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12586          || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12587              && CLASS_DATA (sym)->attr.coarray_comp))
12588        || class_attr.codimension)
12589       && (sym->attr.result || sym->result == sym))
12590     {
12591       gfc_error ("Function result '%s' at %L shall not be a coarray or have "
12592                  "a coarray component", sym->name, &sym->declared_at);
12593       return;
12594     }
12595
12596   /* F2008, C524.  */
12597   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
12598       && sym->ts.u.derived->ts.is_iso_c)
12599     {
12600       gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12601                  "shall not be a coarray", sym->name, &sym->declared_at);
12602       return;
12603     }
12604
12605   /* F2008, C525.  */
12606   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12607         || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12608             && CLASS_DATA (sym)->attr.coarray_comp))
12609       && (class_attr.codimension || class_attr.pointer || class_attr.dimension
12610           || class_attr.allocatable))
12611     {
12612       gfc_error ("Variable '%s' at %L with coarray component "
12613                  "shall be a nonpointer, nonallocatable scalar",
12614                  sym->name, &sym->declared_at);
12615       return;
12616     }
12617
12618   /* F2008, C526.  The function-result case was handled above.  */
12619   if (class_attr.codimension
12620       && !(class_attr.allocatable || sym->attr.dummy || sym->attr.save
12621            || sym->attr.select_type_temporary
12622            || sym->ns->save_all
12623            || sym->ns->proc_name->attr.flavor == FL_MODULE
12624            || sym->ns->proc_name->attr.is_main_program
12625            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
12626     {
12627       gfc_error ("Variable '%s' at %L is a coarray and is not ALLOCATABLE, SAVE "
12628                  "nor a dummy argument", sym->name, &sym->declared_at);
12629       return;
12630     }
12631   /* F2008, C528.  */
12632   else if (class_attr.codimension && !sym->attr.select_type_temporary
12633            && !class_attr.allocatable && as && as->cotype == AS_DEFERRED)
12634     {
12635       gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
12636                  "deferred shape", sym->name, &sym->declared_at);
12637       return;
12638     }
12639   else if (class_attr.codimension && class_attr.allocatable && as
12640            && (as->cotype != AS_DEFERRED || as->type != AS_DEFERRED))
12641     {
12642       gfc_error ("Allocatable coarray variable '%s' at %L must have "
12643                  "deferred shape", sym->name, &sym->declared_at);
12644       return;
12645     }
12646
12647   /* F2008, C541.  */
12648   if ((((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12649         || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12650             && CLASS_DATA (sym)->attr.coarray_comp))
12651        || (class_attr.codimension && class_attr.allocatable))
12652       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
12653     {
12654       gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
12655                  "allocatable coarray or have coarray components",
12656                  sym->name, &sym->declared_at);
12657       return;
12658     }
12659
12660   if (class_attr.codimension && sym->attr.dummy
12661       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
12662     {
12663       gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
12664                  "procedure '%s'", sym->name, &sym->declared_at,
12665                  sym->ns->proc_name->name);
12666       return;
12667     }
12668
12669   switch (sym->attr.flavor)
12670     {
12671     case FL_VARIABLE:
12672       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
12673         return;
12674       break;
12675
12676     case FL_PROCEDURE:
12677       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
12678         return;
12679       break;
12680
12681     case FL_NAMELIST:
12682       if (resolve_fl_namelist (sym) == FAILURE)
12683         return;
12684       break;
12685
12686     case FL_PARAMETER:
12687       if (resolve_fl_parameter (sym) == FAILURE)
12688         return;
12689       break;
12690
12691     default:
12692       break;
12693     }
12694
12695   /* Resolve array specifier. Check as well some constraints
12696      on COMMON blocks.  */
12697
12698   check_constant = sym->attr.in_common && !sym->attr.pointer;
12699
12700   /* Set the formal_arg_flag so that check_conflict will not throw
12701      an error for host associated variables in the specification
12702      expression for an array_valued function.  */
12703   if (sym->attr.function && sym->as)
12704     formal_arg_flag = 1;
12705
12706   gfc_resolve_array_spec (sym->as, check_constant);
12707
12708   formal_arg_flag = 0;
12709
12710   /* Resolve formal namespaces.  */
12711   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
12712       && !sym->attr.contained && !sym->attr.intrinsic)
12713     gfc_resolve (sym->formal_ns);
12714
12715   /* Make sure the formal namespace is present.  */
12716   if (sym->formal && !sym->formal_ns)
12717     {
12718       gfc_formal_arglist *formal = sym->formal;
12719       while (formal && !formal->sym)
12720         formal = formal->next;
12721
12722       if (formal)
12723         {
12724           sym->formal_ns = formal->sym->ns;
12725           sym->formal_ns->refs++;
12726         }
12727     }
12728
12729   /* Check threadprivate restrictions.  */
12730   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
12731       && (!sym->attr.in_common
12732           && sym->module == NULL
12733           && (sym->ns->proc_name == NULL
12734               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
12735     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
12736
12737   /* If we have come this far we can apply default-initializers, as
12738      described in 14.7.5, to those variables that have not already
12739      been assigned one.  */
12740   if (sym->ts.type == BT_DERIVED
12741       && sym->ns == gfc_current_ns
12742       && !sym->value
12743       && !sym->attr.allocatable
12744       && !sym->attr.alloc_comp)
12745     {
12746       symbol_attribute *a = &sym->attr;
12747
12748       if ((!a->save && !a->dummy && !a->pointer
12749            && !a->in_common && !a->use_assoc
12750            && (a->referenced || a->result)
12751            && !(a->function && sym != sym->result))
12752           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
12753         apply_default_init (sym);
12754     }
12755
12756   if (sym->ts.type == BT_CLASS && sym->ns == gfc_current_ns
12757       && sym->attr.dummy && sym->attr.intent == INTENT_OUT
12758       && !CLASS_DATA (sym)->attr.class_pointer
12759       && !CLASS_DATA (sym)->attr.allocatable)
12760     apply_default_init (sym);
12761
12762   /* If this symbol has a type-spec, check it.  */
12763   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
12764       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
12765     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
12766           == FAILURE)
12767       return;
12768 }
12769
12770
12771 /************* Resolve DATA statements *************/
12772
12773 static struct
12774 {
12775   gfc_data_value *vnode;
12776   mpz_t left;
12777 }
12778 values;
12779
12780
12781 /* Advance the values structure to point to the next value in the data list.  */
12782
12783 static gfc_try
12784 next_data_value (void)
12785 {
12786   while (mpz_cmp_ui (values.left, 0) == 0)
12787     {
12788
12789       if (values.vnode->next == NULL)
12790         return FAILURE;
12791
12792       values.vnode = values.vnode->next;
12793       mpz_set (values.left, values.vnode->repeat);
12794     }
12795
12796   return SUCCESS;
12797 }
12798
12799
12800 static gfc_try
12801 check_data_variable (gfc_data_variable *var, locus *where)
12802 {
12803   gfc_expr *e;
12804   mpz_t size;
12805   mpz_t offset;
12806   gfc_try t;
12807   ar_type mark = AR_UNKNOWN;
12808   int i;
12809   mpz_t section_index[GFC_MAX_DIMENSIONS];
12810   gfc_ref *ref;
12811   gfc_array_ref *ar;
12812   gfc_symbol *sym;
12813   int has_pointer;
12814
12815   if (gfc_resolve_expr (var->expr) == FAILURE)
12816     return FAILURE;
12817
12818   ar = NULL;
12819   mpz_init_set_si (offset, 0);
12820   e = var->expr;
12821
12822   if (e->expr_type != EXPR_VARIABLE)
12823     gfc_internal_error ("check_data_variable(): Bad expression");
12824
12825   sym = e->symtree->n.sym;
12826
12827   if (sym->ns->is_block_data && !sym->attr.in_common)
12828     {
12829       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
12830                  sym->name, &sym->declared_at);
12831     }
12832
12833   if (e->ref == NULL && sym->as)
12834     {
12835       gfc_error ("DATA array '%s' at %L must be specified in a previous"
12836                  " declaration", sym->name, where);
12837       return FAILURE;
12838     }
12839
12840   has_pointer = sym->attr.pointer;
12841
12842   if (gfc_is_coindexed (e))
12843     {
12844       gfc_error ("DATA element '%s' at %L cannot have a coindex", sym->name,
12845                  where);
12846       return FAILURE;
12847     }
12848
12849   for (ref = e->ref; ref; ref = ref->next)
12850     {
12851       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
12852         has_pointer = 1;
12853
12854       if (has_pointer
12855             && ref->type == REF_ARRAY
12856             && ref->u.ar.type != AR_FULL)
12857           {
12858             gfc_error ("DATA element '%s' at %L is a pointer and so must "
12859                         "be a full array", sym->name, where);
12860             return FAILURE;
12861           }
12862     }
12863
12864   if (e->rank == 0 || has_pointer)
12865     {
12866       mpz_init_set_ui (size, 1);
12867       ref = NULL;
12868     }
12869   else
12870     {
12871       ref = e->ref;
12872
12873       /* Find the array section reference.  */
12874       for (ref = e->ref; ref; ref = ref->next)
12875         {
12876           if (ref->type != REF_ARRAY)
12877             continue;
12878           if (ref->u.ar.type == AR_ELEMENT)
12879             continue;
12880           break;
12881         }
12882       gcc_assert (ref);
12883
12884       /* Set marks according to the reference pattern.  */
12885       switch (ref->u.ar.type)
12886         {
12887         case AR_FULL:
12888           mark = AR_FULL;
12889           break;
12890
12891         case AR_SECTION:
12892           ar = &ref->u.ar;
12893           /* Get the start position of array section.  */
12894           gfc_get_section_index (ar, section_index, &offset);
12895           mark = AR_SECTION;
12896           break;
12897
12898         default:
12899           gcc_unreachable ();
12900         }
12901
12902       if (gfc_array_size (e, &size) == FAILURE)
12903         {
12904           gfc_error ("Nonconstant array section at %L in DATA statement",
12905                      &e->where);
12906           mpz_clear (offset);
12907           return FAILURE;
12908         }
12909     }
12910
12911   t = SUCCESS;
12912
12913   while (mpz_cmp_ui (size, 0) > 0)
12914     {
12915       if (next_data_value () == FAILURE)
12916         {
12917           gfc_error ("DATA statement at %L has more variables than values",
12918                      where);
12919           t = FAILURE;
12920           break;
12921         }
12922
12923       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
12924       if (t == FAILURE)
12925         break;
12926
12927       /* If we have more than one element left in the repeat count,
12928          and we have more than one element left in the target variable,
12929          then create a range assignment.  */
12930       /* FIXME: Only done for full arrays for now, since array sections
12931          seem tricky.  */
12932       if (mark == AR_FULL && ref && ref->next == NULL
12933           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
12934         {
12935           mpz_t range;
12936
12937           if (mpz_cmp (size, values.left) >= 0)
12938             {
12939               mpz_init_set (range, values.left);
12940               mpz_sub (size, size, values.left);
12941               mpz_set_ui (values.left, 0);
12942             }
12943           else
12944             {
12945               mpz_init_set (range, size);
12946               mpz_sub (values.left, values.left, size);
12947               mpz_set_ui (size, 0);
12948             }
12949
12950           t = gfc_assign_data_value (var->expr, values.vnode->expr,
12951                                      offset, &range);
12952
12953           mpz_add (offset, offset, range);
12954           mpz_clear (range);
12955
12956           if (t == FAILURE)
12957             break;
12958         }
12959
12960       /* Assign initial value to symbol.  */
12961       else
12962         {
12963           mpz_sub_ui (values.left, values.left, 1);
12964           mpz_sub_ui (size, size, 1);
12965
12966           t = gfc_assign_data_value (var->expr, values.vnode->expr,
12967                                      offset, NULL);
12968           if (t == FAILURE)
12969             break;
12970
12971           if (mark == AR_FULL)
12972             mpz_add_ui (offset, offset, 1);
12973
12974           /* Modify the array section indexes and recalculate the offset
12975              for next element.  */
12976           else if (mark == AR_SECTION)
12977             gfc_advance_section (section_index, ar, &offset);
12978         }
12979     }
12980
12981   if (mark == AR_SECTION)
12982     {
12983       for (i = 0; i < ar->dimen; i++)
12984         mpz_clear (section_index[i]);
12985     }
12986
12987   mpz_clear (size);
12988   mpz_clear (offset);
12989
12990   return t;
12991 }
12992
12993
12994 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
12995
12996 /* Iterate over a list of elements in a DATA statement.  */
12997
12998 static gfc_try
12999 traverse_data_list (gfc_data_variable *var, locus *where)
13000 {
13001   mpz_t trip;
13002   iterator_stack frame;
13003   gfc_expr *e, *start, *end, *step;
13004   gfc_try retval = SUCCESS;
13005
13006   mpz_init (frame.value);
13007   mpz_init (trip);
13008
13009   start = gfc_copy_expr (var->iter.start);
13010   end = gfc_copy_expr (var->iter.end);
13011   step = gfc_copy_expr (var->iter.step);
13012
13013   if (gfc_simplify_expr (start, 1) == FAILURE
13014       || start->expr_type != EXPR_CONSTANT)
13015     {
13016       gfc_error ("start of implied-do loop at %L could not be "
13017                  "simplified to a constant value", &start->where);
13018       retval = FAILURE;
13019       goto cleanup;
13020     }
13021   if (gfc_simplify_expr (end, 1) == FAILURE
13022       || end->expr_type != EXPR_CONSTANT)
13023     {
13024       gfc_error ("end of implied-do loop at %L could not be "
13025                  "simplified to a constant value", &start->where);
13026       retval = FAILURE;
13027       goto cleanup;
13028     }
13029   if (gfc_simplify_expr (step, 1) == FAILURE
13030       || step->expr_type != EXPR_CONSTANT)
13031     {
13032       gfc_error ("step of implied-do loop at %L could not be "
13033                  "simplified to a constant value", &start->where);
13034       retval = FAILURE;
13035       goto cleanup;
13036     }
13037
13038   mpz_set (trip, end->value.integer);
13039   mpz_sub (trip, trip, start->value.integer);
13040   mpz_add (trip, trip, step->value.integer);
13041
13042   mpz_div (trip, trip, step->value.integer);
13043
13044   mpz_set (frame.value, start->value.integer);
13045
13046   frame.prev = iter_stack;
13047   frame.variable = var->iter.var->symtree;
13048   iter_stack = &frame;
13049
13050   while (mpz_cmp_ui (trip, 0) > 0)
13051     {
13052       if (traverse_data_var (var->list, where) == FAILURE)
13053         {
13054           retval = FAILURE;
13055           goto cleanup;
13056         }
13057
13058       e = gfc_copy_expr (var->expr);
13059       if (gfc_simplify_expr (e, 1) == FAILURE)
13060         {
13061           gfc_free_expr (e);
13062           retval = FAILURE;
13063           goto cleanup;
13064         }
13065
13066       mpz_add (frame.value, frame.value, step->value.integer);
13067
13068       mpz_sub_ui (trip, trip, 1);
13069     }
13070
13071 cleanup:
13072   mpz_clear (frame.value);
13073   mpz_clear (trip);
13074
13075   gfc_free_expr (start);
13076   gfc_free_expr (end);
13077   gfc_free_expr (step);
13078
13079   iter_stack = frame.prev;
13080   return retval;
13081 }
13082
13083
13084 /* Type resolve variables in the variable list of a DATA statement.  */
13085
13086 static gfc_try
13087 traverse_data_var (gfc_data_variable *var, locus *where)
13088 {
13089   gfc_try t;
13090
13091   for (; var; var = var->next)
13092     {
13093       if (var->expr == NULL)
13094         t = traverse_data_list (var, where);
13095       else
13096         t = check_data_variable (var, where);
13097
13098       if (t == FAILURE)
13099         return FAILURE;
13100     }
13101
13102   return SUCCESS;
13103 }
13104
13105
13106 /* Resolve the expressions and iterators associated with a data statement.
13107    This is separate from the assignment checking because data lists should
13108    only be resolved once.  */
13109
13110 static gfc_try
13111 resolve_data_variables (gfc_data_variable *d)
13112 {
13113   for (; d; d = d->next)
13114     {
13115       if (d->list == NULL)
13116         {
13117           if (gfc_resolve_expr (d->expr) == FAILURE)
13118             return FAILURE;
13119         }
13120       else
13121         {
13122           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
13123             return FAILURE;
13124
13125           if (resolve_data_variables (d->list) == FAILURE)
13126             return FAILURE;
13127         }
13128     }
13129
13130   return SUCCESS;
13131 }
13132
13133
13134 /* Resolve a single DATA statement.  We implement this by storing a pointer to
13135    the value list into static variables, and then recursively traversing the
13136    variables list, expanding iterators and such.  */
13137
13138 static void
13139 resolve_data (gfc_data *d)
13140 {
13141
13142   if (resolve_data_variables (d->var) == FAILURE)
13143     return;
13144
13145   values.vnode = d->value;
13146   if (d->value == NULL)
13147     mpz_set_ui (values.left, 0);
13148   else
13149     mpz_set (values.left, d->value->repeat);
13150
13151   if (traverse_data_var (d->var, &d->where) == FAILURE)
13152     return;
13153
13154   /* At this point, we better not have any values left.  */
13155
13156   if (next_data_value () == SUCCESS)
13157     gfc_error ("DATA statement at %L has more values than variables",
13158                &d->where);
13159 }
13160
13161
13162 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
13163    accessed by host or use association, is a dummy argument to a pure function,
13164    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
13165    is storage associated with any such variable, shall not be used in the
13166    following contexts: (clients of this function).  */
13167
13168 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
13169    procedure.  Returns zero if assignment is OK, nonzero if there is a
13170    problem.  */
13171 int
13172 gfc_impure_variable (gfc_symbol *sym)
13173 {
13174   gfc_symbol *proc;
13175   gfc_namespace *ns;
13176
13177   if (sym->attr.use_assoc || sym->attr.in_common)
13178     return 1;
13179
13180   /* Check if the symbol's ns is inside the pure procedure.  */
13181   for (ns = gfc_current_ns; ns; ns = ns->parent)
13182     {
13183       if (ns == sym->ns)
13184         break;
13185       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
13186         return 1;
13187     }
13188
13189   proc = sym->ns->proc_name;
13190   if (sym->attr.dummy && gfc_pure (proc)
13191         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
13192                 ||
13193              proc->attr.function))
13194     return 1;
13195
13196   /* TODO: Sort out what can be storage associated, if anything, and include
13197      it here.  In principle equivalences should be scanned but it does not
13198      seem to be possible to storage associate an impure variable this way.  */
13199   return 0;
13200 }
13201
13202
13203 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
13204    current namespace is inside a pure procedure.  */
13205
13206 int
13207 gfc_pure (gfc_symbol *sym)
13208 {
13209   symbol_attribute attr;
13210   gfc_namespace *ns;
13211
13212   if (sym == NULL)
13213     {
13214       /* Check if the current namespace or one of its parents
13215         belongs to a pure procedure.  */
13216       for (ns = gfc_current_ns; ns; ns = ns->parent)
13217         {
13218           sym = ns->proc_name;
13219           if (sym == NULL)
13220             return 0;
13221           attr = sym->attr;
13222           if (attr.flavor == FL_PROCEDURE && attr.pure)
13223             return 1;
13224         }
13225       return 0;
13226     }
13227
13228   attr = sym->attr;
13229
13230   return attr.flavor == FL_PROCEDURE && attr.pure;
13231 }
13232
13233
13234 /* Test whether a symbol is implicitly pure or not.  For a NULL pointer,
13235    checks if the current namespace is implicitly pure.  Note that this
13236    function returns false for a PURE procedure.  */
13237
13238 int
13239 gfc_implicit_pure (gfc_symbol *sym)
13240 {
13241   gfc_namespace *ns;
13242
13243   if (sym == NULL)
13244     {
13245       /* Check if the current procedure is implicit_pure.  Walk up
13246          the procedure list until we find a procedure.  */
13247       for (ns = gfc_current_ns; ns; ns = ns->parent)
13248         {
13249           sym = ns->proc_name;
13250           if (sym == NULL)
13251             return 0;
13252           
13253           if (sym->attr.flavor == FL_PROCEDURE)
13254             break;
13255         }
13256     }
13257   
13258   return sym->attr.flavor == FL_PROCEDURE && sym->attr.implicit_pure
13259     && !sym->attr.pure;
13260 }
13261
13262
13263 /* Test whether the current procedure is elemental or not.  */
13264
13265 int
13266 gfc_elemental (gfc_symbol *sym)
13267 {
13268   symbol_attribute attr;
13269
13270   if (sym == NULL)
13271     sym = gfc_current_ns->proc_name;
13272   if (sym == NULL)
13273     return 0;
13274   attr = sym->attr;
13275
13276   return attr.flavor == FL_PROCEDURE && attr.elemental;
13277 }
13278
13279
13280 /* Warn about unused labels.  */
13281
13282 static void
13283 warn_unused_fortran_label (gfc_st_label *label)
13284 {
13285   if (label == NULL)
13286     return;
13287
13288   warn_unused_fortran_label (label->left);
13289
13290   if (label->defined == ST_LABEL_UNKNOWN)
13291     return;
13292
13293   switch (label->referenced)
13294     {
13295     case ST_LABEL_UNKNOWN:
13296       gfc_warning ("Label %d at %L defined but not used", label->value,
13297                    &label->where);
13298       break;
13299
13300     case ST_LABEL_BAD_TARGET:
13301       gfc_warning ("Label %d at %L defined but cannot be used",
13302                    label->value, &label->where);
13303       break;
13304
13305     default:
13306       break;
13307     }
13308
13309   warn_unused_fortran_label (label->right);
13310 }
13311
13312
13313 /* Returns the sequence type of a symbol or sequence.  */
13314
13315 static seq_type
13316 sequence_type (gfc_typespec ts)
13317 {
13318   seq_type result;
13319   gfc_component *c;
13320
13321   switch (ts.type)
13322   {
13323     case BT_DERIVED:
13324
13325       if (ts.u.derived->components == NULL)
13326         return SEQ_NONDEFAULT;
13327
13328       result = sequence_type (ts.u.derived->components->ts);
13329       for (c = ts.u.derived->components->next; c; c = c->next)
13330         if (sequence_type (c->ts) != result)
13331           return SEQ_MIXED;
13332
13333       return result;
13334
13335     case BT_CHARACTER:
13336       if (ts.kind != gfc_default_character_kind)
13337           return SEQ_NONDEFAULT;
13338
13339       return SEQ_CHARACTER;
13340
13341     case BT_INTEGER:
13342       if (ts.kind != gfc_default_integer_kind)
13343           return SEQ_NONDEFAULT;
13344
13345       return SEQ_NUMERIC;
13346
13347     case BT_REAL:
13348       if (!(ts.kind == gfc_default_real_kind
13349             || ts.kind == gfc_default_double_kind))
13350           return SEQ_NONDEFAULT;
13351
13352       return SEQ_NUMERIC;
13353
13354     case BT_COMPLEX:
13355       if (ts.kind != gfc_default_complex_kind)
13356           return SEQ_NONDEFAULT;
13357
13358       return SEQ_NUMERIC;
13359
13360     case BT_LOGICAL:
13361       if (ts.kind != gfc_default_logical_kind)
13362           return SEQ_NONDEFAULT;
13363
13364       return SEQ_NUMERIC;
13365
13366     default:
13367       return SEQ_NONDEFAULT;
13368   }
13369 }
13370
13371
13372 /* Resolve derived type EQUIVALENCE object.  */
13373
13374 static gfc_try
13375 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
13376 {
13377   gfc_component *c = derived->components;
13378
13379   if (!derived)
13380     return SUCCESS;
13381
13382   /* Shall not be an object of nonsequence derived type.  */
13383   if (!derived->attr.sequence)
13384     {
13385       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
13386                  "attribute to be an EQUIVALENCE object", sym->name,
13387                  &e->where);
13388       return FAILURE;
13389     }
13390
13391   /* Shall not have allocatable components.  */
13392   if (derived->attr.alloc_comp)
13393     {
13394       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
13395                  "components to be an EQUIVALENCE object",sym->name,
13396                  &e->where);
13397       return FAILURE;
13398     }
13399
13400   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
13401     {
13402       gfc_error ("Derived type variable '%s' at %L with default "
13403                  "initialization cannot be in EQUIVALENCE with a variable "
13404                  "in COMMON", sym->name, &e->where);
13405       return FAILURE;
13406     }
13407
13408   for (; c ; c = c->next)
13409     {
13410       if (c->ts.type == BT_DERIVED
13411           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
13412         return FAILURE;
13413
13414       /* Shall not be an object of sequence derived type containing a pointer
13415          in the structure.  */
13416       if (c->attr.pointer)
13417         {
13418           gfc_error ("Derived type variable '%s' at %L with pointer "
13419                      "component(s) cannot be an EQUIVALENCE object",
13420                      sym->name, &e->where);
13421           return FAILURE;
13422         }
13423     }
13424   return SUCCESS;
13425 }
13426
13427
13428 /* Resolve equivalence object. 
13429    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
13430    an allocatable array, an object of nonsequence derived type, an object of
13431    sequence derived type containing a pointer at any level of component
13432    selection, an automatic object, a function name, an entry name, a result
13433    name, a named constant, a structure component, or a subobject of any of
13434    the preceding objects.  A substring shall not have length zero.  A
13435    derived type shall not have components with default initialization nor
13436    shall two objects of an equivalence group be initialized.
13437    Either all or none of the objects shall have an protected attribute.
13438    The simple constraints are done in symbol.c(check_conflict) and the rest
13439    are implemented here.  */
13440
13441 static void
13442 resolve_equivalence (gfc_equiv *eq)
13443 {
13444   gfc_symbol *sym;
13445   gfc_symbol *first_sym;
13446   gfc_expr *e;
13447   gfc_ref *r;
13448   locus *last_where = NULL;
13449   seq_type eq_type, last_eq_type;
13450   gfc_typespec *last_ts;
13451   int object, cnt_protected;
13452   const char *msg;
13453
13454   last_ts = &eq->expr->symtree->n.sym->ts;
13455
13456   first_sym = eq->expr->symtree->n.sym;
13457
13458   cnt_protected = 0;
13459
13460   for (object = 1; eq; eq = eq->eq, object++)
13461     {
13462       e = eq->expr;
13463
13464       e->ts = e->symtree->n.sym->ts;
13465       /* match_varspec might not know yet if it is seeing
13466          array reference or substring reference, as it doesn't
13467          know the types.  */
13468       if (e->ref && e->ref->type == REF_ARRAY)
13469         {
13470           gfc_ref *ref = e->ref;
13471           sym = e->symtree->n.sym;
13472
13473           if (sym->attr.dimension)
13474             {
13475               ref->u.ar.as = sym->as;
13476               ref = ref->next;
13477             }
13478
13479           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
13480           if (e->ts.type == BT_CHARACTER
13481               && ref
13482               && ref->type == REF_ARRAY
13483               && ref->u.ar.dimen == 1
13484               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
13485               && ref->u.ar.stride[0] == NULL)
13486             {
13487               gfc_expr *start = ref->u.ar.start[0];
13488               gfc_expr *end = ref->u.ar.end[0];
13489               void *mem = NULL;
13490
13491               /* Optimize away the (:) reference.  */
13492               if (start == NULL && end == NULL)
13493                 {
13494                   if (e->ref == ref)
13495                     e->ref = ref->next;
13496                   else
13497                     e->ref->next = ref->next;
13498                   mem = ref;
13499                 }
13500               else
13501                 {
13502                   ref->type = REF_SUBSTRING;
13503                   if (start == NULL)
13504                     start = gfc_get_int_expr (gfc_default_integer_kind,
13505                                               NULL, 1);
13506                   ref->u.ss.start = start;
13507                   if (end == NULL && e->ts.u.cl)
13508                     end = gfc_copy_expr (e->ts.u.cl->length);
13509                   ref->u.ss.end = end;
13510                   ref->u.ss.length = e->ts.u.cl;
13511                   e->ts.u.cl = NULL;
13512                 }
13513               ref = ref->next;
13514               free (mem);
13515             }
13516
13517           /* Any further ref is an error.  */
13518           if (ref)
13519             {
13520               gcc_assert (ref->type == REF_ARRAY);
13521               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
13522                          &ref->u.ar.where);
13523               continue;
13524             }
13525         }
13526
13527       if (gfc_resolve_expr (e) == FAILURE)
13528         continue;
13529
13530       sym = e->symtree->n.sym;
13531
13532       if (sym->attr.is_protected)
13533         cnt_protected++;
13534       if (cnt_protected > 0 && cnt_protected != object)
13535         {
13536               gfc_error ("Either all or none of the objects in the "
13537                          "EQUIVALENCE set at %L shall have the "
13538                          "PROTECTED attribute",
13539                          &e->where);
13540               break;
13541         }
13542
13543       /* Shall not equivalence common block variables in a PURE procedure.  */
13544       if (sym->ns->proc_name
13545           && sym->ns->proc_name->attr.pure
13546           && sym->attr.in_common)
13547         {
13548           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
13549                      "object in the pure procedure '%s'",
13550                      sym->name, &e->where, sym->ns->proc_name->name);
13551           break;
13552         }
13553
13554       /* Shall not be a named constant.  */
13555       if (e->expr_type == EXPR_CONSTANT)
13556         {
13557           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
13558                      "object", sym->name, &e->where);
13559           continue;
13560         }
13561
13562       if (e->ts.type == BT_DERIVED
13563           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
13564         continue;
13565
13566       /* Check that the types correspond correctly:
13567          Note 5.28:
13568          A numeric sequence structure may be equivalenced to another sequence
13569          structure, an object of default integer type, default real type, double
13570          precision real type, default logical type such that components of the
13571          structure ultimately only become associated to objects of the same
13572          kind. A character sequence structure may be equivalenced to an object
13573          of default character kind or another character sequence structure.
13574          Other objects may be equivalenced only to objects of the same type and
13575          kind parameters.  */
13576
13577       /* Identical types are unconditionally OK.  */
13578       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
13579         goto identical_types;
13580
13581       last_eq_type = sequence_type (*last_ts);
13582       eq_type = sequence_type (sym->ts);
13583
13584       /* Since the pair of objects is not of the same type, mixed or
13585          non-default sequences can be rejected.  */
13586
13587       msg = "Sequence %s with mixed components in EQUIVALENCE "
13588             "statement at %L with different type objects";
13589       if ((object ==2
13590            && last_eq_type == SEQ_MIXED
13591            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
13592               == FAILURE)
13593           || (eq_type == SEQ_MIXED
13594               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13595                                  &e->where) == FAILURE))
13596         continue;
13597
13598       msg = "Non-default type object or sequence %s in EQUIVALENCE "
13599             "statement at %L with objects of different type";
13600       if ((object ==2
13601            && last_eq_type == SEQ_NONDEFAULT
13602            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
13603                               last_where) == FAILURE)
13604           || (eq_type == SEQ_NONDEFAULT
13605               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13606                                  &e->where) == FAILURE))
13607         continue;
13608
13609       msg ="Non-CHARACTER object '%s' in default CHARACTER "
13610            "EQUIVALENCE statement at %L";
13611       if (last_eq_type == SEQ_CHARACTER
13612           && eq_type != SEQ_CHARACTER
13613           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13614                              &e->where) == FAILURE)
13615                 continue;
13616
13617       msg ="Non-NUMERIC object '%s' in default NUMERIC "
13618            "EQUIVALENCE statement at %L";
13619       if (last_eq_type == SEQ_NUMERIC
13620           && eq_type != SEQ_NUMERIC
13621           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13622                              &e->where) == FAILURE)
13623                 continue;
13624
13625   identical_types:
13626       last_ts =&sym->ts;
13627       last_where = &e->where;
13628
13629       if (!e->ref)
13630         continue;
13631
13632       /* Shall not be an automatic array.  */
13633       if (e->ref->type == REF_ARRAY
13634           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
13635         {
13636           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
13637                      "an EQUIVALENCE object", sym->name, &e->where);
13638           continue;
13639         }
13640
13641       r = e->ref;
13642       while (r)
13643         {
13644           /* Shall not be a structure component.  */
13645           if (r->type == REF_COMPONENT)
13646             {
13647               gfc_error ("Structure component '%s' at %L cannot be an "
13648                          "EQUIVALENCE object",
13649                          r->u.c.component->name, &e->where);
13650               break;
13651             }
13652
13653           /* A substring shall not have length zero.  */
13654           if (r->type == REF_SUBSTRING)
13655             {
13656               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
13657                 {
13658                   gfc_error ("Substring at %L has length zero",
13659                              &r->u.ss.start->where);
13660                   break;
13661                 }
13662             }
13663           r = r->next;
13664         }
13665     }
13666 }
13667
13668
13669 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
13670
13671 static void
13672 resolve_fntype (gfc_namespace *ns)
13673 {
13674   gfc_entry_list *el;
13675   gfc_symbol *sym;
13676
13677   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
13678     return;
13679
13680   /* If there are any entries, ns->proc_name is the entry master
13681      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
13682   if (ns->entries)
13683     sym = ns->entries->sym;
13684   else
13685     sym = ns->proc_name;
13686   if (sym->result == sym
13687       && sym->ts.type == BT_UNKNOWN
13688       && gfc_set_default_type (sym, 0, NULL) == FAILURE
13689       && !sym->attr.untyped)
13690     {
13691       gfc_error ("Function '%s' at %L has no IMPLICIT type",
13692                  sym->name, &sym->declared_at);
13693       sym->attr.untyped = 1;
13694     }
13695
13696   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
13697       && !sym->attr.contained
13698       && !gfc_check_symbol_access (sym->ts.u.derived)
13699       && gfc_check_symbol_access (sym))
13700     {
13701       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
13702                       "%L of PRIVATE type '%s'", sym->name,
13703                       &sym->declared_at, sym->ts.u.derived->name);
13704     }
13705
13706     if (ns->entries)
13707     for (el = ns->entries->next; el; el = el->next)
13708       {
13709         if (el->sym->result == el->sym
13710             && el->sym->ts.type == BT_UNKNOWN
13711             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
13712             && !el->sym->attr.untyped)
13713           {
13714             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
13715                        el->sym->name, &el->sym->declared_at);
13716             el->sym->attr.untyped = 1;
13717           }
13718       }
13719 }
13720
13721
13722 /* 12.3.2.1.1 Defined operators.  */
13723
13724 static gfc_try
13725 check_uop_procedure (gfc_symbol *sym, locus where)
13726 {
13727   gfc_formal_arglist *formal;
13728
13729   if (!sym->attr.function)
13730     {
13731       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
13732                  sym->name, &where);
13733       return FAILURE;
13734     }
13735
13736   if (sym->ts.type == BT_CHARACTER
13737       && !(sym->ts.u.cl && sym->ts.u.cl->length)
13738       && !(sym->result && sym->result->ts.u.cl
13739            && sym->result->ts.u.cl->length))
13740     {
13741       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
13742                  "character length", sym->name, &where);
13743       return FAILURE;
13744     }
13745
13746   formal = sym->formal;
13747   if (!formal || !formal->sym)
13748     {
13749       gfc_error ("User operator procedure '%s' at %L must have at least "
13750                  "one argument", sym->name, &where);
13751       return FAILURE;
13752     }
13753
13754   if (formal->sym->attr.intent != INTENT_IN)
13755     {
13756       gfc_error ("First argument of operator interface at %L must be "
13757                  "INTENT(IN)", &where);
13758       return FAILURE;
13759     }
13760
13761   if (formal->sym->attr.optional)
13762     {
13763       gfc_error ("First argument of operator interface at %L cannot be "
13764                  "optional", &where);
13765       return FAILURE;
13766     }
13767
13768   formal = formal->next;
13769   if (!formal || !formal->sym)
13770     return SUCCESS;
13771
13772   if (formal->sym->attr.intent != INTENT_IN)
13773     {
13774       gfc_error ("Second argument of operator interface at %L must be "
13775                  "INTENT(IN)", &where);
13776       return FAILURE;
13777     }
13778
13779   if (formal->sym->attr.optional)
13780     {
13781       gfc_error ("Second argument of operator interface at %L cannot be "
13782                  "optional", &where);
13783       return FAILURE;
13784     }
13785
13786   if (formal->next)
13787     {
13788       gfc_error ("Operator interface at %L must have, at most, two "
13789                  "arguments", &where);
13790       return FAILURE;
13791     }
13792
13793   return SUCCESS;
13794 }
13795
13796 static void
13797 gfc_resolve_uops (gfc_symtree *symtree)
13798 {
13799   gfc_interface *itr;
13800
13801   if (symtree == NULL)
13802     return;
13803
13804   gfc_resolve_uops (symtree->left);
13805   gfc_resolve_uops (symtree->right);
13806
13807   for (itr = symtree->n.uop->op; itr; itr = itr->next)
13808     check_uop_procedure (itr->sym, itr->sym->declared_at);
13809 }
13810
13811
13812 /* Examine all of the expressions associated with a program unit,
13813    assign types to all intermediate expressions, make sure that all
13814    assignments are to compatible types and figure out which names
13815    refer to which functions or subroutines.  It doesn't check code
13816    block, which is handled by resolve_code.  */
13817
13818 static void
13819 resolve_types (gfc_namespace *ns)
13820 {
13821   gfc_namespace *n;
13822   gfc_charlen *cl;
13823   gfc_data *d;
13824   gfc_equiv *eq;
13825   gfc_namespace* old_ns = gfc_current_ns;
13826
13827   /* Check that all IMPLICIT types are ok.  */
13828   if (!ns->seen_implicit_none)
13829     {
13830       unsigned letter;
13831       for (letter = 0; letter != GFC_LETTERS; ++letter)
13832         if (ns->set_flag[letter]
13833             && resolve_typespec_used (&ns->default_type[letter],
13834                                       &ns->implicit_loc[letter],
13835                                       NULL) == FAILURE)
13836           return;
13837     }
13838
13839   gfc_current_ns = ns;
13840
13841   resolve_entries (ns);
13842
13843   resolve_common_vars (ns->blank_common.head, false);
13844   resolve_common_blocks (ns->common_root);
13845
13846   resolve_contained_functions (ns);
13847
13848   if (ns->proc_name && ns->proc_name->attr.flavor == FL_PROCEDURE
13849       && ns->proc_name->attr.if_source == IFSRC_IFBODY)
13850     resolve_formal_arglist (ns->proc_name);
13851
13852   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
13853
13854   for (cl = ns->cl_list; cl; cl = cl->next)
13855     resolve_charlen (cl);
13856
13857   gfc_traverse_ns (ns, resolve_symbol);
13858
13859   resolve_fntype (ns);
13860
13861   for (n = ns->contained; n; n = n->sibling)
13862     {
13863       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
13864         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
13865                    "also be PURE", n->proc_name->name,
13866                    &n->proc_name->declared_at);
13867
13868       resolve_types (n);
13869     }
13870
13871   forall_flag = 0;
13872   do_concurrent_flag = 0;
13873   gfc_check_interfaces (ns);
13874
13875   gfc_traverse_ns (ns, resolve_values);
13876
13877   if (ns->save_all)
13878     gfc_save_all (ns);
13879
13880   iter_stack = NULL;
13881   for (d = ns->data; d; d = d->next)
13882     resolve_data (d);
13883
13884   iter_stack = NULL;
13885   gfc_traverse_ns (ns, gfc_formalize_init_value);
13886
13887   gfc_traverse_ns (ns, gfc_verify_binding_labels);
13888
13889   if (ns->common_root != NULL)
13890     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
13891
13892   for (eq = ns->equiv; eq; eq = eq->next)
13893     resolve_equivalence (eq);
13894
13895   /* Warn about unused labels.  */
13896   if (warn_unused_label)
13897     warn_unused_fortran_label (ns->st_labels);
13898
13899   gfc_resolve_uops (ns->uop_root);
13900
13901   gfc_current_ns = old_ns;
13902 }
13903
13904
13905 /* Call resolve_code recursively.  */
13906
13907 static void
13908 resolve_codes (gfc_namespace *ns)
13909 {
13910   gfc_namespace *n;
13911   bitmap_obstack old_obstack;
13912
13913   if (ns->resolved == 1)
13914     return;
13915
13916   for (n = ns->contained; n; n = n->sibling)
13917     resolve_codes (n);
13918
13919   gfc_current_ns = ns;
13920
13921   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
13922   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
13923     cs_base = NULL;
13924
13925   /* Set to an out of range value.  */
13926   current_entry_id = -1;
13927
13928   old_obstack = labels_obstack;
13929   bitmap_obstack_initialize (&labels_obstack);
13930
13931   resolve_code (ns->code, ns);
13932
13933   bitmap_obstack_release (&labels_obstack);
13934   labels_obstack = old_obstack;
13935 }
13936
13937
13938 /* This function is called after a complete program unit has been compiled.
13939    Its purpose is to examine all of the expressions associated with a program
13940    unit, assign types to all intermediate expressions, make sure that all
13941    assignments are to compatible types and figure out which names refer to
13942    which functions or subroutines.  */
13943
13944 void
13945 gfc_resolve (gfc_namespace *ns)
13946 {
13947   gfc_namespace *old_ns;
13948   code_stack *old_cs_base;
13949
13950   if (ns->resolved)
13951     return;
13952
13953   ns->resolved = -1;
13954   old_ns = gfc_current_ns;
13955   old_cs_base = cs_base;
13956
13957   resolve_types (ns);
13958   resolve_codes (ns);
13959
13960   gfc_current_ns = old_ns;
13961   cs_base = old_cs_base;
13962   ns->resolved = 1;
13963
13964   gfc_run_passes (ns);
13965 }