gfortran.h: Do not include coretypes.h here.
[platform/upstream/gcc.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 "coretypes.h"
26 #include "flags.h"
27 #include "gfortran.h"
28 #include "obstack.h"
29 #include "bitmap.h"
30 #include "arith.h"  /* For gfc_compare_expr().  */
31 #include "dependency.h"
32 #include "data.h"
33 #include "target-memory.h" /* for gfc_simplify_transfer */
34 #include "constructor.h"
35
36 /* Types used in equivalence statements.  */
37
38 typedef enum seq_type
39 {
40   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
41 }
42 seq_type;
43
44 /* Stack to keep track of the nesting of blocks as we move through the
45    code.  See resolve_branch() and resolve_code().  */
46
47 typedef struct code_stack
48 {
49   struct gfc_code *head, *current;
50   struct code_stack *prev;
51
52   /* This bitmap keeps track of the targets valid for a branch from
53      inside this block except for END {IF|SELECT}s of enclosing
54      blocks.  */
55   bitmap reachable_labels;
56 }
57 code_stack;
58
59 static code_stack *cs_base = NULL;
60
61
62 /* Nonzero if we're inside a FORALL or DO CONCURRENT block.  */
63
64 static int forall_flag;
65 static int do_concurrent_flag;
66
67 static bool assumed_type_expr_allowed = false;
68
69 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
70
71 static int omp_workshare_flag;
72
73 /* Nonzero if we are processing a formal arglist. The corresponding function
74    resets the flag each time that it is read.  */
75 static int formal_arg_flag = 0;
76
77 /* True if we are resolving a specification expression.  */
78 static int specification_expr = 0;
79
80 /* The id of the last entry seen.  */
81 static int current_entry_id;
82
83 /* We use bitmaps to determine if a branch target is valid.  */
84 static bitmap_obstack labels_obstack;
85
86 /* True when simplifying a EXPR_VARIABLE argument to an inquiry function.  */
87 static bool inquiry_argument = false;
88
89 int
90 gfc_is_formal_arg (void)
91 {
92   return formal_arg_flag;
93 }
94
95 /* Is the symbol host associated?  */
96 static bool
97 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
98 {
99   for (ns = ns->parent; ns; ns = ns->parent)
100     {      
101       if (sym->ns == ns)
102         return true;
103     }
104
105   return false;
106 }
107
108 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
109    an ABSTRACT derived-type.  If where is not NULL, an error message with that
110    locus is printed, optionally using name.  */
111
112 static gfc_try
113 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
114 {
115   if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
116     {
117       if (where)
118         {
119           if (name)
120             gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
121                        name, where, ts->u.derived->name);
122           else
123             gfc_error ("ABSTRACT type '%s' used at %L",
124                        ts->u.derived->name, where);
125         }
126
127       return FAILURE;
128     }
129
130   return SUCCESS;
131 }
132
133
134 static void resolve_symbol (gfc_symbol *sym);
135 static gfc_try resolve_intrinsic (gfc_symbol *sym, locus *loc);
136
137
138 /* Resolve the interface for a PROCEDURE declaration or procedure pointer.  */
139
140 static gfc_try
141 resolve_procedure_interface (gfc_symbol *sym)
142 {
143   if (sym->ts.interface == sym)
144     {
145       gfc_error ("PROCEDURE '%s' at %L may not be used as its own interface",
146                  sym->name, &sym->declared_at);
147       return FAILURE;
148     }
149   if (sym->ts.interface->attr.procedure)
150     {
151       gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared "
152                  "in a later PROCEDURE statement", sym->ts.interface->name,
153                  sym->name, &sym->declared_at);
154       return FAILURE;
155     }
156
157   /* Get the attributes from the interface (now resolved).  */
158   if (sym->ts.interface->attr.if_source || sym->ts.interface->attr.intrinsic)
159     {
160       gfc_symbol *ifc = sym->ts.interface;
161       resolve_symbol (ifc);
162
163       if (ifc->attr.intrinsic)
164         resolve_intrinsic (ifc, &ifc->declared_at);
165
166       if (ifc->result)
167         {
168           sym->ts = ifc->result->ts;
169           sym->result = sym;
170         }
171       else   
172         sym->ts = ifc->ts;
173       sym->ts.interface = ifc;
174       sym->attr.function = ifc->attr.function;
175       sym->attr.subroutine = ifc->attr.subroutine;
176       gfc_copy_formal_args (sym, ifc);
177
178       sym->attr.allocatable = ifc->attr.allocatable;
179       sym->attr.pointer = ifc->attr.pointer;
180       sym->attr.pure = ifc->attr.pure;
181       sym->attr.elemental = ifc->attr.elemental;
182       sym->attr.dimension = ifc->attr.dimension;
183       sym->attr.contiguous = ifc->attr.contiguous;
184       sym->attr.recursive = ifc->attr.recursive;
185       sym->attr.always_explicit = ifc->attr.always_explicit;
186       sym->attr.ext_attr |= ifc->attr.ext_attr;
187       sym->attr.is_bind_c = ifc->attr.is_bind_c;
188       /* Copy array spec.  */
189       sym->as = gfc_copy_array_spec (ifc->as);
190       if (sym->as)
191         {
192           int i;
193           for (i = 0; i < sym->as->rank; i++)
194             {
195               gfc_expr_replace_symbols (sym->as->lower[i], sym);
196               gfc_expr_replace_symbols (sym->as->upper[i], sym);
197             }
198         }
199       /* Copy char length.  */
200       if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
201         {
202           sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
203           gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
204           if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
205               && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
206             return FAILURE;
207         }
208     }
209   else if (sym->ts.interface->name[0] != '\0')
210     {
211       gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
212                  sym->ts.interface->name, sym->name, &sym->declared_at);
213       return FAILURE;
214     }
215
216   return SUCCESS;
217 }
218
219
220 /* Resolve types of formal argument lists.  These have to be done early so that
221    the formal argument lists of module procedures can be copied to the
222    containing module before the individual procedures are resolved
223    individually.  We also resolve argument lists of procedures in interface
224    blocks because they are self-contained scoping units.
225
226    Since a dummy argument cannot be a non-dummy procedure, the only
227    resort left for untyped names are the IMPLICIT types.  */
228
229 static void
230 resolve_formal_arglist (gfc_symbol *proc)
231 {
232   gfc_formal_arglist *f;
233   gfc_symbol *sym;
234   int i;
235
236   if (proc->result != NULL)
237     sym = proc->result;
238   else
239     sym = proc;
240
241   if (gfc_elemental (proc)
242       || sym->attr.pointer || sym->attr.allocatable
243       || (sym->as && sym->as->rank > 0))
244     {
245       proc->attr.always_explicit = 1;
246       sym->attr.always_explicit = 1;
247     }
248
249   formal_arg_flag = 1;
250
251   for (f = proc->formal; f; f = f->next)
252     {
253       sym = f->sym;
254
255       if (sym == NULL)
256         {
257           /* Alternate return placeholder.  */
258           if (gfc_elemental (proc))
259             gfc_error ("Alternate return specifier in elemental subroutine "
260                        "'%s' at %L is not allowed", proc->name,
261                        &proc->declared_at);
262           if (proc->attr.function)
263             gfc_error ("Alternate return specifier in function "
264                        "'%s' at %L is not allowed", proc->name,
265                        &proc->declared_at);
266           continue;
267         }
268       else if (sym->attr.procedure && sym->ts.interface
269                && sym->attr.if_source != IFSRC_DECL)
270         resolve_procedure_interface (sym);
271
272       if (sym->attr.if_source != IFSRC_UNKNOWN)
273         resolve_formal_arglist (sym);
274
275       if (sym->attr.subroutine || sym->attr.external)
276         {
277           if (sym->attr.flavor == FL_UNKNOWN)
278             gfc_add_flavor (&sym->attr, FL_PROCEDURE, sym->name, &sym->declared_at);
279         }
280       else
281         {
282           if (sym->ts.type == BT_UNKNOWN && !proc->attr.intrinsic
283               && (!sym->attr.function || sym->result == sym))
284             gfc_set_default_type (sym, 1, sym->ns);
285         }
286
287       gfc_resolve_array_spec (sym->as, 0);
288
289       /* We can't tell if an array with dimension (:) is assumed or deferred
290          shape until we know if it has the pointer or allocatable attributes.
291       */
292       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
293           && !(sym->attr.pointer || sym->attr.allocatable)
294           && sym->attr.flavor != FL_PROCEDURE)
295         {
296           sym->as->type = AS_ASSUMED_SHAPE;
297           for (i = 0; i < sym->as->rank; i++)
298             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
299                                                   NULL, 1);
300         }
301
302       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
303           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
304           || sym->attr.optional)
305         {
306           proc->attr.always_explicit = 1;
307           if (proc->result)
308             proc->result->attr.always_explicit = 1;
309         }
310
311       /* If the flavor is unknown at this point, it has to be a variable.
312          A procedure specification would have already set the type.  */
313
314       if (sym->attr.flavor == FL_UNKNOWN)
315         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
316
317       if (gfc_pure (proc))
318         {
319           if (sym->attr.flavor == FL_PROCEDURE)
320             {
321               /* F08:C1279.  */
322               if (!gfc_pure (sym))
323                 {
324                   gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
325                             "also be PURE", sym->name, &sym->declared_at);
326                   continue;
327                 }
328             }
329           else if (!sym->attr.pointer)
330             {
331               if (proc->attr.function && sym->attr.intent != INTENT_IN)
332                 {
333                   if (sym->attr.value)
334                     gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s'"
335                                     " of pure function '%s' at %L with VALUE "
336                                     "attribute but without INTENT(IN)",
337                                     sym->name, proc->name, &sym->declared_at);
338                   else
339                     gfc_error ("Argument '%s' of pure function '%s' at %L must "
340                                "be INTENT(IN) or VALUE", sym->name, proc->name,
341                                &sym->declared_at);
342                 }
343
344               if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
345                 {
346                   if (sym->attr.value)
347                     gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s'"
348                                     " of pure subroutine '%s' at %L with VALUE "
349                                     "attribute but without INTENT", sym->name,
350                                     proc->name, &sym->declared_at);
351                   else
352                     gfc_error ("Argument '%s' of pure subroutine '%s' at %L "
353                                "must have its INTENT specified or have the "
354                                "VALUE attribute", sym->name, proc->name,
355                                &sym->declared_at);
356                 }
357             }
358         }
359
360       if (proc->attr.implicit_pure)
361         {
362           if (sym->attr.flavor == FL_PROCEDURE)
363             {
364               if (!gfc_pure(sym))
365                 proc->attr.implicit_pure = 0;
366             }
367           else if (!sym->attr.pointer)
368             {
369               if (proc->attr.function && sym->attr.intent != INTENT_IN)
370                 proc->attr.implicit_pure = 0;
371
372               if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
373                 proc->attr.implicit_pure = 0;
374             }
375         }
376
377       if (gfc_elemental (proc))
378         {
379           /* F08:C1289.  */
380           if (sym->attr.codimension
381               || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
382                   && CLASS_DATA (sym)->attr.codimension))
383             {
384               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
385                          "procedure", sym->name, &sym->declared_at);
386               continue;
387             }
388
389           if (sym->as || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
390                           && CLASS_DATA (sym)->as))
391             {
392               gfc_error ("Argument '%s' of elemental procedure at %L must "
393                          "be scalar", sym->name, &sym->declared_at);
394               continue;
395             }
396
397           if (sym->attr.allocatable
398               || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
399                   && CLASS_DATA (sym)->attr.allocatable))
400             {
401               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
402                          "have the ALLOCATABLE attribute", sym->name,
403                          &sym->declared_at);
404               continue;
405             }
406
407           if (sym->attr.pointer
408               || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
409                   && CLASS_DATA (sym)->attr.class_pointer))
410             {
411               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
412                          "have the POINTER attribute", sym->name,
413                          &sym->declared_at);
414               continue;
415             }
416
417           if (sym->attr.flavor == FL_PROCEDURE)
418             {
419               gfc_error ("Dummy procedure '%s' not allowed in elemental "
420                          "procedure '%s' at %L", sym->name, proc->name,
421                          &sym->declared_at);
422               continue;
423             }
424
425           if (sym->attr.intent == INTENT_UNKNOWN)
426             {
427               gfc_error ("Argument '%s' of elemental procedure '%s' at %L must "
428                          "have its INTENT specified", sym->name, proc->name,
429                          &sym->declared_at);
430               continue;
431             }
432         }
433
434       /* Each dummy shall be specified to be scalar.  */
435       if (proc->attr.proc == PROC_ST_FUNCTION)
436         {
437           if (sym->as != NULL)
438             {
439               gfc_error ("Argument '%s' of statement function at %L must "
440                          "be scalar", sym->name, &sym->declared_at);
441               continue;
442             }
443
444           if (sym->ts.type == BT_CHARACTER)
445             {
446               gfc_charlen *cl = sym->ts.u.cl;
447               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
448                 {
449                   gfc_error ("Character-valued argument '%s' of statement "
450                              "function at %L must have constant length",
451                              sym->name, &sym->declared_at);
452                   continue;
453                 }
454             }
455         }
456     }
457   formal_arg_flag = 0;
458 }
459
460
461 /* Work function called when searching for symbols that have argument lists
462    associated with them.  */
463
464 static void
465 find_arglists (gfc_symbol *sym)
466 {
467   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns
468       || sym->attr.flavor == FL_DERIVED)
469     return;
470
471   resolve_formal_arglist (sym);
472 }
473
474
475 /* Given a namespace, resolve all formal argument lists within the namespace.
476  */
477
478 static void
479 resolve_formal_arglists (gfc_namespace *ns)
480 {
481   if (ns == NULL)
482     return;
483
484   gfc_traverse_ns (ns, find_arglists);
485 }
486
487
488 static void
489 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
490 {
491   gfc_try t;
492
493   /* If this namespace is not a function or an entry master function,
494      ignore it.  */
495   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
496       || sym->attr.entry_master)
497     return;
498
499   /* Try to find out of what the return type is.  */
500   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
501     {
502       t = gfc_set_default_type (sym->result, 0, ns);
503
504       if (t == FAILURE && !sym->result->attr.untyped)
505         {
506           if (sym->result == sym)
507             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
508                        sym->name, &sym->declared_at);
509           else if (!sym->result->attr.proc_pointer)
510             gfc_error ("Result '%s' of contained function '%s' at %L has "
511                        "no IMPLICIT type", sym->result->name, sym->name,
512                        &sym->result->declared_at);
513           sym->result->attr.untyped = 1;
514         }
515     }
516
517   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
518      type, lists the only ways a character length value of * can be used:
519      dummy arguments of procedures, named constants, and function results
520      in external functions.  Internal function results and results of module
521      procedures are not on this list, ergo, not permitted.  */
522
523   if (sym->result->ts.type == BT_CHARACTER)
524     {
525       gfc_charlen *cl = sym->result->ts.u.cl;
526       if ((!cl || !cl->length) && !sym->result->ts.deferred)
527         {
528           /* See if this is a module-procedure and adapt error message
529              accordingly.  */
530           bool module_proc;
531           gcc_assert (ns->parent && ns->parent->proc_name);
532           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
533
534           gfc_error ("Character-valued %s '%s' at %L must not be"
535                      " assumed length",
536                      module_proc ? _("module procedure")
537                                  : _("internal function"),
538                      sym->name, &sym->declared_at);
539         }
540     }
541 }
542
543
544 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
545    introduce duplicates.  */
546
547 static void
548 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
549 {
550   gfc_formal_arglist *f, *new_arglist;
551   gfc_symbol *new_sym;
552
553   for (; new_args != NULL; new_args = new_args->next)
554     {
555       new_sym = new_args->sym;
556       /* See if this arg is already in the formal argument list.  */
557       for (f = proc->formal; f; f = f->next)
558         {
559           if (new_sym == f->sym)
560             break;
561         }
562
563       if (f)
564         continue;
565
566       /* Add a new argument.  Argument order is not important.  */
567       new_arglist = gfc_get_formal_arglist ();
568       new_arglist->sym = new_sym;
569       new_arglist->next = proc->formal;
570       proc->formal  = new_arglist;
571     }
572 }
573
574
575 /* Flag the arguments that are not present in all entries.  */
576
577 static void
578 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
579 {
580   gfc_formal_arglist *f, *head;
581   head = new_args;
582
583   for (f = proc->formal; f; f = f->next)
584     {
585       if (f->sym == NULL)
586         continue;
587
588       for (new_args = head; new_args; new_args = new_args->next)
589         {
590           if (new_args->sym == f->sym)
591             break;
592         }
593
594       if (new_args)
595         continue;
596
597       f->sym->attr.not_always_present = 1;
598     }
599 }
600
601
602 /* Resolve alternate entry points.  If a symbol has multiple entry points we
603    create a new master symbol for the main routine, and turn the existing
604    symbol into an entry point.  */
605
606 static void
607 resolve_entries (gfc_namespace *ns)
608 {
609   gfc_namespace *old_ns;
610   gfc_code *c;
611   gfc_symbol *proc;
612   gfc_entry_list *el;
613   char name[GFC_MAX_SYMBOL_LEN + 1];
614   static int master_count = 0;
615
616   if (ns->proc_name == NULL)
617     return;
618
619   /* No need to do anything if this procedure doesn't have alternate entry
620      points.  */
621   if (!ns->entries)
622     return;
623
624   /* We may already have resolved alternate entry points.  */
625   if (ns->proc_name->attr.entry_master)
626     return;
627
628   /* If this isn't a procedure something has gone horribly wrong.  */
629   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
630
631   /* Remember the current namespace.  */
632   old_ns = gfc_current_ns;
633
634   gfc_current_ns = ns;
635
636   /* Add the main entry point to the list of entry points.  */
637   el = gfc_get_entry_list ();
638   el->sym = ns->proc_name;
639   el->id = 0;
640   el->next = ns->entries;
641   ns->entries = el;
642   ns->proc_name->attr.entry = 1;
643
644   /* If it is a module function, it needs to be in the right namespace
645      so that gfc_get_fake_result_decl can gather up the results. The
646      need for this arose in get_proc_name, where these beasts were
647      left in their own namespace, to keep prior references linked to
648      the entry declaration.*/
649   if (ns->proc_name->attr.function
650       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
651     el->sym->ns = ns;
652
653   /* Do the same for entries where the master is not a module
654      procedure.  These are retained in the module namespace because
655      of the module procedure declaration.  */
656   for (el = el->next; el; el = el->next)
657     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
658           && el->sym->attr.mod_proc)
659       el->sym->ns = ns;
660   el = ns->entries;
661
662   /* Add an entry statement for it.  */
663   c = gfc_get_code ();
664   c->op = EXEC_ENTRY;
665   c->ext.entry = el;
666   c->next = ns->code;
667   ns->code = c;
668
669   /* Create a new symbol for the master function.  */
670   /* Give the internal function a unique name (within this file).
671      Also include the function name so the user has some hope of figuring
672      out what is going on.  */
673   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
674             master_count++, ns->proc_name->name);
675   gfc_get_ha_symbol (name, &proc);
676   gcc_assert (proc != NULL);
677
678   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
679   if (ns->proc_name->attr.subroutine)
680     gfc_add_subroutine (&proc->attr, proc->name, NULL);
681   else
682     {
683       gfc_symbol *sym;
684       gfc_typespec *ts, *fts;
685       gfc_array_spec *as, *fas;
686       gfc_add_function (&proc->attr, proc->name, NULL);
687       proc->result = proc;
688       fas = ns->entries->sym->as;
689       fas = fas ? fas : ns->entries->sym->result->as;
690       fts = &ns->entries->sym->result->ts;
691       if (fts->type == BT_UNKNOWN)
692         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
693       for (el = ns->entries->next; el; el = el->next)
694         {
695           ts = &el->sym->result->ts;
696           as = el->sym->as;
697           as = as ? as : el->sym->result->as;
698           if (ts->type == BT_UNKNOWN)
699             ts = gfc_get_default_type (el->sym->result->name, NULL);
700
701           if (! gfc_compare_types (ts, fts)
702               || (el->sym->result->attr.dimension
703                   != ns->entries->sym->result->attr.dimension)
704               || (el->sym->result->attr.pointer
705                   != ns->entries->sym->result->attr.pointer))
706             break;
707           else if (as && fas && ns->entries->sym->result != el->sym->result
708                       && gfc_compare_array_spec (as, fas) == 0)
709             gfc_error ("Function %s at %L has entries with mismatched "
710                        "array specifications", ns->entries->sym->name,
711                        &ns->entries->sym->declared_at);
712           /* The characteristics need to match and thus both need to have
713              the same string length, i.e. both len=*, or both len=4.
714              Having both len=<variable> is also possible, but difficult to
715              check at compile time.  */
716           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
717                    && (((ts->u.cl->length && !fts->u.cl->length)
718                         ||(!ts->u.cl->length && fts->u.cl->length))
719                        || (ts->u.cl->length
720                            && ts->u.cl->length->expr_type
721                               != fts->u.cl->length->expr_type)
722                        || (ts->u.cl->length
723                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
724                            && mpz_cmp (ts->u.cl->length->value.integer,
725                                        fts->u.cl->length->value.integer) != 0)))
726             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
727                             "entries returning variables of different "
728                             "string lengths", ns->entries->sym->name,
729                             &ns->entries->sym->declared_at);
730         }
731
732       if (el == NULL)
733         {
734           sym = ns->entries->sym->result;
735           /* All result types the same.  */
736           proc->ts = *fts;
737           if (sym->attr.dimension)
738             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
739           if (sym->attr.pointer)
740             gfc_add_pointer (&proc->attr, NULL);
741         }
742       else
743         {
744           /* Otherwise the result will be passed through a union by
745              reference.  */
746           proc->attr.mixed_entry_master = 1;
747           for (el = ns->entries; el; el = el->next)
748             {
749               sym = el->sym->result;
750               if (sym->attr.dimension)
751                 {
752                   if (el == ns->entries)
753                     gfc_error ("FUNCTION result %s can't be an array in "
754                                "FUNCTION %s at %L", sym->name,
755                                ns->entries->sym->name, &sym->declared_at);
756                   else
757                     gfc_error ("ENTRY result %s can't be an array in "
758                                "FUNCTION %s at %L", sym->name,
759                                ns->entries->sym->name, &sym->declared_at);
760                 }
761               else if (sym->attr.pointer)
762                 {
763                   if (el == ns->entries)
764                     gfc_error ("FUNCTION result %s can't be a POINTER in "
765                                "FUNCTION %s at %L", sym->name,
766                                ns->entries->sym->name, &sym->declared_at);
767                   else
768                     gfc_error ("ENTRY result %s can't be a POINTER in "
769                                "FUNCTION %s at %L", sym->name,
770                                ns->entries->sym->name, &sym->declared_at);
771                 }
772               else
773                 {
774                   ts = &sym->ts;
775                   if (ts->type == BT_UNKNOWN)
776                     ts = gfc_get_default_type (sym->name, NULL);
777                   switch (ts->type)
778                     {
779                     case BT_INTEGER:
780                       if (ts->kind == gfc_default_integer_kind)
781                         sym = NULL;
782                       break;
783                     case BT_REAL:
784                       if (ts->kind == gfc_default_real_kind
785                           || ts->kind == gfc_default_double_kind)
786                         sym = NULL;
787                       break;
788                     case BT_COMPLEX:
789                       if (ts->kind == gfc_default_complex_kind)
790                         sym = NULL;
791                       break;
792                     case BT_LOGICAL:
793                       if (ts->kind == gfc_default_logical_kind)
794                         sym = NULL;
795                       break;
796                     case BT_UNKNOWN:
797                       /* We will issue error elsewhere.  */
798                       sym = NULL;
799                       break;
800                     default:
801                       break;
802                     }
803                   if (sym)
804                     {
805                       if (el == ns->entries)
806                         gfc_error ("FUNCTION result %s can't be of type %s "
807                                    "in FUNCTION %s at %L", sym->name,
808                                    gfc_typename (ts), ns->entries->sym->name,
809                                    &sym->declared_at);
810                       else
811                         gfc_error ("ENTRY result %s can't be of type %s "
812                                    "in FUNCTION %s at %L", sym->name,
813                                    gfc_typename (ts), ns->entries->sym->name,
814                                    &sym->declared_at);
815                     }
816                 }
817             }
818         }
819     }
820   proc->attr.access = ACCESS_PRIVATE;
821   proc->attr.entry_master = 1;
822
823   /* Merge all the entry point arguments.  */
824   for (el = ns->entries; el; el = el->next)
825     merge_argument_lists (proc, el->sym->formal);
826
827   /* Check the master formal arguments for any that are not
828      present in all entry points.  */
829   for (el = ns->entries; el; el = el->next)
830     check_argument_lists (proc, el->sym->formal);
831
832   /* Use the master function for the function body.  */
833   ns->proc_name = proc;
834
835   /* Finalize the new symbols.  */
836   gfc_commit_symbols ();
837
838   /* Restore the original namespace.  */
839   gfc_current_ns = old_ns;
840 }
841
842
843 /* Resolve common variables.  */
844 static void
845 resolve_common_vars (gfc_symbol *sym, bool named_common)
846 {
847   gfc_symbol *csym = sym;
848
849   for (; csym; csym = csym->common_next)
850     {
851       if (csym->value || csym->attr.data)
852         {
853           if (!csym->ns->is_block_data)
854             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
855                             "but only in BLOCK DATA initialization is "
856                             "allowed", csym->name, &csym->declared_at);
857           else if (!named_common)
858             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
859                             "in a blank COMMON but initialization is only "
860                             "allowed in named common blocks", csym->name,
861                             &csym->declared_at);
862         }
863
864       if (csym->ts.type != BT_DERIVED)
865         continue;
866
867       if (!(csym->ts.u.derived->attr.sequence
868             || csym->ts.u.derived->attr.is_bind_c))
869         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
870                        "has neither the SEQUENCE nor the BIND(C) "
871                        "attribute", csym->name, &csym->declared_at);
872       if (csym->ts.u.derived->attr.alloc_comp)
873         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
874                        "has an ultimate component that is "
875                        "allocatable", csym->name, &csym->declared_at);
876       if (gfc_has_default_initializer (csym->ts.u.derived))
877         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
878                        "may not have default initializer", csym->name,
879                        &csym->declared_at);
880
881       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
882         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
883     }
884 }
885
886 /* Resolve common blocks.  */
887 static void
888 resolve_common_blocks (gfc_symtree *common_root)
889 {
890   gfc_symbol *sym;
891
892   if (common_root == NULL)
893     return;
894
895   if (common_root->left)
896     resolve_common_blocks (common_root->left);
897   if (common_root->right)
898     resolve_common_blocks (common_root->right);
899
900   resolve_common_vars (common_root->n.common->head, true);
901
902   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
903   if (sym == NULL)
904     return;
905
906   if (sym->attr.flavor == FL_PARAMETER)
907     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
908                sym->name, &common_root->n.common->where, &sym->declared_at);
909
910   if (sym->attr.external)
911     gfc_error ("COMMON block '%s' at %L can not have the EXTERNAL attribute",
912                sym->name, &common_root->n.common->where);
913
914   if (sym->attr.intrinsic)
915     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
916                sym->name, &common_root->n.common->where);
917   else if (sym->attr.result
918            || gfc_is_function_return_value (sym, gfc_current_ns))
919     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
920                     "that is also a function result", sym->name,
921                     &common_root->n.common->where);
922   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
923            && sym->attr.proc != PROC_ST_FUNCTION)
924     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
925                     "that is also a global procedure", sym->name,
926                     &common_root->n.common->where);
927 }
928
929
930 /* Resolve contained function types.  Because contained functions can call one
931    another, they have to be worked out before any of the contained procedures
932    can be resolved.
933
934    The good news is that if a function doesn't already have a type, the only
935    way it can get one is through an IMPLICIT type or a RESULT variable, because
936    by definition contained functions are contained namespace they're contained
937    in, not in a sibling or parent namespace.  */
938
939 static void
940 resolve_contained_functions (gfc_namespace *ns)
941 {
942   gfc_namespace *child;
943   gfc_entry_list *el;
944
945   resolve_formal_arglists (ns);
946
947   for (child = ns->contained; child; child = child->sibling)
948     {
949       /* Resolve alternate entry points first.  */
950       resolve_entries (child);
951
952       /* Then check function return types.  */
953       resolve_contained_fntype (child->proc_name, child);
954       for (el = child->entries; el; el = el->next)
955         resolve_contained_fntype (el->sym, child);
956     }
957 }
958
959
960 static gfc_try resolve_fl_derived0 (gfc_symbol *sym);
961
962
963 /* Resolve all of the elements of a structure constructor and make sure that
964    the types are correct. The 'init' flag indicates that the given
965    constructor is an initializer.  */
966
967 static gfc_try
968 resolve_structure_cons (gfc_expr *expr, int init)
969 {
970   gfc_constructor *cons;
971   gfc_component *comp;
972   gfc_try t;
973   symbol_attribute a;
974
975   t = SUCCESS;
976
977   if (expr->ts.type == BT_DERIVED)
978     resolve_fl_derived0 (expr->ts.u.derived);
979
980   cons = gfc_constructor_first (expr->value.constructor);
981
982   /* See if the user is trying to invoke a structure constructor for one of
983      the iso_c_binding derived types.  */
984   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
985       && expr->ts.u.derived->ts.is_iso_c && cons
986       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
987     {
988       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
989                  expr->ts.u.derived->name, &(expr->where));
990       return FAILURE;
991     }
992
993   /* Return if structure constructor is c_null_(fun)prt.  */
994   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
995       && expr->ts.u.derived->ts.is_iso_c && cons
996       && cons->expr && cons->expr->expr_type == EXPR_NULL)
997     return SUCCESS;
998
999   /* A constructor may have references if it is the result of substituting a
1000      parameter variable.  In this case we just pull out the component we
1001      want.  */
1002   if (expr->ref)
1003     comp = expr->ref->u.c.sym->components;
1004   else
1005     comp = expr->ts.u.derived->components;
1006
1007   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
1008     {
1009       int rank;
1010
1011       if (!cons->expr)
1012         continue;
1013
1014       if (gfc_resolve_expr (cons->expr) == FAILURE)
1015         {
1016           t = FAILURE;
1017           continue;
1018         }
1019
1020       rank = comp->as ? comp->as->rank : 0;
1021       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
1022           && (comp->attr.allocatable || cons->expr->rank))
1023         {
1024           gfc_error ("The rank of the element in the structure "
1025                      "constructor at %L does not match that of the "
1026                      "component (%d/%d)", &cons->expr->where,
1027                      cons->expr->rank, rank);
1028           t = FAILURE;
1029         }
1030
1031       /* If we don't have the right type, try to convert it.  */
1032
1033       if (!comp->attr.proc_pointer &&
1034           !gfc_compare_types (&cons->expr->ts, &comp->ts))
1035         {
1036           t = FAILURE;
1037           if (strcmp (comp->name, "_extends") == 0)
1038             {
1039               /* Can afford to be brutal with the _extends initializer.
1040                  The derived type can get lost because it is PRIVATE
1041                  but it is not usage constrained by the standard.  */
1042               cons->expr->ts = comp->ts;
1043               t = SUCCESS;
1044             }
1045           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
1046             gfc_error ("The element in the structure constructor at %L, "
1047                        "for pointer component '%s', is %s but should be %s",
1048                        &cons->expr->where, comp->name,
1049                        gfc_basic_typename (cons->expr->ts.type),
1050                        gfc_basic_typename (comp->ts.type));
1051           else
1052             t = gfc_convert_type (cons->expr, &comp->ts, 1);
1053         }
1054
1055       /* For strings, the length of the constructor should be the same as
1056          the one of the structure, ensure this if the lengths are known at
1057          compile time and when we are dealing with PARAMETER or structure
1058          constructors.  */
1059       if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1060           && comp->ts.u.cl->length
1061           && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1062           && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1063           && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1064           && cons->expr->rank != 0
1065           && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1066                       comp->ts.u.cl->length->value.integer) != 0)
1067         {
1068           if (cons->expr->expr_type == EXPR_VARIABLE
1069               && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1070             {
1071               /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1072                  to make use of the gfc_resolve_character_array_constructor
1073                  machinery.  The expression is later simplified away to
1074                  an array of string literals.  */
1075               gfc_expr *para = cons->expr;
1076               cons->expr = gfc_get_expr ();
1077               cons->expr->ts = para->ts;
1078               cons->expr->where = para->where;
1079               cons->expr->expr_type = EXPR_ARRAY;
1080               cons->expr->rank = para->rank;
1081               cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1082               gfc_constructor_append_expr (&cons->expr->value.constructor,
1083                                            para, &cons->expr->where);
1084             }
1085           if (cons->expr->expr_type == EXPR_ARRAY)
1086             {
1087               gfc_constructor *p;
1088               p = gfc_constructor_first (cons->expr->value.constructor);
1089               if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1090                 {
1091                   gfc_charlen *cl, *cl2;
1092
1093                   cl2 = NULL;
1094                   for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1095                     {
1096                       if (cl == cons->expr->ts.u.cl)
1097                         break;
1098                       cl2 = cl;
1099                     }
1100
1101                   gcc_assert (cl);
1102
1103                   if (cl2)
1104                     cl2->next = cl->next;
1105
1106                   gfc_free_expr (cl->length);
1107                   free (cl);
1108                 }
1109
1110               cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1111               cons->expr->ts.u.cl->length_from_typespec = true;
1112               cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1113               gfc_resolve_character_array_constructor (cons->expr);
1114             }
1115         }
1116
1117       if (cons->expr->expr_type == EXPR_NULL
1118           && !(comp->attr.pointer || comp->attr.allocatable
1119                || comp->attr.proc_pointer
1120                || (comp->ts.type == BT_CLASS
1121                    && (CLASS_DATA (comp)->attr.class_pointer
1122                        || CLASS_DATA (comp)->attr.allocatable))))
1123         {
1124           t = FAILURE;
1125           gfc_error ("The NULL in the structure constructor at %L is "
1126                      "being applied to component '%s', which is neither "
1127                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
1128                      comp->name);
1129         }
1130
1131       if (comp->attr.proc_pointer && comp->ts.interface)
1132         {
1133           /* Check procedure pointer interface.  */
1134           gfc_symbol *s2 = NULL;
1135           gfc_component *c2;
1136           const char *name;
1137           char err[200];
1138
1139           if (gfc_is_proc_ptr_comp (cons->expr, &c2))
1140             {
1141               s2 = c2->ts.interface;
1142               name = c2->name;
1143             }
1144           else if (cons->expr->expr_type == EXPR_FUNCTION)
1145             {
1146               s2 = cons->expr->symtree->n.sym->result;
1147               name = cons->expr->symtree->n.sym->result->name;
1148             }
1149           else if (cons->expr->expr_type != EXPR_NULL)
1150             {
1151               s2 = cons->expr->symtree->n.sym;
1152               name = cons->expr->symtree->n.sym->name;
1153             }
1154
1155           if (s2 && !gfc_compare_interfaces (comp->ts.interface, s2, name, 0, 1,
1156                                              err, sizeof (err), NULL, NULL))
1157             {
1158               gfc_error ("Interface mismatch for procedure-pointer component "
1159                          "'%s' in structure constructor at %L: %s",
1160                          comp->name, &cons->expr->where, err);
1161               return FAILURE;
1162             }
1163         }
1164
1165       if (!comp->attr.pointer || comp->attr.proc_pointer
1166           || cons->expr->expr_type == EXPR_NULL)
1167         continue;
1168
1169       a = gfc_expr_attr (cons->expr);
1170
1171       if (!a.pointer && !a.target)
1172         {
1173           t = FAILURE;
1174           gfc_error ("The element in the structure constructor at %L, "
1175                      "for pointer component '%s' should be a POINTER or "
1176                      "a TARGET", &cons->expr->where, comp->name);
1177         }
1178
1179       if (init)
1180         {
1181           /* F08:C461. Additional checks for pointer initialization.  */
1182           if (a.allocatable)
1183             {
1184               t = FAILURE;
1185               gfc_error ("Pointer initialization target at %L "
1186                          "must not be ALLOCATABLE ", &cons->expr->where);
1187             }
1188           if (!a.save)
1189             {
1190               t = FAILURE;
1191               gfc_error ("Pointer initialization target at %L "
1192                          "must have the SAVE attribute", &cons->expr->where);
1193             }
1194         }
1195
1196       /* F2003, C1272 (3).  */
1197       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
1198           && (gfc_impure_variable (cons->expr->symtree->n.sym)
1199               || gfc_is_coindexed (cons->expr)))
1200         {
1201           t = FAILURE;
1202           gfc_error ("Invalid expression in the structure constructor for "
1203                      "pointer component '%s' at %L in PURE procedure",
1204                      comp->name, &cons->expr->where);
1205         }
1206
1207       if (gfc_implicit_pure (NULL)
1208             && cons->expr->expr_type == EXPR_VARIABLE
1209             && (gfc_impure_variable (cons->expr->symtree->n.sym)
1210                 || gfc_is_coindexed (cons->expr)))
1211         gfc_current_ns->proc_name->attr.implicit_pure = 0;
1212
1213     }
1214
1215   return t;
1216 }
1217
1218
1219 /****************** Expression name resolution ******************/
1220
1221 /* Returns 0 if a symbol was not declared with a type or
1222    attribute declaration statement, nonzero otherwise.  */
1223
1224 static int
1225 was_declared (gfc_symbol *sym)
1226 {
1227   symbol_attribute a;
1228
1229   a = sym->attr;
1230
1231   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1232     return 1;
1233
1234   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1235       || a.optional || a.pointer || a.save || a.target || a.volatile_
1236       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1237       || a.asynchronous || a.codimension)
1238     return 1;
1239
1240   return 0;
1241 }
1242
1243
1244 /* Determine if a symbol is generic or not.  */
1245
1246 static int
1247 generic_sym (gfc_symbol *sym)
1248 {
1249   gfc_symbol *s;
1250
1251   if (sym->attr.generic ||
1252       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1253     return 1;
1254
1255   if (was_declared (sym) || sym->ns->parent == NULL)
1256     return 0;
1257
1258   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1259   
1260   if (s != NULL)
1261     {
1262       if (s == sym)
1263         return 0;
1264       else
1265         return generic_sym (s);
1266     }
1267
1268   return 0;
1269 }
1270
1271
1272 /* Determine if a symbol is specific or not.  */
1273
1274 static int
1275 specific_sym (gfc_symbol *sym)
1276 {
1277   gfc_symbol *s;
1278
1279   if (sym->attr.if_source == IFSRC_IFBODY
1280       || sym->attr.proc == PROC_MODULE
1281       || sym->attr.proc == PROC_INTERNAL
1282       || sym->attr.proc == PROC_ST_FUNCTION
1283       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1284       || sym->attr.external)
1285     return 1;
1286
1287   if (was_declared (sym) || sym->ns->parent == NULL)
1288     return 0;
1289
1290   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1291
1292   return (s == NULL) ? 0 : specific_sym (s);
1293 }
1294
1295
1296 /* Figure out if the procedure is specific, generic or unknown.  */
1297
1298 typedef enum
1299 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1300 proc_type;
1301
1302 static proc_type
1303 procedure_kind (gfc_symbol *sym)
1304 {
1305   if (generic_sym (sym))
1306     return PTYPE_GENERIC;
1307
1308   if (specific_sym (sym))
1309     return PTYPE_SPECIFIC;
1310
1311   return PTYPE_UNKNOWN;
1312 }
1313
1314 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1315    is nonzero when matching actual arguments.  */
1316
1317 static int need_full_assumed_size = 0;
1318
1319 static bool
1320 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1321 {
1322   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1323       return false;
1324
1325   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1326      What should it be?  */
1327   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1328           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1329                && (e->ref->u.ar.type == AR_FULL))
1330     {
1331       gfc_error ("The upper bound in the last dimension must "
1332                  "appear in the reference to the assumed size "
1333                  "array '%s' at %L", sym->name, &e->where);
1334       return true;
1335     }
1336   return false;
1337 }
1338
1339
1340 /* Look for bad assumed size array references in argument expressions
1341   of elemental and array valued intrinsic procedures.  Since this is
1342   called from procedure resolution functions, it only recurses at
1343   operators.  */
1344
1345 static bool
1346 resolve_assumed_size_actual (gfc_expr *e)
1347 {
1348   if (e == NULL)
1349    return false;
1350
1351   switch (e->expr_type)
1352     {
1353     case EXPR_VARIABLE:
1354       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1355         return true;
1356       break;
1357
1358     case EXPR_OP:
1359       if (resolve_assumed_size_actual (e->value.op.op1)
1360           || resolve_assumed_size_actual (e->value.op.op2))
1361         return true;
1362       break;
1363
1364     default:
1365       break;
1366     }
1367   return false;
1368 }
1369
1370
1371 /* Check a generic procedure, passed as an actual argument, to see if
1372    there is a matching specific name.  If none, it is an error, and if
1373    more than one, the reference is ambiguous.  */
1374 static int
1375 count_specific_procs (gfc_expr *e)
1376 {
1377   int n;
1378   gfc_interface *p;
1379   gfc_symbol *sym;
1380         
1381   n = 0;
1382   sym = e->symtree->n.sym;
1383
1384   for (p = sym->generic; p; p = p->next)
1385     if (strcmp (sym->name, p->sym->name) == 0)
1386       {
1387         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1388                                        sym->name);
1389         n++;
1390       }
1391
1392   if (n > 1)
1393     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1394                &e->where);
1395
1396   if (n == 0)
1397     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1398                "argument at %L", sym->name, &e->where);
1399
1400   return n;
1401 }
1402
1403
1404 /* See if a call to sym could possibly be a not allowed RECURSION because of
1405    a missing RECURSIVE declaration.  This means that either sym is the current
1406    context itself, or sym is the parent of a contained procedure calling its
1407    non-RECURSIVE containing procedure.
1408    This also works if sym is an ENTRY.  */
1409
1410 static bool
1411 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1412 {
1413   gfc_symbol* proc_sym;
1414   gfc_symbol* context_proc;
1415   gfc_namespace* real_context;
1416
1417   if (sym->attr.flavor == FL_PROGRAM
1418       || sym->attr.flavor == FL_DERIVED)
1419     return false;
1420
1421   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1422
1423   /* If we've got an ENTRY, find real procedure.  */
1424   if (sym->attr.entry && sym->ns->entries)
1425     proc_sym = sym->ns->entries->sym;
1426   else
1427     proc_sym = sym;
1428
1429   /* If sym is RECURSIVE, all is well of course.  */
1430   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1431     return false;
1432
1433   /* Find the context procedure's "real" symbol if it has entries.
1434      We look for a procedure symbol, so recurse on the parents if we don't
1435      find one (like in case of a BLOCK construct).  */
1436   for (real_context = context; ; real_context = real_context->parent)
1437     {
1438       /* We should find something, eventually!  */
1439       gcc_assert (real_context);
1440
1441       context_proc = (real_context->entries ? real_context->entries->sym
1442                                             : real_context->proc_name);
1443
1444       /* In some special cases, there may not be a proc_name, like for this
1445          invalid code:
1446          real(bad_kind()) function foo () ...
1447          when checking the call to bad_kind ().
1448          In these cases, we simply return here and assume that the
1449          call is ok.  */
1450       if (!context_proc)
1451         return false;
1452
1453       if (context_proc->attr.flavor != FL_LABEL)
1454         break;
1455     }
1456
1457   /* A call from sym's body to itself is recursion, of course.  */
1458   if (context_proc == proc_sym)
1459     return true;
1460
1461   /* The same is true if context is a contained procedure and sym the
1462      containing one.  */
1463   if (context_proc->attr.contained)
1464     {
1465       gfc_symbol* parent_proc;
1466
1467       gcc_assert (context->parent);
1468       parent_proc = (context->parent->entries ? context->parent->entries->sym
1469                                               : context->parent->proc_name);
1470
1471       if (parent_proc == proc_sym)
1472         return true;
1473     }
1474
1475   return false;
1476 }
1477
1478
1479 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1480    its typespec and formal argument list.  */
1481
1482 static gfc_try
1483 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1484 {
1485   gfc_intrinsic_sym* isym = NULL;
1486   const char* symstd;
1487
1488   if (sym->formal)
1489     return SUCCESS;
1490
1491   /* Already resolved.  */
1492   if (sym->from_intmod && sym->ts.type != BT_UNKNOWN)
1493     return SUCCESS;
1494
1495   /* We already know this one is an intrinsic, so we don't call
1496      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1497      gfc_find_subroutine directly to check whether it is a function or
1498      subroutine.  */
1499
1500   if (sym->intmod_sym_id)
1501     isym = gfc_intrinsic_function_by_id ((gfc_isym_id) sym->intmod_sym_id);
1502   else if (!sym->attr.subroutine)
1503     isym = gfc_find_function (sym->name);
1504
1505   if (isym)
1506     {
1507       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1508           && !sym->attr.implicit_type)
1509         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1510                       " ignored", sym->name, &sym->declared_at);
1511
1512       if (!sym->attr.function &&
1513           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1514         return FAILURE;
1515
1516       sym->ts = isym->ts;
1517     }
1518   else if ((isym = gfc_find_subroutine (sym->name)))
1519     {
1520       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1521         {
1522           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1523                       " specifier", sym->name, &sym->declared_at);
1524           return FAILURE;
1525         }
1526
1527       if (!sym->attr.subroutine &&
1528           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1529         return FAILURE;
1530     }
1531   else
1532     {
1533       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1534                  &sym->declared_at);
1535       return FAILURE;
1536     }
1537
1538   gfc_copy_formal_args_intr (sym, isym);
1539
1540   /* Check it is actually available in the standard settings.  */
1541   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1542       == FAILURE)
1543     {
1544       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1545                  " available in the current standard settings but %s.  Use"
1546                  " an appropriate -std=* option or enable -fall-intrinsics"
1547                  " in order to use it.",
1548                  sym->name, &sym->declared_at, symstd);
1549       return FAILURE;
1550     }
1551
1552   return SUCCESS;
1553 }
1554
1555
1556 /* Resolve a procedure expression, like passing it to a called procedure or as
1557    RHS for a procedure pointer assignment.  */
1558
1559 static gfc_try
1560 resolve_procedure_expression (gfc_expr* expr)
1561 {
1562   gfc_symbol* sym;
1563
1564   if (expr->expr_type != EXPR_VARIABLE)
1565     return SUCCESS;
1566   gcc_assert (expr->symtree);
1567
1568   sym = expr->symtree->n.sym;
1569
1570   if (sym->attr.intrinsic)
1571     resolve_intrinsic (sym, &expr->where);
1572
1573   if (sym->attr.flavor != FL_PROCEDURE
1574       || (sym->attr.function && sym->result == sym))
1575     return SUCCESS;
1576
1577   /* A non-RECURSIVE procedure that is used as procedure expression within its
1578      own body is in danger of being called recursively.  */
1579   if (is_illegal_recursion (sym, gfc_current_ns))
1580     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1581                  " itself recursively.  Declare it RECURSIVE or use"
1582                  " -frecursive", sym->name, &expr->where);
1583   
1584   return SUCCESS;
1585 }
1586
1587
1588 /* Resolve an actual argument list.  Most of the time, this is just
1589    resolving the expressions in the list.
1590    The exception is that we sometimes have to decide whether arguments
1591    that look like procedure arguments are really simple variable
1592    references.  */
1593
1594 static gfc_try
1595 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1596                         bool no_formal_args)
1597 {
1598   gfc_symbol *sym;
1599   gfc_symtree *parent_st;
1600   gfc_expr *e;
1601   int save_need_full_assumed_size;
1602
1603   assumed_type_expr_allowed = true;
1604
1605   for (; arg; arg = arg->next)
1606     {
1607       e = arg->expr;
1608       if (e == NULL)
1609         {
1610           /* Check the label is a valid branching target.  */
1611           if (arg->label)
1612             {
1613               if (arg->label->defined == ST_LABEL_UNKNOWN)
1614                 {
1615                   gfc_error ("Label %d referenced at %L is never defined",
1616                              arg->label->value, &arg->label->where);
1617                   return FAILURE;
1618                 }
1619             }
1620           continue;
1621         }
1622
1623       if (e->expr_type == EXPR_VARIABLE
1624             && e->symtree->n.sym->attr.generic
1625             && no_formal_args
1626             && count_specific_procs (e) != 1)
1627         return FAILURE;
1628
1629       if (e->ts.type != BT_PROCEDURE)
1630         {
1631           save_need_full_assumed_size = need_full_assumed_size;
1632           if (e->expr_type != EXPR_VARIABLE)
1633             need_full_assumed_size = 0;
1634           if (gfc_resolve_expr (e) != SUCCESS)
1635             return FAILURE;
1636           need_full_assumed_size = save_need_full_assumed_size;
1637           goto argument_list;
1638         }
1639
1640       /* See if the expression node should really be a variable reference.  */
1641
1642       sym = e->symtree->n.sym;
1643
1644       if (sym->attr.flavor == FL_PROCEDURE
1645           || sym->attr.intrinsic
1646           || sym->attr.external)
1647         {
1648           int actual_ok;
1649
1650           /* If a procedure is not already determined to be something else
1651              check if it is intrinsic.  */
1652           if (!sym->attr.intrinsic
1653               && !(sym->attr.external || sym->attr.use_assoc
1654                    || sym->attr.if_source == IFSRC_IFBODY)
1655               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1656             sym->attr.intrinsic = 1;
1657
1658           if (sym->attr.proc == PROC_ST_FUNCTION)
1659             {
1660               gfc_error ("Statement function '%s' at %L is not allowed as an "
1661                          "actual argument", sym->name, &e->where);
1662             }
1663
1664           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1665                                                sym->attr.subroutine);
1666           if (sym->attr.intrinsic && actual_ok == 0)
1667             {
1668               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1669                          "actual argument", sym->name, &e->where);
1670             }
1671
1672           if (sym->attr.contained && !sym->attr.use_assoc
1673               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1674             {
1675               if (gfc_notify_std (GFC_STD_F2008,
1676                                   "Fortran 2008: Internal procedure '%s' is"
1677                                   " used as actual argument at %L",
1678                                   sym->name, &e->where) == FAILURE)
1679                 return FAILURE;
1680             }
1681
1682           if (sym->attr.elemental && !sym->attr.intrinsic)
1683             {
1684               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1685                          "allowed as an actual argument at %L", sym->name,
1686                          &e->where);
1687             }
1688
1689           /* Check if a generic interface has a specific procedure
1690             with the same name before emitting an error.  */
1691           if (sym->attr.generic && count_specific_procs (e) != 1)
1692             return FAILURE;
1693           
1694           /* Just in case a specific was found for the expression.  */
1695           sym = e->symtree->n.sym;
1696
1697           /* If the symbol is the function that names the current (or
1698              parent) scope, then we really have a variable reference.  */
1699
1700           if (gfc_is_function_return_value (sym, sym->ns))
1701             goto got_variable;
1702
1703           /* If all else fails, see if we have a specific intrinsic.  */
1704           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1705             {
1706               gfc_intrinsic_sym *isym;
1707
1708               isym = gfc_find_function (sym->name);
1709               if (isym == NULL || !isym->specific)
1710                 {
1711                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1712                              "for the reference '%s' at %L", sym->name,
1713                              &e->where);
1714                   return FAILURE;
1715                 }
1716               sym->ts = isym->ts;
1717               sym->attr.intrinsic = 1;
1718               sym->attr.function = 1;
1719             }
1720
1721           if (gfc_resolve_expr (e) == FAILURE)
1722             return FAILURE;
1723           goto argument_list;
1724         }
1725
1726       /* See if the name is a module procedure in a parent unit.  */
1727
1728       if (was_declared (sym) || sym->ns->parent == NULL)
1729         goto got_variable;
1730
1731       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1732         {
1733           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1734           return FAILURE;
1735         }
1736
1737       if (parent_st == NULL)
1738         goto got_variable;
1739
1740       sym = parent_st->n.sym;
1741       e->symtree = parent_st;           /* Point to the right thing.  */
1742
1743       if (sym->attr.flavor == FL_PROCEDURE
1744           || sym->attr.intrinsic
1745           || sym->attr.external)
1746         {
1747           if (gfc_resolve_expr (e) == FAILURE)
1748             return FAILURE;
1749           goto argument_list;
1750         }
1751
1752     got_variable:
1753       e->expr_type = EXPR_VARIABLE;
1754       e->ts = sym->ts;
1755       if ((sym->as != NULL && sym->ts.type != BT_CLASS)
1756           || (sym->ts.type == BT_CLASS && sym->attr.class_ok
1757               && CLASS_DATA (sym)->as))
1758         {
1759           e->rank = sym->ts.type == BT_CLASS
1760                     ? CLASS_DATA (sym)->as->rank : sym->as->rank;
1761           e->ref = gfc_get_ref ();
1762           e->ref->type = REF_ARRAY;
1763           e->ref->u.ar.type = AR_FULL;
1764           e->ref->u.ar.as = sym->ts.type == BT_CLASS
1765                             ? CLASS_DATA (sym)->as : sym->as;
1766         }
1767
1768       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1769          primary.c (match_actual_arg). If above code determines that it
1770          is a  variable instead, it needs to be resolved as it was not
1771          done at the beginning of this function.  */
1772       save_need_full_assumed_size = need_full_assumed_size;
1773       if (e->expr_type != EXPR_VARIABLE)
1774         need_full_assumed_size = 0;
1775       if (gfc_resolve_expr (e) != SUCCESS)
1776         return FAILURE;
1777       need_full_assumed_size = save_need_full_assumed_size;
1778
1779     argument_list:
1780       /* Check argument list functions %VAL, %LOC and %REF.  There is
1781          nothing to do for %REF.  */
1782       if (arg->name && arg->name[0] == '%')
1783         {
1784           if (strncmp ("%VAL", arg->name, 4) == 0)
1785             {
1786               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1787                 {
1788                   gfc_error ("By-value argument at %L is not of numeric "
1789                              "type", &e->where);
1790                   return FAILURE;
1791                 }
1792
1793               if (e->rank)
1794                 {
1795                   gfc_error ("By-value argument at %L cannot be an array or "
1796                              "an array section", &e->where);
1797                 return FAILURE;
1798                 }
1799
1800               /* Intrinsics are still PROC_UNKNOWN here.  However,
1801                  since same file external procedures are not resolvable
1802                  in gfortran, it is a good deal easier to leave them to
1803                  intrinsic.c.  */
1804               if (ptype != PROC_UNKNOWN
1805                   && ptype != PROC_DUMMY
1806                   && ptype != PROC_EXTERNAL
1807                   && ptype != PROC_MODULE)
1808                 {
1809                   gfc_error ("By-value argument at %L is not allowed "
1810                              "in this context", &e->where);
1811                   return FAILURE;
1812                 }
1813             }
1814
1815           /* Statement functions have already been excluded above.  */
1816           else if (strncmp ("%LOC", arg->name, 4) == 0
1817                    && e->ts.type == BT_PROCEDURE)
1818             {
1819               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1820                 {
1821                   gfc_error ("Passing internal procedure at %L by location "
1822                              "not allowed", &e->where);
1823                   return FAILURE;
1824                 }
1825             }
1826         }
1827
1828       /* Fortran 2008, C1237.  */
1829       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1830           && gfc_has_ultimate_pointer (e))
1831         {
1832           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1833                      "component", &e->where);
1834           return FAILURE;
1835         }
1836     }
1837   assumed_type_expr_allowed = false;
1838
1839   return SUCCESS;
1840 }
1841
1842
1843 /* Do the checks of the actual argument list that are specific to elemental
1844    procedures.  If called with c == NULL, we have a function, otherwise if
1845    expr == NULL, we have a subroutine.  */
1846
1847 static gfc_try
1848 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1849 {
1850   gfc_actual_arglist *arg0;
1851   gfc_actual_arglist *arg;
1852   gfc_symbol *esym = NULL;
1853   gfc_intrinsic_sym *isym = NULL;
1854   gfc_expr *e = NULL;
1855   gfc_intrinsic_arg *iformal = NULL;
1856   gfc_formal_arglist *eformal = NULL;
1857   bool formal_optional = false;
1858   bool set_by_optional = false;
1859   int i;
1860   int rank = 0;
1861
1862   /* Is this an elemental procedure?  */
1863   if (expr && expr->value.function.actual != NULL)
1864     {
1865       if (expr->value.function.esym != NULL
1866           && expr->value.function.esym->attr.elemental)
1867         {
1868           arg0 = expr->value.function.actual;
1869           esym = expr->value.function.esym;
1870         }
1871       else if (expr->value.function.isym != NULL
1872                && expr->value.function.isym->elemental)
1873         {
1874           arg0 = expr->value.function.actual;
1875           isym = expr->value.function.isym;
1876         }
1877       else
1878         return SUCCESS;
1879     }
1880   else if (c && c->ext.actual != NULL)
1881     {
1882       arg0 = c->ext.actual;
1883       
1884       if (c->resolved_sym)
1885         esym = c->resolved_sym;
1886       else
1887         esym = c->symtree->n.sym;
1888       gcc_assert (esym);
1889
1890       if (!esym->attr.elemental)
1891         return SUCCESS;
1892     }
1893   else
1894     return SUCCESS;
1895
1896   /* The rank of an elemental is the rank of its array argument(s).  */
1897   for (arg = arg0; arg; arg = arg->next)
1898     {
1899       if (arg->expr != NULL && arg->expr->rank > 0)
1900         {
1901           rank = arg->expr->rank;
1902           if (arg->expr->expr_type == EXPR_VARIABLE
1903               && arg->expr->symtree->n.sym->attr.optional)
1904             set_by_optional = true;
1905
1906           /* Function specific; set the result rank and shape.  */
1907           if (expr)
1908             {
1909               expr->rank = rank;
1910               if (!expr->shape && arg->expr->shape)
1911                 {
1912                   expr->shape = gfc_get_shape (rank);
1913                   for (i = 0; i < rank; i++)
1914                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1915                 }
1916             }
1917           break;
1918         }
1919     }
1920
1921   /* If it is an array, it shall not be supplied as an actual argument
1922      to an elemental procedure unless an array of the same rank is supplied
1923      as an actual argument corresponding to a nonoptional dummy argument of
1924      that elemental procedure(12.4.1.5).  */
1925   formal_optional = false;
1926   if (isym)
1927     iformal = isym->formal;
1928   else
1929     eformal = esym->formal;
1930
1931   for (arg = arg0; arg; arg = arg->next)
1932     {
1933       if (eformal)
1934         {
1935           if (eformal->sym && eformal->sym->attr.optional)
1936             formal_optional = true;
1937           eformal = eformal->next;
1938         }
1939       else if (isym && iformal)
1940         {
1941           if (iformal->optional)
1942             formal_optional = true;
1943           iformal = iformal->next;
1944         }
1945       else if (isym)
1946         formal_optional = true;
1947
1948       if (pedantic && arg->expr != NULL
1949           && arg->expr->expr_type == EXPR_VARIABLE
1950           && arg->expr->symtree->n.sym->attr.optional
1951           && formal_optional
1952           && arg->expr->rank
1953           && (set_by_optional || arg->expr->rank != rank)
1954           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1955         {
1956           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1957                        "MISSING, it cannot be the actual argument of an "
1958                        "ELEMENTAL procedure unless there is a non-optional "
1959                        "argument with the same rank (12.4.1.5)",
1960                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1961         }
1962     }
1963
1964   for (arg = arg0; arg; arg = arg->next)
1965     {
1966       if (arg->expr == NULL || arg->expr->rank == 0)
1967         continue;
1968
1969       /* Being elemental, the last upper bound of an assumed size array
1970          argument must be present.  */
1971       if (resolve_assumed_size_actual (arg->expr))
1972         return FAILURE;
1973
1974       /* Elemental procedure's array actual arguments must conform.  */
1975       if (e != NULL)
1976         {
1977           if (gfc_check_conformance (arg->expr, e,
1978                                      "elemental procedure") == FAILURE)
1979             return FAILURE;
1980         }
1981       else
1982         e = arg->expr;
1983     }
1984
1985   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1986      is an array, the intent inout/out variable needs to be also an array.  */
1987   if (rank > 0 && esym && expr == NULL)
1988     for (eformal = esym->formal, arg = arg0; arg && eformal;
1989          arg = arg->next, eformal = eformal->next)
1990       if ((eformal->sym->attr.intent == INTENT_OUT
1991            || eformal->sym->attr.intent == INTENT_INOUT)
1992           && arg->expr && arg->expr->rank == 0)
1993         {
1994           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1995                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1996                      "actual argument is an array", &arg->expr->where,
1997                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1998                      : "INOUT", eformal->sym->name, esym->name);
1999           return FAILURE;
2000         }
2001   return SUCCESS;
2002 }
2003
2004
2005 /* This function does the checking of references to global procedures
2006    as defined in sections 18.1 and 14.1, respectively, of the Fortran
2007    77 and 95 standards.  It checks for a gsymbol for the name, making
2008    one if it does not already exist.  If it already exists, then the
2009    reference being resolved must correspond to the type of gsymbol.
2010    Otherwise, the new symbol is equipped with the attributes of the
2011    reference.  The corresponding code that is called in creating
2012    global entities is parse.c.
2013
2014    In addition, for all but -std=legacy, the gsymbols are used to
2015    check the interfaces of external procedures from the same file.
2016    The namespace of the gsymbol is resolved and then, once this is
2017    done the interface is checked.  */
2018
2019
2020 static bool
2021 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
2022 {
2023   if (!gsym_ns->proc_name->attr.recursive)
2024     return true;
2025
2026   if (sym->ns == gsym_ns)
2027     return false;
2028
2029   if (sym->ns->parent && sym->ns->parent == gsym_ns)
2030     return false;
2031
2032   return true;
2033 }
2034
2035 static bool
2036 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
2037 {
2038   if (gsym_ns->entries)
2039     {
2040       gfc_entry_list *entry = gsym_ns->entries;
2041
2042       for (; entry; entry = entry->next)
2043         {
2044           if (strcmp (sym->name, entry->sym->name) == 0)
2045             {
2046               if (strcmp (gsym_ns->proc_name->name,
2047                           sym->ns->proc_name->name) == 0)
2048                 return false;
2049
2050               if (sym->ns->parent
2051                   && strcmp (gsym_ns->proc_name->name,
2052                              sym->ns->parent->proc_name->name) == 0)
2053                 return false;
2054             }
2055         }
2056     }
2057   return true;
2058 }
2059
2060 static void
2061 resolve_global_procedure (gfc_symbol *sym, locus *where,
2062                           gfc_actual_arglist **actual, int sub)
2063 {
2064   gfc_gsymbol * gsym;
2065   gfc_namespace *ns;
2066   enum gfc_symbol_type type;
2067
2068   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
2069
2070   gsym = gfc_get_gsymbol (sym->name);
2071
2072   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
2073     gfc_global_used (gsym, where);
2074
2075   if (gfc_option.flag_whole_file
2076         && (sym->attr.if_source == IFSRC_UNKNOWN
2077             || sym->attr.if_source == IFSRC_IFBODY)
2078         && gsym->type != GSYM_UNKNOWN
2079         && gsym->ns
2080         && gsym->ns->resolved != -1
2081         && gsym->ns->proc_name
2082         && not_in_recursive (sym, gsym->ns)
2083         && not_entry_self_reference (sym, gsym->ns))
2084     {
2085       gfc_symbol *def_sym;
2086
2087       /* Resolve the gsymbol namespace if needed.  */
2088       if (!gsym->ns->resolved)
2089         {
2090           gfc_dt_list *old_dt_list;
2091           struct gfc_omp_saved_state old_omp_state;
2092
2093           /* Stash away derived types so that the backend_decls do not
2094              get mixed up.  */
2095           old_dt_list = gfc_derived_types;
2096           gfc_derived_types = NULL;
2097           /* And stash away openmp state.  */
2098           gfc_omp_save_and_clear_state (&old_omp_state);
2099
2100           gfc_resolve (gsym->ns);
2101
2102           /* Store the new derived types with the global namespace.  */
2103           if (gfc_derived_types)
2104             gsym->ns->derived_types = gfc_derived_types;
2105
2106           /* Restore the derived types of this namespace.  */
2107           gfc_derived_types = old_dt_list;
2108           /* And openmp state.  */
2109           gfc_omp_restore_state (&old_omp_state);
2110         }
2111
2112       /* Make sure that translation for the gsymbol occurs before
2113          the procedure currently being resolved.  */
2114       ns = gfc_global_ns_list;
2115       for (; ns && ns != gsym->ns; ns = ns->sibling)
2116         {
2117           if (ns->sibling == gsym->ns)
2118             {
2119               ns->sibling = gsym->ns->sibling;
2120               gsym->ns->sibling = gfc_global_ns_list;
2121               gfc_global_ns_list = gsym->ns;
2122               break;
2123             }
2124         }
2125
2126       def_sym = gsym->ns->proc_name;
2127       if (def_sym->attr.entry_master)
2128         {
2129           gfc_entry_list *entry;
2130           for (entry = gsym->ns->entries; entry; entry = entry->next)
2131             if (strcmp (entry->sym->name, sym->name) == 0)
2132               {
2133                 def_sym = entry->sym;
2134                 break;
2135               }
2136         }
2137
2138       /* Differences in constant character lengths.  */
2139       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
2140         {
2141           long int l1 = 0, l2 = 0;
2142           gfc_charlen *cl1 = sym->ts.u.cl;
2143           gfc_charlen *cl2 = def_sym->ts.u.cl;
2144
2145           if (cl1 != NULL
2146               && cl1->length != NULL
2147               && cl1->length->expr_type == EXPR_CONSTANT)
2148             l1 = mpz_get_si (cl1->length->value.integer);
2149
2150           if (cl2 != NULL
2151               && cl2->length != NULL
2152               && cl2->length->expr_type == EXPR_CONSTANT)
2153             l2 = mpz_get_si (cl2->length->value.integer);
2154
2155           if (l1 && l2 && l1 != l2)
2156             gfc_error ("Character length mismatch in return type of "
2157                        "function '%s' at %L (%ld/%ld)", sym->name,
2158                        &sym->declared_at, l1, l2);
2159         }
2160
2161      /* Type mismatch of function return type and expected type.  */
2162      if (sym->attr.function
2163          && !gfc_compare_types (&sym->ts, &def_sym->ts))
2164         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
2165                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2166                    gfc_typename (&def_sym->ts));
2167
2168       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
2169         {
2170           gfc_formal_arglist *arg = def_sym->formal;
2171           for ( ; arg; arg = arg->next)
2172             if (!arg->sym)
2173               continue;
2174             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
2175             else if (arg->sym->attr.allocatable
2176                      || arg->sym->attr.asynchronous
2177                      || arg->sym->attr.optional
2178                      || arg->sym->attr.pointer
2179                      || arg->sym->attr.target
2180                      || arg->sym->attr.value
2181                      || arg->sym->attr.volatile_)
2182               {
2183                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
2184                            "has an attribute that requires an explicit "
2185                            "interface for this procedure", arg->sym->name,
2186                            sym->name, &sym->declared_at);
2187                 break;
2188               }
2189             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
2190             else if (arg->sym && arg->sym->as
2191                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
2192               {
2193                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
2194                            "argument '%s' must have an explicit interface",
2195                            sym->name, &sym->declared_at, arg->sym->name);
2196                 break;
2197               }
2198             /* F2008, 12.4.2.2 (2c)  */
2199             else if (arg->sym->attr.codimension)
2200               {
2201                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
2202                            "'%s' must have an explicit interface",
2203                            sym->name, &sym->declared_at, arg->sym->name);
2204                 break;
2205               }
2206             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
2207             else if (false) /* TODO: is a parametrized derived type  */
2208               {
2209                 gfc_error ("Procedure '%s' at %L with parametrized derived "
2210                            "type argument '%s' must have an explicit "
2211                            "interface", sym->name, &sym->declared_at,
2212                            arg->sym->name);
2213                 break;
2214               }
2215             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
2216             else if (arg->sym->ts.type == BT_CLASS)
2217               {
2218                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
2219                            "argument '%s' must have an explicit interface",
2220                            sym->name, &sym->declared_at, arg->sym->name);
2221                 break;
2222               }
2223         }
2224
2225       if (def_sym->attr.function)
2226         {
2227           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
2228           if (def_sym->as && def_sym->as->rank
2229               && (!sym->as || sym->as->rank != def_sym->as->rank))
2230             gfc_error ("The reference to function '%s' at %L either needs an "
2231                        "explicit INTERFACE or the rank is incorrect", sym->name,
2232                        where);
2233
2234           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
2235           if ((def_sym->result->attr.pointer
2236                || def_sym->result->attr.allocatable)
2237                && (sym->attr.if_source != IFSRC_IFBODY
2238                    || def_sym->result->attr.pointer
2239                         != sym->result->attr.pointer
2240                    || def_sym->result->attr.allocatable
2241                         != sym->result->attr.allocatable))
2242             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
2243                        "result must have an explicit interface", sym->name,
2244                        where);
2245
2246           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
2247           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
2248               && def_sym->ts.type == BT_CHARACTER && def_sym->ts.u.cl->length != NULL)
2249             {
2250               gfc_charlen *cl = sym->ts.u.cl;
2251
2252               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
2253                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
2254                 {
2255                   gfc_error ("Nonconstant character-length function '%s' at %L "
2256                              "must have an explicit interface", sym->name,
2257                              &sym->declared_at);
2258                 }
2259             }
2260         }
2261
2262       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2263       if (def_sym->attr.elemental && !sym->attr.elemental)
2264         {
2265           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2266                      "interface", sym->name, &sym->declared_at);
2267         }
2268
2269       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2270       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2271         {
2272           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2273                      "an explicit interface", sym->name, &sym->declared_at);
2274         }
2275
2276       if (gfc_option.flag_whole_file == 1
2277           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2278               && !(gfc_option.warn_std & GFC_STD_GNU)))
2279         gfc_errors_to_warnings (1);
2280
2281       if (sym->attr.if_source != IFSRC_IFBODY)  
2282         gfc_procedure_use (def_sym, actual, where);
2283
2284       gfc_errors_to_warnings (0);
2285     }
2286
2287   if (gsym->type == GSYM_UNKNOWN)
2288     {
2289       gsym->type = type;
2290       gsym->where = *where;
2291     }
2292
2293   gsym->used = 1;
2294 }
2295
2296
2297 /************* Function resolution *************/
2298
2299 /* Resolve a function call known to be generic.
2300    Section 14.1.2.4.1.  */
2301
2302 static match
2303 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2304 {
2305   gfc_symbol *s;
2306
2307   if (sym->attr.generic)
2308     {
2309       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2310       if (s != NULL)
2311         {
2312           expr->value.function.name = s->name;
2313           expr->value.function.esym = s;
2314
2315           if (s->ts.type != BT_UNKNOWN)
2316             expr->ts = s->ts;
2317           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2318             expr->ts = s->result->ts;
2319
2320           if (s->as != NULL)
2321             expr->rank = s->as->rank;
2322           else if (s->result != NULL && s->result->as != NULL)
2323             expr->rank = s->result->as->rank;
2324
2325           gfc_set_sym_referenced (expr->value.function.esym);
2326
2327           return MATCH_YES;
2328         }
2329
2330       /* TODO: Need to search for elemental references in generic
2331          interface.  */
2332     }
2333
2334   if (sym->attr.intrinsic)
2335     return gfc_intrinsic_func_interface (expr, 0);
2336
2337   return MATCH_NO;
2338 }
2339
2340
2341 static gfc_try
2342 resolve_generic_f (gfc_expr *expr)
2343 {
2344   gfc_symbol *sym;
2345   match m;
2346   gfc_interface *intr = NULL;
2347
2348   sym = expr->symtree->n.sym;
2349
2350   for (;;)
2351     {
2352       m = resolve_generic_f0 (expr, sym);
2353       if (m == MATCH_YES)
2354         return SUCCESS;
2355       else if (m == MATCH_ERROR)
2356         return FAILURE;
2357
2358 generic:
2359       if (!intr)
2360         for (intr = sym->generic; intr; intr = intr->next)
2361           if (intr->sym->attr.flavor == FL_DERIVED)
2362             break;
2363
2364       if (sym->ns->parent == NULL)
2365         break;
2366       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2367
2368       if (sym == NULL)
2369         break;
2370       if (!generic_sym (sym))
2371         goto generic;
2372     }
2373
2374   /* Last ditch attempt.  See if the reference is to an intrinsic
2375      that possesses a matching interface.  14.1.2.4  */
2376   if (sym  && !intr && !gfc_is_intrinsic (sym, 0, expr->where))
2377     {
2378       gfc_error ("There is no specific function for the generic '%s' "
2379                  "at %L", expr->symtree->n.sym->name, &expr->where);
2380       return FAILURE;
2381     }
2382
2383   if (intr)
2384     {
2385       if (gfc_convert_to_structure_constructor (expr, intr->sym, NULL, NULL,
2386                                                 false) != SUCCESS)
2387         return FAILURE;
2388       return resolve_structure_cons (expr, 0);
2389     }
2390
2391   m = gfc_intrinsic_func_interface (expr, 0);
2392   if (m == MATCH_YES)
2393     return SUCCESS;
2394
2395   if (m == MATCH_NO)
2396     gfc_error ("Generic function '%s' at %L is not consistent with a "
2397                "specific intrinsic interface", expr->symtree->n.sym->name,
2398                &expr->where);
2399
2400   return FAILURE;
2401 }
2402
2403
2404 /* Resolve a function call known to be specific.  */
2405
2406 static match
2407 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2408 {
2409   match m;
2410
2411   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2412     {
2413       if (sym->attr.dummy)
2414         {
2415           sym->attr.proc = PROC_DUMMY;
2416           goto found;
2417         }
2418
2419       sym->attr.proc = PROC_EXTERNAL;
2420       goto found;
2421     }
2422
2423   if (sym->attr.proc == PROC_MODULE
2424       || sym->attr.proc == PROC_ST_FUNCTION
2425       || sym->attr.proc == PROC_INTERNAL)
2426     goto found;
2427
2428   if (sym->attr.intrinsic)
2429     {
2430       m = gfc_intrinsic_func_interface (expr, 1);
2431       if (m == MATCH_YES)
2432         return MATCH_YES;
2433       if (m == MATCH_NO)
2434         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2435                    "with an intrinsic", sym->name, &expr->where);
2436
2437       return MATCH_ERROR;
2438     }
2439
2440   return MATCH_NO;
2441
2442 found:
2443   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2444
2445   if (sym->result)
2446     expr->ts = sym->result->ts;
2447   else
2448     expr->ts = sym->ts;
2449   expr->value.function.name = sym->name;
2450   expr->value.function.esym = sym;
2451   if (sym->as != NULL)
2452     expr->rank = sym->as->rank;
2453
2454   return MATCH_YES;
2455 }
2456
2457
2458 static gfc_try
2459 resolve_specific_f (gfc_expr *expr)
2460 {
2461   gfc_symbol *sym;
2462   match m;
2463
2464   sym = expr->symtree->n.sym;
2465
2466   for (;;)
2467     {
2468       m = resolve_specific_f0 (sym, expr);
2469       if (m == MATCH_YES)
2470         return SUCCESS;
2471       if (m == MATCH_ERROR)
2472         return FAILURE;
2473
2474       if (sym->ns->parent == NULL)
2475         break;
2476
2477       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2478
2479       if (sym == NULL)
2480         break;
2481     }
2482
2483   gfc_error ("Unable to resolve the specific function '%s' at %L",
2484              expr->symtree->n.sym->name, &expr->where);
2485
2486   return SUCCESS;
2487 }
2488
2489
2490 /* Resolve a procedure call not known to be generic nor specific.  */
2491
2492 static gfc_try
2493 resolve_unknown_f (gfc_expr *expr)
2494 {
2495   gfc_symbol *sym;
2496   gfc_typespec *ts;
2497
2498   sym = expr->symtree->n.sym;
2499
2500   if (sym->attr.dummy)
2501     {
2502       sym->attr.proc = PROC_DUMMY;
2503       expr->value.function.name = sym->name;
2504       goto set_type;
2505     }
2506
2507   /* See if we have an intrinsic function reference.  */
2508
2509   if (gfc_is_intrinsic (sym, 0, expr->where))
2510     {
2511       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2512         return SUCCESS;
2513       return FAILURE;
2514     }
2515
2516   /* The reference is to an external name.  */
2517
2518   sym->attr.proc = PROC_EXTERNAL;
2519   expr->value.function.name = sym->name;
2520   expr->value.function.esym = expr->symtree->n.sym;
2521
2522   if (sym->as != NULL)
2523     expr->rank = sym->as->rank;
2524
2525   /* Type of the expression is either the type of the symbol or the
2526      default type of the symbol.  */
2527
2528 set_type:
2529   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2530
2531   if (sym->ts.type != BT_UNKNOWN)
2532     expr->ts = sym->ts;
2533   else
2534     {
2535       ts = gfc_get_default_type (sym->name, sym->ns);
2536
2537       if (ts->type == BT_UNKNOWN)
2538         {
2539           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2540                      sym->name, &expr->where);
2541           return FAILURE;
2542         }
2543       else
2544         expr->ts = *ts;
2545     }
2546
2547   return SUCCESS;
2548 }
2549
2550
2551 /* Return true, if the symbol is an external procedure.  */
2552 static bool
2553 is_external_proc (gfc_symbol *sym)
2554 {
2555   if (!sym->attr.dummy && !sym->attr.contained
2556         && !(sym->attr.intrinsic
2557               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2558         && sym->attr.proc != PROC_ST_FUNCTION
2559         && !sym->attr.proc_pointer
2560         && !sym->attr.use_assoc
2561         && sym->name)
2562     return true;
2563
2564   return false;
2565 }
2566
2567
2568 /* Figure out if a function reference is pure or not.  Also set the name
2569    of the function for a potential error message.  Return nonzero if the
2570    function is PURE, zero if not.  */
2571 static int
2572 pure_stmt_function (gfc_expr *, gfc_symbol *);
2573
2574 static int
2575 pure_function (gfc_expr *e, const char **name)
2576 {
2577   int pure;
2578
2579   *name = NULL;
2580
2581   if (e->symtree != NULL
2582         && e->symtree->n.sym != NULL
2583         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2584     return pure_stmt_function (e, e->symtree->n.sym);
2585
2586   if (e->value.function.esym)
2587     {
2588       pure = gfc_pure (e->value.function.esym);
2589       *name = e->value.function.esym->name;
2590     }
2591   else if (e->value.function.isym)
2592     {
2593       pure = e->value.function.isym->pure
2594              || e->value.function.isym->elemental;
2595       *name = e->value.function.isym->name;
2596     }
2597   else
2598     {
2599       /* Implicit functions are not pure.  */
2600       pure = 0;
2601       *name = e->value.function.name;
2602     }
2603
2604   return pure;
2605 }
2606
2607
2608 static bool
2609 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2610                  int *f ATTRIBUTE_UNUSED)
2611 {
2612   const char *name;
2613
2614   /* Don't bother recursing into other statement functions
2615      since they will be checked individually for purity.  */
2616   if (e->expr_type != EXPR_FUNCTION
2617         || !e->symtree
2618         || e->symtree->n.sym == sym
2619         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2620     return false;
2621
2622   return pure_function (e, &name) ? false : true;
2623 }
2624
2625
2626 static int
2627 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2628 {
2629   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2630 }
2631
2632
2633 static gfc_try
2634 is_scalar_expr_ptr (gfc_expr *expr)
2635 {
2636   gfc_try retval = SUCCESS;
2637   gfc_ref *ref;
2638   int start;
2639   int end;
2640
2641   /* See if we have a gfc_ref, which means we have a substring, array
2642      reference, or a component.  */
2643   if (expr->ref != NULL)
2644     {
2645       ref = expr->ref;
2646       while (ref->next != NULL)
2647         ref = ref->next;
2648
2649       switch (ref->type)
2650         {
2651         case REF_SUBSTRING:
2652           if (ref->u.ss.start == NULL || ref->u.ss.end == NULL
2653               || gfc_dep_compare_expr (ref->u.ss.start, ref->u.ss.end) != 0)
2654             retval = FAILURE;
2655           break;
2656
2657         case REF_ARRAY:
2658           if (ref->u.ar.type == AR_ELEMENT)
2659             retval = SUCCESS;
2660           else if (ref->u.ar.type == AR_FULL)
2661             {
2662               /* The user can give a full array if the array is of size 1.  */
2663               if (ref->u.ar.as != NULL
2664                   && ref->u.ar.as->rank == 1
2665                   && ref->u.ar.as->type == AS_EXPLICIT
2666                   && ref->u.ar.as->lower[0] != NULL
2667                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2668                   && ref->u.ar.as->upper[0] != NULL
2669                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2670                 {
2671                   /* If we have a character string, we need to check if
2672                      its length is one.  */
2673                   if (expr->ts.type == BT_CHARACTER)
2674                     {
2675                       if (expr->ts.u.cl == NULL
2676                           || expr->ts.u.cl->length == NULL
2677                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2678                           != 0)
2679                         retval = FAILURE;
2680                     }
2681                   else
2682                     {
2683                       /* We have constant lower and upper bounds.  If the
2684                          difference between is 1, it can be considered a
2685                          scalar.  
2686                          FIXME: Use gfc_dep_compare_expr instead.  */
2687                       start = (int) mpz_get_si
2688                                 (ref->u.ar.as->lower[0]->value.integer);
2689                       end = (int) mpz_get_si
2690                                 (ref->u.ar.as->upper[0]->value.integer);
2691                       if (end - start + 1 != 1)
2692                         retval = FAILURE;
2693                    }
2694                 }
2695               else
2696                 retval = FAILURE;
2697             }
2698           else
2699             retval = FAILURE;
2700           break;
2701         default:
2702           retval = SUCCESS;
2703           break;
2704         }
2705     }
2706   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2707     {
2708       /* Character string.  Make sure it's of length 1.  */
2709       if (expr->ts.u.cl == NULL
2710           || expr->ts.u.cl->length == NULL
2711           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2712         retval = FAILURE;
2713     }
2714   else if (expr->rank != 0)
2715     retval = FAILURE;
2716
2717   return retval;
2718 }
2719
2720
2721 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2722    and, in the case of c_associated, set the binding label based on
2723    the arguments.  */
2724
2725 static gfc_try
2726 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2727                           gfc_symbol **new_sym)
2728 {
2729   char name[GFC_MAX_SYMBOL_LEN + 1];
2730   int optional_arg = 0;
2731   gfc_try retval = SUCCESS;
2732   gfc_symbol *args_sym;
2733   gfc_typespec *arg_ts;
2734   symbol_attribute arg_attr;
2735
2736   if (args->expr->expr_type == EXPR_CONSTANT
2737       || args->expr->expr_type == EXPR_OP
2738       || args->expr->expr_type == EXPR_NULL)
2739     {
2740       gfc_error ("Argument to '%s' at %L is not a variable",
2741                  sym->name, &(args->expr->where));
2742       return FAILURE;
2743     }
2744
2745   args_sym = args->expr->symtree->n.sym;
2746
2747   /* The typespec for the actual arg should be that stored in the expr
2748      and not necessarily that of the expr symbol (args_sym), because
2749      the actual expression could be a part-ref of the expr symbol.  */
2750   arg_ts = &(args->expr->ts);
2751   arg_attr = gfc_expr_attr (args->expr);
2752     
2753   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2754     {
2755       /* If the user gave two args then they are providing something for
2756          the optional arg (the second cptr).  Therefore, set the name and
2757          binding label to the c_associated for two cptrs.  Otherwise,
2758          set c_associated to expect one cptr.  */
2759       if (args->next)
2760         {
2761           /* two args.  */
2762           sprintf (name, "%s_2", sym->name);
2763           optional_arg = 1;
2764         }
2765       else
2766         {
2767           /* one arg.  */
2768           sprintf (name, "%s_1", sym->name);
2769           optional_arg = 0;
2770         }
2771
2772       /* Get a new symbol for the version of c_associated that
2773          will get called.  */
2774       *new_sym = get_iso_c_sym (sym, name, NULL, optional_arg);
2775     }
2776   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2777            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2778     {
2779       sprintf (name, "%s", sym->name);
2780
2781       /* Error check the call.  */
2782       if (args->next != NULL)
2783         {
2784           gfc_error_now ("More actual than formal arguments in '%s' "
2785                          "call at %L", name, &(args->expr->where));
2786           retval = FAILURE;
2787         }
2788       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2789         {
2790           gfc_ref *ref;
2791           bool seen_section;
2792
2793           /* Make sure we have either the target or pointer attribute.  */
2794           if (!arg_attr.target && !arg_attr.pointer)
2795             {
2796               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2797                              "a TARGET or an associated pointer",
2798                              args_sym->name,
2799                              sym->name, &(args->expr->where));
2800               retval = FAILURE;
2801             }
2802
2803           if (gfc_is_coindexed (args->expr))
2804             {
2805               gfc_error_now ("Coindexed argument not permitted"
2806                              " in '%s' call at %L", name,
2807                              &(args->expr->where));
2808               retval = FAILURE;
2809             }
2810
2811           /* Follow references to make sure there are no array
2812              sections.  */
2813           seen_section = false;
2814
2815           for (ref=args->expr->ref; ref; ref = ref->next)
2816             {
2817               if (ref->type == REF_ARRAY)
2818                 {
2819                   if (ref->u.ar.type == AR_SECTION)
2820                     seen_section = true;
2821
2822                   if (ref->u.ar.type != AR_ELEMENT)
2823                     {
2824                       gfc_ref *r;
2825                       for (r = ref->next; r; r=r->next)
2826                         if (r->type == REF_COMPONENT)
2827                           {
2828                             gfc_error_now ("Array section not permitted"
2829                                            " in '%s' call at %L", name,
2830                                            &(args->expr->where));
2831                             retval = FAILURE;
2832                             break;
2833                           }
2834                     }
2835                 }
2836             }
2837
2838           if (seen_section && retval == SUCCESS)
2839             gfc_warning ("Array section in '%s' call at %L", name,
2840                          &(args->expr->where));
2841                          
2842           /* See if we have interoperable type and type param.  */
2843           if (gfc_verify_c_interop (arg_ts) == SUCCESS
2844               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2845             {
2846               if (args_sym->attr.target == 1)
2847                 {
2848                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2849                      has the target attribute and is interoperable.  */
2850                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2851                      allocatable variable that has the TARGET attribute and
2852                      is not an array of zero size.  */
2853                   if (args_sym->attr.allocatable == 1)
2854                     {
2855                       if (args_sym->attr.dimension != 0 
2856                           && (args_sym->as && args_sym->as->rank == 0))
2857                         {
2858                           gfc_error_now ("Allocatable variable '%s' used as a "
2859                                          "parameter to '%s' at %L must not be "
2860                                          "an array of zero size",
2861                                          args_sym->name, sym->name,
2862                                          &(args->expr->where));
2863                           retval = FAILURE;
2864                         }
2865                     }
2866                   else
2867                     {
2868                       /* A non-allocatable target variable with C
2869                          interoperable type and type parameters must be
2870                          interoperable.  */
2871                       if (args_sym && args_sym->attr.dimension)
2872                         {
2873                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2874                             {
2875                               gfc_error ("Assumed-shape array '%s' at %L "
2876                                          "cannot be an argument to the "
2877                                          "procedure '%s' because "
2878                                          "it is not C interoperable",
2879                                          args_sym->name,
2880                                          &(args->expr->where), sym->name);
2881                               retval = FAILURE;
2882                             }
2883                           else if (args_sym->as->type == AS_DEFERRED)
2884                             {
2885                               gfc_error ("Deferred-shape array '%s' at %L "
2886                                          "cannot be an argument to the "
2887                                          "procedure '%s' because "
2888                                          "it is not C interoperable",
2889                                          args_sym->name,
2890                                          &(args->expr->where), sym->name);
2891                               retval = FAILURE;
2892                             }
2893                         }
2894                               
2895                       /* Make sure it's not a character string.  Arrays of
2896                          any type should be ok if the variable is of a C
2897                          interoperable type.  */
2898                       if (arg_ts->type == BT_CHARACTER)
2899                         if (arg_ts->u.cl != NULL
2900                             && (arg_ts->u.cl->length == NULL
2901                                 || arg_ts->u.cl->length->expr_type
2902                                    != EXPR_CONSTANT
2903                                 || mpz_cmp_si
2904                                     (arg_ts->u.cl->length->value.integer, 1)
2905                                    != 0)
2906                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2907                           {
2908                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2909                                            "at %L must have a length of 1",
2910                                            args_sym->name, sym->name,
2911                                            &(args->expr->where));
2912                             retval = FAILURE;
2913                           }
2914                     }
2915                 }
2916               else if (arg_attr.pointer
2917                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2918                 {
2919                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2920                      scalar pointer.  */
2921                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2922                                  "associated scalar POINTER", args_sym->name,
2923                                  sym->name, &(args->expr->where));
2924                   retval = FAILURE;
2925                 }
2926             }
2927           else
2928             {
2929               /* The parameter is not required to be C interoperable.  If it
2930                  is not C interoperable, it must be a nonpolymorphic scalar
2931                  with no length type parameters.  It still must have either
2932                  the pointer or target attribute, and it can be
2933                  allocatable (but must be allocated when c_loc is called).  */
2934               if (args->expr->rank != 0 
2935                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2936                 {
2937                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2938                                  "scalar", args_sym->name, sym->name,
2939                                  &(args->expr->where));
2940                   retval = FAILURE;
2941                 }
2942               else if (arg_ts->type == BT_CHARACTER 
2943                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2944                 {
2945                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2946                                  "%L must have a length of 1",
2947                                  args_sym->name, sym->name,
2948                                  &(args->expr->where));
2949                   retval = FAILURE;
2950                 }
2951               else if (arg_ts->type == BT_CLASS)
2952                 {
2953                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
2954                                  "polymorphic", args_sym->name, sym->name,
2955                                  &(args->expr->where));
2956                   retval = FAILURE;
2957                 }
2958             }
2959         }
2960       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2961         {
2962           if (args_sym->attr.flavor != FL_PROCEDURE)
2963             {
2964               /* TODO: Update this error message to allow for procedure
2965                  pointers once they are implemented.  */
2966               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2967                              "procedure",
2968                              args_sym->name, sym->name,
2969                              &(args->expr->where));
2970               retval = FAILURE;
2971             }
2972           else if (args_sym->attr.is_bind_c != 1)
2973             {
2974               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2975                              "BIND(C)",
2976                              args_sym->name, sym->name,
2977                              &(args->expr->where));
2978               retval = FAILURE;
2979             }
2980         }
2981       
2982       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2983       *new_sym = sym;
2984     }
2985   else
2986     {
2987       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2988                           "iso_c_binding function: '%s'!\n", sym->name);
2989     }
2990
2991   return retval;
2992 }
2993
2994
2995 /* Resolve a function call, which means resolving the arguments, then figuring
2996    out which entity the name refers to.  */
2997
2998 static gfc_try
2999 resolve_function (gfc_expr *expr)
3000 {
3001   gfc_actual_arglist *arg;
3002   gfc_symbol *sym;
3003   const char *name;
3004   gfc_try t;
3005   int temp;
3006   procedure_type p = PROC_INTRINSIC;
3007   bool no_formal_args;
3008
3009   sym = NULL;
3010   if (expr->symtree)
3011     sym = expr->symtree->n.sym;
3012
3013   /* If this is a procedure pointer component, it has already been resolved.  */
3014   if (gfc_is_proc_ptr_comp (expr, NULL))
3015     return SUCCESS;
3016   
3017   if (sym && sym->attr.intrinsic
3018       && resolve_intrinsic (sym, &expr->where) == FAILURE)
3019     return FAILURE;
3020
3021   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
3022     {
3023       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
3024       return FAILURE;
3025     }
3026
3027   /* If this ia a deferred TBP with an abstract interface (which may
3028      of course be referenced), expr->value.function.esym will be set.  */
3029   if (sym && sym->attr.abstract && !expr->value.function.esym)
3030     {
3031       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3032                  sym->name, &expr->where);
3033       return FAILURE;
3034     }
3035
3036   /* Switch off assumed size checking and do this again for certain kinds
3037      of procedure, once the procedure itself is resolved.  */
3038   need_full_assumed_size++;
3039
3040   if (expr->symtree && expr->symtree->n.sym)
3041     p = expr->symtree->n.sym->attr.proc;
3042
3043   if (expr->value.function.isym && expr->value.function.isym->inquiry)
3044     inquiry_argument = true;
3045   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
3046
3047   if (resolve_actual_arglist (expr->value.function.actual,
3048                               p, no_formal_args) == FAILURE)
3049     {
3050       inquiry_argument = false;
3051       return FAILURE;
3052     }
3053
3054   inquiry_argument = false;
3055  
3056   /* Need to setup the call to the correct c_associated, depending on
3057      the number of cptrs to user gives to compare.  */
3058   if (sym && sym->attr.is_iso_c == 1)
3059     {
3060       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
3061           == FAILURE)
3062         return FAILURE;
3063       
3064       /* Get the symtree for the new symbol (resolved func).
3065          the old one will be freed later, when it's no longer used.  */
3066       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
3067     }
3068   
3069   /* Resume assumed_size checking.  */
3070   need_full_assumed_size--;
3071
3072   /* If the procedure is external, check for usage.  */
3073   if (sym && is_external_proc (sym))
3074     resolve_global_procedure (sym, &expr->where,
3075                               &expr->value.function.actual, 0);
3076
3077   if (sym && sym->ts.type == BT_CHARACTER
3078       && sym->ts.u.cl
3079       && sym->ts.u.cl->length == NULL
3080       && !sym->attr.dummy
3081       && !sym->ts.deferred
3082       && expr->value.function.esym == NULL
3083       && !sym->attr.contained)
3084     {
3085       /* Internal procedures are taken care of in resolve_contained_fntype.  */
3086       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
3087                  "be used at %L since it is not a dummy argument",
3088                  sym->name, &expr->where);
3089       return FAILURE;
3090     }
3091
3092   /* See if function is already resolved.  */
3093
3094   if (expr->value.function.name != NULL)
3095     {
3096       if (expr->ts.type == BT_UNKNOWN)
3097         expr->ts = sym->ts;
3098       t = SUCCESS;
3099     }
3100   else
3101     {
3102       /* Apply the rules of section 14.1.2.  */
3103
3104       switch (procedure_kind (sym))
3105         {
3106         case PTYPE_GENERIC:
3107           t = resolve_generic_f (expr);
3108           break;
3109
3110         case PTYPE_SPECIFIC:
3111           t = resolve_specific_f (expr);
3112           break;
3113
3114         case PTYPE_UNKNOWN:
3115           t = resolve_unknown_f (expr);
3116           break;
3117
3118         default:
3119           gfc_internal_error ("resolve_function(): bad function type");
3120         }
3121     }
3122
3123   /* If the expression is still a function (it might have simplified),
3124      then we check to see if we are calling an elemental function.  */
3125
3126   if (expr->expr_type != EXPR_FUNCTION)
3127     return t;
3128
3129   temp = need_full_assumed_size;
3130   need_full_assumed_size = 0;
3131
3132   if (resolve_elemental_actual (expr, NULL) == FAILURE)
3133     return FAILURE;
3134
3135   if (omp_workshare_flag
3136       && expr->value.function.esym
3137       && ! gfc_elemental (expr->value.function.esym))
3138     {
3139       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
3140                  "in WORKSHARE construct", expr->value.function.esym->name,
3141                  &expr->where);
3142       t = FAILURE;
3143     }
3144
3145 #define GENERIC_ID expr->value.function.isym->id
3146   else if (expr->value.function.actual != NULL
3147            && expr->value.function.isym != NULL
3148            && GENERIC_ID != GFC_ISYM_LBOUND
3149            && GENERIC_ID != GFC_ISYM_LEN
3150            && GENERIC_ID != GFC_ISYM_LOC
3151            && GENERIC_ID != GFC_ISYM_PRESENT)
3152     {
3153       /* Array intrinsics must also have the last upper bound of an
3154          assumed size array argument.  UBOUND and SIZE have to be
3155          excluded from the check if the second argument is anything
3156          than a constant.  */
3157
3158       for (arg = expr->value.function.actual; arg; arg = arg->next)
3159         {
3160           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3161               && arg->next != NULL && arg->next->expr)
3162             {
3163               if (arg->next->expr->expr_type != EXPR_CONSTANT)
3164                 break;
3165
3166               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
3167                 break;
3168
3169               if ((int)mpz_get_si (arg->next->expr->value.integer)
3170                         < arg->expr->rank)
3171                 break;
3172             }
3173
3174           if (arg->expr != NULL
3175               && arg->expr->rank > 0
3176               && resolve_assumed_size_actual (arg->expr))
3177             return FAILURE;
3178         }
3179     }
3180 #undef GENERIC_ID
3181
3182   need_full_assumed_size = temp;
3183   name = NULL;
3184
3185   if (!pure_function (expr, &name) && name)
3186     {
3187       if (forall_flag)
3188         {
3189           gfc_error ("Reference to non-PURE function '%s' at %L inside a "
3190                      "FORALL %s", name, &expr->where,
3191                      forall_flag == 2 ? "mask" : "block");
3192           t = FAILURE;
3193         }
3194       else if (do_concurrent_flag)
3195         {
3196           gfc_error ("Reference to non-PURE function '%s' at %L inside a "
3197                      "DO CONCURRENT %s", name, &expr->where,
3198                      do_concurrent_flag == 2 ? "mask" : "block");
3199           t = FAILURE;
3200         }
3201       else if (gfc_pure (NULL))
3202         {
3203           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
3204                      "procedure within a PURE procedure", name, &expr->where);
3205           t = FAILURE;
3206         }
3207
3208       if (gfc_implicit_pure (NULL))
3209         gfc_current_ns->proc_name->attr.implicit_pure = 0;
3210     }
3211
3212   /* Functions without the RECURSIVE attribution are not allowed to
3213    * call themselves.  */
3214   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3215     {
3216       gfc_symbol *esym;
3217       esym = expr->value.function.esym;
3218
3219       if (is_illegal_recursion (esym, gfc_current_ns))
3220       {
3221         if (esym->attr.entry && esym->ns->entries)
3222           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3223                      " function '%s' is not RECURSIVE",
3224                      esym->name, &expr->where, esym->ns->entries->sym->name);
3225         else
3226           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
3227                      " is not RECURSIVE", esym->name, &expr->where);
3228
3229         t = FAILURE;
3230       }
3231     }
3232
3233   /* Character lengths of use associated functions may contains references to
3234      symbols not referenced from the current program unit otherwise.  Make sure
3235      those symbols are marked as referenced.  */
3236
3237   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3238       && expr->value.function.esym->attr.use_assoc)
3239     {
3240       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3241     }
3242
3243   /* Make sure that the expression has a typespec that works.  */
3244   if (expr->ts.type == BT_UNKNOWN)
3245     {
3246       if (expr->symtree->n.sym->result
3247             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3248             && !expr->symtree->n.sym->result->attr.proc_pointer)
3249         expr->ts = expr->symtree->n.sym->result->ts;
3250     }
3251
3252   return t;
3253 }
3254
3255
3256 /************* Subroutine resolution *************/
3257
3258 static void
3259 pure_subroutine (gfc_code *c, gfc_symbol *sym)
3260 {
3261   if (gfc_pure (sym))
3262     return;
3263
3264   if (forall_flag)
3265     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
3266                sym->name, &c->loc);
3267   else if (do_concurrent_flag)
3268     gfc_error ("Subroutine call to '%s' in DO CONCURRENT block at %L is not "
3269                "PURE", sym->name, &c->loc);
3270   else if (gfc_pure (NULL))
3271     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
3272                &c->loc);
3273
3274   if (gfc_implicit_pure (NULL))
3275     gfc_current_ns->proc_name->attr.implicit_pure = 0;
3276 }
3277
3278
3279 static match
3280 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3281 {
3282   gfc_symbol *s;
3283
3284   if (sym->attr.generic)
3285     {
3286       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3287       if (s != NULL)
3288         {
3289           c->resolved_sym = s;
3290           pure_subroutine (c, s);
3291           return MATCH_YES;
3292         }
3293
3294       /* TODO: Need to search for elemental references in generic interface.  */
3295     }
3296
3297   if (sym->attr.intrinsic)
3298     return gfc_intrinsic_sub_interface (c, 0);
3299
3300   return MATCH_NO;
3301 }
3302
3303
3304 static gfc_try
3305 resolve_generic_s (gfc_code *c)
3306 {
3307   gfc_symbol *sym;
3308   match m;
3309
3310   sym = c->symtree->n.sym;
3311
3312   for (;;)
3313     {
3314       m = resolve_generic_s0 (c, sym);
3315       if (m == MATCH_YES)
3316         return SUCCESS;
3317       else if (m == MATCH_ERROR)
3318         return FAILURE;
3319
3320 generic:
3321       if (sym->ns->parent == NULL)
3322         break;
3323       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3324
3325       if (sym == NULL)
3326         break;
3327       if (!generic_sym (sym))
3328         goto generic;
3329     }
3330
3331   /* Last ditch attempt.  See if the reference is to an intrinsic
3332      that possesses a matching interface.  14.1.2.4  */
3333   sym = c->symtree->n.sym;
3334
3335   if (!gfc_is_intrinsic (sym, 1, c->loc))
3336     {
3337       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3338                  sym->name, &c->loc);
3339       return FAILURE;
3340     }
3341
3342   m = gfc_intrinsic_sub_interface (c, 0);
3343   if (m == MATCH_YES)
3344     return SUCCESS;
3345   if (m == MATCH_NO)
3346     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3347                "intrinsic subroutine interface", sym->name, &c->loc);
3348
3349   return FAILURE;
3350 }
3351
3352
3353 /* Set the name and binding label of the subroutine symbol in the call
3354    expression represented by 'c' to include the type and kind of the
3355    second parameter.  This function is for resolving the appropriate
3356    version of c_f_pointer() and c_f_procpointer().  For example, a
3357    call to c_f_pointer() for a default integer pointer could have a
3358    name of c_f_pointer_i4.  If no second arg exists, which is an error
3359    for these two functions, it defaults to the generic symbol's name
3360    and binding label.  */
3361
3362 static void
3363 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3364                     char *name, const char **binding_label)
3365 {
3366   gfc_expr *arg = NULL;
3367   char type;
3368   int kind;
3369
3370   /* The second arg of c_f_pointer and c_f_procpointer determines
3371      the type and kind for the procedure name.  */
3372   arg = c->ext.actual->next->expr;
3373
3374   if (arg != NULL)
3375     {
3376       /* Set up the name to have the given symbol's name,
3377          plus the type and kind.  */
3378       /* a derived type is marked with the type letter 'u' */
3379       if (arg->ts.type == BT_DERIVED)
3380         {
3381           type = 'd';
3382           kind = 0; /* set the kind as 0 for now */
3383         }
3384       else
3385         {
3386           type = gfc_type_letter (arg->ts.type);
3387           kind = arg->ts.kind;
3388         }
3389
3390       if (arg->ts.type == BT_CHARACTER)
3391         /* Kind info for character strings not needed.  */
3392         kind = 0;
3393
3394       sprintf (name, "%s_%c%d", sym->name, type, kind);
3395       /* Set up the binding label as the given symbol's label plus
3396          the type and kind.  */
3397       *binding_label = gfc_get_string ("%s_%c%d", sym->binding_label, type, 
3398                                        kind);
3399     }
3400   else
3401     {
3402       /* If the second arg is missing, set the name and label as
3403          was, cause it should at least be found, and the missing
3404          arg error will be caught by compare_parameters().  */
3405       sprintf (name, "%s", sym->name);
3406       *binding_label = sym->binding_label;
3407     }
3408    
3409   return;
3410 }
3411
3412
3413 /* Resolve a generic version of the iso_c_binding procedure given
3414    (sym) to the specific one based on the type and kind of the
3415    argument(s).  Currently, this function resolves c_f_pointer() and
3416    c_f_procpointer based on the type and kind of the second argument
3417    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3418    Upon successfully exiting, c->resolved_sym will hold the resolved
3419    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3420    otherwise.  */
3421
3422 match
3423 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3424 {
3425   gfc_symbol *new_sym;
3426   /* this is fine, since we know the names won't use the max */
3427   char name[GFC_MAX_SYMBOL_LEN + 1];
3428   const char* binding_label;
3429   /* default to success; will override if find error */
3430   match m = MATCH_YES;
3431
3432   /* Make sure the actual arguments are in the necessary order (based on the 
3433      formal args) before resolving.  */
3434   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3435
3436   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3437       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3438     {
3439       set_name_and_label (c, sym, name, &binding_label);
3440       
3441       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3442         {
3443           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3444             {
3445               /* Make sure we got a third arg if the second arg has non-zero
3446                  rank.  We must also check that the type and rank are
3447                  correct since we short-circuit this check in
3448                  gfc_procedure_use() (called above to sort actual args).  */
3449               if (c->ext.actual->next->expr->rank != 0)
3450                 {
3451                   if(c->ext.actual->next->next == NULL 
3452                      || c->ext.actual->next->next->expr == NULL)
3453                     {
3454                       m = MATCH_ERROR;
3455                       gfc_error ("Missing SHAPE parameter for call to %s "
3456                                  "at %L", sym->name, &(c->loc));
3457                     }
3458                   else if (c->ext.actual->next->next->expr->ts.type
3459                            != BT_INTEGER
3460                            || c->ext.actual->next->next->expr->rank != 1)
3461                     {
3462                       m = MATCH_ERROR;
3463                       gfc_error ("SHAPE parameter for call to %s at %L must "
3464                                  "be a rank 1 INTEGER array", sym->name,
3465                                  &(c->loc));
3466                     }
3467                 }
3468             }
3469         }
3470       
3471       if (m != MATCH_ERROR)
3472         {
3473           /* the 1 means to add the optional arg to formal list */
3474           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3475          
3476           /* for error reporting, say it's declared where the original was */
3477           new_sym->declared_at = sym->declared_at;
3478         }
3479     }
3480   else
3481     {
3482       /* no differences for c_loc or c_funloc */
3483       new_sym = sym;
3484     }
3485
3486   /* set the resolved symbol */
3487   if (m != MATCH_ERROR)
3488     c->resolved_sym = new_sym;
3489   else
3490     c->resolved_sym = sym;
3491   
3492   return m;
3493 }
3494
3495
3496 /* Resolve a subroutine call known to be specific.  */
3497
3498 static match
3499 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3500 {
3501   match m;
3502
3503   if(sym->attr.is_iso_c)
3504     {
3505       m = gfc_iso_c_sub_interface (c,sym);
3506       return m;
3507     }
3508   
3509   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3510     {
3511       if (sym->attr.dummy)
3512         {
3513           sym->attr.proc = PROC_DUMMY;
3514           goto found;
3515         }
3516
3517       sym->attr.proc = PROC_EXTERNAL;
3518       goto found;
3519     }
3520
3521   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3522     goto found;
3523
3524   if (sym->attr.intrinsic)
3525     {
3526       m = gfc_intrinsic_sub_interface (c, 1);
3527       if (m == MATCH_YES)
3528         return MATCH_YES;
3529       if (m == MATCH_NO)
3530         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3531                    "with an intrinsic", sym->name, &c->loc);
3532
3533       return MATCH_ERROR;
3534     }
3535
3536   return MATCH_NO;
3537
3538 found:
3539   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3540
3541   c->resolved_sym = sym;
3542   pure_subroutine (c, sym);
3543
3544   return MATCH_YES;
3545 }
3546
3547
3548 static gfc_try
3549 resolve_specific_s (gfc_code *c)
3550 {
3551   gfc_symbol *sym;
3552   match m;
3553
3554   sym = c->symtree->n.sym;
3555
3556   for (;;)
3557     {
3558       m = resolve_specific_s0 (c, sym);
3559       if (m == MATCH_YES)
3560         return SUCCESS;
3561       if (m == MATCH_ERROR)
3562         return FAILURE;
3563
3564       if (sym->ns->parent == NULL)
3565         break;
3566
3567       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3568
3569       if (sym == NULL)
3570         break;
3571     }
3572
3573   sym = c->symtree->n.sym;
3574   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3575              sym->name, &c->loc);
3576
3577   return FAILURE;
3578 }
3579
3580
3581 /* Resolve a subroutine call not known to be generic nor specific.  */
3582
3583 static gfc_try
3584 resolve_unknown_s (gfc_code *c)
3585 {
3586   gfc_symbol *sym;
3587
3588   sym = c->symtree->n.sym;
3589
3590   if (sym->attr.dummy)
3591     {
3592       sym->attr.proc = PROC_DUMMY;
3593       goto found;
3594     }
3595
3596   /* See if we have an intrinsic function reference.  */
3597
3598   if (gfc_is_intrinsic (sym, 1, c->loc))
3599     {
3600       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3601         return SUCCESS;
3602       return FAILURE;
3603     }
3604
3605   /* The reference is to an external name.  */
3606
3607 found:
3608   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3609
3610   c->resolved_sym = sym;
3611
3612   pure_subroutine (c, sym);
3613
3614   return SUCCESS;
3615 }
3616
3617
3618 /* Resolve a subroutine call.  Although it was tempting to use the same code
3619    for functions, subroutines and functions are stored differently and this
3620    makes things awkward.  */
3621
3622 static gfc_try
3623 resolve_call (gfc_code *c)
3624 {
3625   gfc_try t;
3626   procedure_type ptype = PROC_INTRINSIC;
3627   gfc_symbol *csym, *sym;
3628   bool no_formal_args;
3629
3630   csym = c->symtree ? c->symtree->n.sym : NULL;
3631
3632   if (csym && csym->ts.type != BT_UNKNOWN)
3633     {
3634       gfc_error ("'%s' at %L has a type, which is not consistent with "
3635                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3636       return FAILURE;
3637     }
3638
3639   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3640     {
3641       gfc_symtree *st;
3642       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3643       sym = st ? st->n.sym : NULL;
3644       if (sym && csym != sym
3645               && sym->ns == gfc_current_ns
3646               && sym->attr.flavor == FL_PROCEDURE
3647               && sym->attr.contained)
3648         {
3649           sym->refs++;
3650           if (csym->attr.generic)
3651             c->symtree->n.sym = sym;
3652           else
3653             c->symtree = st;
3654           csym = c->symtree->n.sym;
3655         }
3656     }
3657
3658   /* If this ia a deferred TBP with an abstract interface
3659      (which may of course be referenced), c->expr1 will be set.  */
3660   if (csym && csym->attr.abstract && !c->expr1)
3661     {
3662       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3663                  csym->name, &c->loc);
3664       return FAILURE;
3665     }
3666
3667   /* Subroutines without the RECURSIVE attribution are not allowed to
3668    * call themselves.  */
3669   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3670     {
3671       if (csym->attr.entry && csym->ns->entries)
3672         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3673                    " subroutine '%s' is not RECURSIVE",
3674                    csym->name, &c->loc, csym->ns->entries->sym->name);
3675       else
3676         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3677                    " is not RECURSIVE", csym->name, &c->loc);
3678
3679       t = FAILURE;
3680     }
3681
3682   /* Switch off assumed size checking and do this again for certain kinds
3683      of procedure, once the procedure itself is resolved.  */
3684   need_full_assumed_size++;
3685
3686   if (csym)
3687     ptype = csym->attr.proc;
3688
3689   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3690   if (resolve_actual_arglist (c->ext.actual, ptype,
3691                               no_formal_args) == FAILURE)
3692     return FAILURE;
3693
3694   /* Resume assumed_size checking.  */
3695   need_full_assumed_size--;
3696
3697   /* If external, check for usage.  */
3698   if (csym && is_external_proc (csym))
3699     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3700
3701   t = SUCCESS;
3702   if (c->resolved_sym == NULL)
3703     {
3704       c->resolved_isym = NULL;
3705       switch (procedure_kind (csym))
3706         {
3707         case PTYPE_GENERIC:
3708           t = resolve_generic_s (c);
3709           break;
3710
3711         case PTYPE_SPECIFIC:
3712           t = resolve_specific_s (c);
3713           break;
3714
3715         case PTYPE_UNKNOWN:
3716           t = resolve_unknown_s (c);
3717           break;
3718
3719         default:
3720           gfc_internal_error ("resolve_subroutine(): bad function type");
3721         }
3722     }
3723
3724   /* Some checks of elemental subroutine actual arguments.  */
3725   if (resolve_elemental_actual (NULL, c) == FAILURE)
3726     return FAILURE;
3727
3728   return t;
3729 }
3730
3731
3732 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3733    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3734    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3735    if their shapes do not match.  If either op1->shape or op2->shape is
3736    NULL, return SUCCESS.  */
3737
3738 static gfc_try
3739 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3740 {
3741   gfc_try t;
3742   int i;
3743
3744   t = SUCCESS;
3745
3746   if (op1->shape != NULL && op2->shape != NULL)
3747     {
3748       for (i = 0; i < op1->rank; i++)
3749         {
3750           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3751            {
3752              gfc_error ("Shapes for operands at %L and %L are not conformable",
3753                          &op1->where, &op2->where);
3754              t = FAILURE;
3755              break;
3756            }
3757         }
3758     }
3759
3760   return t;
3761 }
3762
3763
3764 /* Resolve an operator expression node.  This can involve replacing the
3765    operation with a user defined function call.  */
3766
3767 static gfc_try
3768 resolve_operator (gfc_expr *e)
3769 {
3770   gfc_expr *op1, *op2;
3771   char msg[200];
3772   bool dual_locus_error;
3773   gfc_try t;
3774
3775   /* Resolve all subnodes-- give them types.  */
3776
3777   switch (e->value.op.op)
3778     {
3779     default:
3780       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3781         return FAILURE;
3782
3783     /* Fall through...  */
3784
3785     case INTRINSIC_NOT:
3786     case INTRINSIC_UPLUS:
3787     case INTRINSIC_UMINUS:
3788     case INTRINSIC_PARENTHESES:
3789       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3790         return FAILURE;
3791       break;
3792     }
3793
3794   /* Typecheck the new node.  */
3795
3796   op1 = e->value.op.op1;
3797   op2 = e->value.op.op2;
3798   dual_locus_error = false;
3799
3800   if ((op1 && op1->expr_type == EXPR_NULL)
3801       || (op2 && op2->expr_type == EXPR_NULL))
3802     {
3803       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3804       goto bad_op;
3805     }
3806
3807   switch (e->value.op.op)
3808     {
3809     case INTRINSIC_UPLUS:
3810     case INTRINSIC_UMINUS:
3811       if (op1->ts.type == BT_INTEGER
3812           || op1->ts.type == BT_REAL
3813           || op1->ts.type == BT_COMPLEX)
3814         {
3815           e->ts = op1->ts;
3816           break;
3817         }
3818
3819       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3820                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3821       goto bad_op;
3822
3823     case INTRINSIC_PLUS:
3824     case INTRINSIC_MINUS:
3825     case INTRINSIC_TIMES:
3826     case INTRINSIC_DIVIDE:
3827     case INTRINSIC_POWER:
3828       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3829         {
3830           gfc_type_convert_binary (e, 1);
3831           break;
3832         }
3833
3834       sprintf (msg,
3835                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3836                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3837                gfc_typename (&op2->ts));
3838       goto bad_op;
3839
3840     case INTRINSIC_CONCAT:
3841       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3842           && op1->ts.kind == op2->ts.kind)
3843         {
3844           e->ts.type = BT_CHARACTER;
3845           e->ts.kind = op1->ts.kind;
3846           break;
3847         }
3848
3849       sprintf (msg,
3850                _("Operands of string concatenation operator at %%L are %s/%s"),
3851                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3852       goto bad_op;
3853
3854     case INTRINSIC_AND:
3855     case INTRINSIC_OR:
3856     case INTRINSIC_EQV:
3857     case INTRINSIC_NEQV:
3858       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3859         {
3860           e->ts.type = BT_LOGICAL;
3861           e->ts.kind = gfc_kind_max (op1, op2);
3862           if (op1->ts.kind < e->ts.kind)
3863             gfc_convert_type (op1, &e->ts, 2);
3864           else if (op2->ts.kind < e->ts.kind)
3865             gfc_convert_type (op2, &e->ts, 2);
3866           break;
3867         }
3868
3869       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3870                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3871                gfc_typename (&op2->ts));
3872
3873       goto bad_op;
3874
3875     case INTRINSIC_NOT:
3876       if (op1->ts.type == BT_LOGICAL)
3877         {
3878           e->ts.type = BT_LOGICAL;
3879           e->ts.kind = op1->ts.kind;
3880           break;
3881         }
3882
3883       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3884                gfc_typename (&op1->ts));
3885       goto bad_op;
3886
3887     case INTRINSIC_GT:
3888     case INTRINSIC_GT_OS:
3889     case INTRINSIC_GE:
3890     case INTRINSIC_GE_OS:
3891     case INTRINSIC_LT:
3892     case INTRINSIC_LT_OS:
3893     case INTRINSIC_LE:
3894     case INTRINSIC_LE_OS:
3895       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3896         {
3897           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3898           goto bad_op;
3899         }
3900
3901       /* Fall through...  */
3902
3903     case INTRINSIC_EQ:
3904     case INTRINSIC_EQ_OS:
3905     case INTRINSIC_NE:
3906     case INTRINSIC_NE_OS:
3907       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3908           && op1->ts.kind == op2->ts.kind)
3909         {
3910           e->ts.type = BT_LOGICAL;
3911           e->ts.kind = gfc_default_logical_kind;
3912           break;
3913         }
3914
3915       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3916         {
3917           gfc_type_convert_binary (e, 1);
3918
3919           e->ts.type = BT_LOGICAL;
3920           e->ts.kind = gfc_default_logical_kind;
3921           break;
3922         }
3923
3924       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3925         sprintf (msg,
3926                  _("Logicals at %%L must be compared with %s instead of %s"),
3927                  (e->value.op.op == INTRINSIC_EQ 
3928                   || e->value.op.op == INTRINSIC_EQ_OS)
3929                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3930       else
3931         sprintf (msg,
3932                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3933                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3934                  gfc_typename (&op2->ts));
3935
3936       goto bad_op;
3937
3938     case INTRINSIC_USER:
3939       if (e->value.op.uop->op == NULL)
3940         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3941       else if (op2 == NULL)
3942         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3943                  e->value.op.uop->name, gfc_typename (&op1->ts));
3944       else
3945         {
3946           sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3947                    e->value.op.uop->name, gfc_typename (&op1->ts),
3948                    gfc_typename (&op2->ts));
3949           e->value.op.uop->op->sym->attr.referenced = 1;
3950         }
3951
3952       goto bad_op;
3953
3954     case INTRINSIC_PARENTHESES:
3955       e->ts = op1->ts;
3956       if (e->ts.type == BT_CHARACTER)
3957         e->ts.u.cl = op1->ts.u.cl;
3958       break;
3959
3960     default:
3961       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3962     }
3963
3964   /* Deal with arrayness of an operand through an operator.  */
3965
3966   t = SUCCESS;
3967
3968   switch (e->value.op.op)
3969     {
3970     case INTRINSIC_PLUS:
3971     case INTRINSIC_MINUS:
3972     case INTRINSIC_TIMES:
3973     case INTRINSIC_DIVIDE:
3974     case INTRINSIC_POWER:
3975     case INTRINSIC_CONCAT:
3976     case INTRINSIC_AND:
3977     case INTRINSIC_OR:
3978     case INTRINSIC_EQV:
3979     case INTRINSIC_NEQV:
3980     case INTRINSIC_EQ:
3981     case INTRINSIC_EQ_OS:
3982     case INTRINSIC_NE:
3983     case INTRINSIC_NE_OS:
3984     case INTRINSIC_GT:
3985     case INTRINSIC_GT_OS:
3986     case INTRINSIC_GE:
3987     case INTRINSIC_GE_OS:
3988     case INTRINSIC_LT:
3989     case INTRINSIC_LT_OS:
3990     case INTRINSIC_LE:
3991     case INTRINSIC_LE_OS:
3992
3993       if (op1->rank == 0 && op2->rank == 0)
3994         e->rank = 0;
3995
3996       if (op1->rank == 0 && op2->rank != 0)
3997         {
3998           e->rank = op2->rank;
3999
4000           if (e->shape == NULL)
4001             e->shape = gfc_copy_shape (op2->shape, op2->rank);
4002         }
4003
4004       if (op1->rank != 0 && op2->rank == 0)
4005         {
4006           e->rank = op1->rank;
4007
4008           if (e->shape == NULL)
4009             e->shape = gfc_copy_shape (op1->shape, op1->rank);
4010         }
4011
4012       if (op1->rank != 0 && op2->rank != 0)
4013         {
4014           if (op1->rank == op2->rank)
4015             {
4016               e->rank = op1->rank;
4017               if (e->shape == NULL)
4018                 {
4019                   t = compare_shapes (op1, op2);
4020                   if (t == FAILURE)
4021                     e->shape = NULL;
4022                   else
4023                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
4024                 }
4025             }
4026           else
4027             {
4028               /* Allow higher level expressions to work.  */
4029               e->rank = 0;
4030
4031               /* Try user-defined operators, and otherwise throw an error.  */
4032               dual_locus_error = true;
4033               sprintf (msg,
4034                        _("Inconsistent ranks for operator at %%L and %%L"));
4035               goto bad_op;
4036             }
4037         }
4038
4039       break;
4040
4041     case INTRINSIC_PARENTHESES:
4042     case INTRINSIC_NOT:
4043     case INTRINSIC_UPLUS:
4044     case INTRINSIC_UMINUS:
4045       /* Simply copy arrayness attribute */
4046       e->rank = op1->rank;
4047
4048       if (e->shape == NULL)
4049         e->shape = gfc_copy_shape (op1->shape, op1->rank);
4050
4051       break;
4052
4053     default:
4054       break;
4055     }
4056
4057   /* Attempt to simplify the expression.  */
4058   if (t == SUCCESS)
4059     {
4060       t = gfc_simplify_expr (e, 0);
4061       /* Some calls do not succeed in simplification and return FAILURE
4062          even though there is no error; e.g. variable references to
4063          PARAMETER arrays.  */
4064       if (!gfc_is_constant_expr (e))
4065         t = SUCCESS;
4066     }
4067   return t;
4068
4069 bad_op:
4070
4071   {
4072     match m = gfc_extend_expr (e);
4073     if (m == MATCH_YES)
4074       return SUCCESS;
4075     if (m == MATCH_ERROR)
4076       return FAILURE;
4077   }
4078
4079   if (dual_locus_error)
4080     gfc_error (msg, &op1->where, &op2->where);
4081   else
4082     gfc_error (msg, &e->where);
4083
4084   return FAILURE;
4085 }
4086
4087
4088 /************** Array resolution subroutines **************/
4089
4090 typedef enum
4091 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
4092 comparison;
4093
4094 /* Compare two integer expressions.  */
4095
4096 static comparison
4097 compare_bound (gfc_expr *a, gfc_expr *b)
4098 {
4099   int i;
4100
4101   if (a == NULL || a->expr_type != EXPR_CONSTANT
4102       || b == NULL || b->expr_type != EXPR_CONSTANT)
4103     return CMP_UNKNOWN;
4104
4105   /* If either of the types isn't INTEGER, we must have
4106      raised an error earlier.  */
4107
4108   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
4109     return CMP_UNKNOWN;
4110
4111   i = mpz_cmp (a->value.integer, b->value.integer);
4112
4113   if (i < 0)
4114     return CMP_LT;
4115   if (i > 0)
4116     return CMP_GT;
4117   return CMP_EQ;
4118 }
4119
4120
4121 /* Compare an integer expression with an integer.  */
4122
4123 static comparison
4124 compare_bound_int (gfc_expr *a, int b)
4125 {
4126   int i;
4127
4128   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4129     return CMP_UNKNOWN;
4130
4131   if (a->ts.type != BT_INTEGER)
4132     gfc_internal_error ("compare_bound_int(): Bad expression");
4133
4134   i = mpz_cmp_si (a->value.integer, b);
4135
4136   if (i < 0)
4137     return CMP_LT;
4138   if (i > 0)
4139     return CMP_GT;
4140   return CMP_EQ;
4141 }
4142
4143
4144 /* Compare an integer expression with a mpz_t.  */
4145
4146 static comparison
4147 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
4148 {
4149   int i;
4150
4151   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4152     return CMP_UNKNOWN;
4153
4154   if (a->ts.type != BT_INTEGER)
4155     gfc_internal_error ("compare_bound_int(): Bad expression");
4156
4157   i = mpz_cmp (a->value.integer, b);
4158
4159   if (i < 0)
4160     return CMP_LT;
4161   if (i > 0)
4162     return CMP_GT;
4163   return CMP_EQ;
4164 }
4165
4166
4167 /* Compute the last value of a sequence given by a triplet.  
4168    Return 0 if it wasn't able to compute the last value, or if the
4169    sequence if empty, and 1 otherwise.  */
4170
4171 static int
4172 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
4173                                 gfc_expr *stride, mpz_t last)
4174 {
4175   mpz_t rem;
4176
4177   if (start == NULL || start->expr_type != EXPR_CONSTANT
4178       || end == NULL || end->expr_type != EXPR_CONSTANT
4179       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
4180     return 0;
4181
4182   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
4183       || (stride != NULL && stride->ts.type != BT_INTEGER))
4184     return 0;
4185
4186   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
4187     {
4188       if (compare_bound (start, end) == CMP_GT)
4189         return 0;
4190       mpz_set (last, end->value.integer);
4191       return 1;
4192     }
4193
4194   if (compare_bound_int (stride, 0) == CMP_GT)
4195     {
4196       /* Stride is positive */
4197       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
4198         return 0;
4199     }
4200   else
4201     {
4202       /* Stride is negative */
4203       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
4204         return 0;
4205     }
4206
4207   mpz_init (rem);
4208   mpz_sub (rem, end->value.integer, start->value.integer);
4209   mpz_tdiv_r (rem, rem, stride->value.integer);
4210   mpz_sub (last, end->value.integer, rem);
4211   mpz_clear (rem);
4212
4213   return 1;
4214 }
4215
4216
4217 /* Compare a single dimension of an array reference to the array
4218    specification.  */
4219
4220 static gfc_try
4221 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
4222 {
4223   mpz_t last_value;
4224
4225   if (ar->dimen_type[i] == DIMEN_STAR)
4226     {
4227       gcc_assert (ar->stride[i] == NULL);
4228       /* This implies [*] as [*:] and [*:3] are not possible.  */
4229       if (ar->start[i] == NULL)
4230         {
4231           gcc_assert (ar->end[i] == NULL);
4232           return SUCCESS;
4233         }
4234     }
4235
4236 /* Given start, end and stride values, calculate the minimum and
4237    maximum referenced indexes.  */
4238
4239   switch (ar->dimen_type[i])
4240     {
4241     case DIMEN_VECTOR:
4242     case DIMEN_THIS_IMAGE:
4243       break;
4244
4245     case DIMEN_STAR:
4246     case DIMEN_ELEMENT:
4247       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4248         {
4249           if (i < as->rank)
4250             gfc_warning ("Array reference at %L is out of bounds "
4251                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
4252                          mpz_get_si (ar->start[i]->value.integer),
4253                          mpz_get_si (as->lower[i]->value.integer), i+1);
4254           else
4255             gfc_warning ("Array reference at %L is out of bounds "
4256                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
4257                          mpz_get_si (ar->start[i]->value.integer),
4258                          mpz_get_si (as->lower[i]->value.integer),
4259                          i + 1 - as->rank);
4260           return SUCCESS;
4261         }
4262       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4263         {
4264           if (i < as->rank)
4265             gfc_warning ("Array reference at %L is out of bounds "
4266                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
4267                          mpz_get_si (ar->start[i]->value.integer),
4268                          mpz_get_si (as->upper[i]->value.integer), i+1);
4269           else
4270             gfc_warning ("Array reference at %L is out of bounds "
4271                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
4272                          mpz_get_si (ar->start[i]->value.integer),
4273                          mpz_get_si (as->upper[i]->value.integer),
4274                          i + 1 - as->rank);
4275           return SUCCESS;
4276         }
4277
4278       break;
4279
4280     case DIMEN_RANGE:
4281       {
4282 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4283 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4284
4285         comparison comp_start_end = compare_bound (AR_START, AR_END);
4286
4287         /* Check for zero stride, which is not allowed.  */
4288         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4289           {
4290             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4291             return FAILURE;
4292           }
4293
4294         /* if start == len || (stride > 0 && start < len)
4295                            || (stride < 0 && start > len),
4296            then the array section contains at least one element.  In this
4297            case, there is an out-of-bounds access if
4298            (start < lower || start > upper).  */
4299         if (compare_bound (AR_START, AR_END) == CMP_EQ
4300             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4301                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4302             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4303                 && comp_start_end == CMP_GT))
4304           {
4305             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4306               {
4307                 gfc_warning ("Lower array reference at %L is out of bounds "
4308                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4309                        mpz_get_si (AR_START->value.integer),
4310                        mpz_get_si (as->lower[i]->value.integer), i+1);
4311                 return SUCCESS;
4312               }
4313             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4314               {
4315                 gfc_warning ("Lower array reference at %L is out of bounds "
4316                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4317                        mpz_get_si (AR_START->value.integer),
4318                        mpz_get_si (as->upper[i]->value.integer), i+1);
4319                 return SUCCESS;
4320               }
4321           }
4322
4323         /* If we can compute the highest index of the array section,
4324            then it also has to be between lower and upper.  */
4325         mpz_init (last_value);
4326         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4327                                             last_value))
4328           {
4329             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4330               {
4331                 gfc_warning ("Upper array reference at %L is out of bounds "
4332                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4333                        mpz_get_si (last_value),
4334                        mpz_get_si (as->lower[i]->value.integer), i+1);
4335                 mpz_clear (last_value);
4336                 return SUCCESS;
4337               }
4338             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4339               {
4340                 gfc_warning ("Upper array reference at %L is out of bounds "
4341                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4342                        mpz_get_si (last_value),
4343                        mpz_get_si (as->upper[i]->value.integer), i+1);
4344                 mpz_clear (last_value);
4345                 return SUCCESS;
4346               }
4347           }
4348         mpz_clear (last_value);
4349
4350 #undef AR_START
4351 #undef AR_END
4352       }
4353       break;
4354
4355     default:
4356       gfc_internal_error ("check_dimension(): Bad array reference");
4357     }
4358
4359   return SUCCESS;
4360 }
4361
4362
4363 /* Compare an array reference with an array specification.  */
4364
4365 static gfc_try
4366 compare_spec_to_ref (gfc_array_ref *ar)
4367 {
4368   gfc_array_spec *as;
4369   int i;
4370
4371   as = ar->as;
4372   i = as->rank - 1;
4373   /* TODO: Full array sections are only allowed as actual parameters.  */
4374   if (as->type == AS_ASSUMED_SIZE
4375       && (/*ar->type == AR_FULL
4376           ||*/ (ar->type == AR_SECTION
4377               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4378     {
4379       gfc_error ("Rightmost upper bound of assumed size array section "
4380                  "not specified at %L", &ar->where);
4381       return FAILURE;
4382     }
4383
4384   if (ar->type == AR_FULL)
4385     return SUCCESS;
4386
4387   if (as->rank != ar->dimen)
4388     {
4389       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4390                  &ar->where, ar->dimen, as->rank);
4391       return FAILURE;
4392     }
4393
4394   /* ar->codimen == 0 is a local array.  */
4395   if (as->corank != ar->codimen && ar->codimen != 0)
4396     {
4397       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4398                  &ar->where, ar->codimen, as->corank);
4399       return FAILURE;
4400     }
4401
4402   for (i = 0; i < as->rank; i++)
4403     if (check_dimension (i, ar, as) == FAILURE)
4404       return FAILURE;
4405
4406   /* Local access has no coarray spec.  */
4407   if (ar->codimen != 0)
4408     for (i = as->rank; i < as->rank + as->corank; i++)
4409       {
4410         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate
4411             && ar->dimen_type[i] != DIMEN_THIS_IMAGE)
4412           {
4413             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4414                        i + 1 - as->rank, &ar->where);
4415             return FAILURE;
4416           }
4417         if (check_dimension (i, ar, as) == FAILURE)
4418           return FAILURE;
4419       }
4420
4421   return SUCCESS;
4422 }
4423
4424
4425 /* Resolve one part of an array index.  */
4426
4427 static gfc_try
4428 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4429                      int force_index_integer_kind)
4430 {
4431   gfc_typespec ts;
4432
4433   if (index == NULL)
4434     return SUCCESS;
4435
4436   if (gfc_resolve_expr (index) == FAILURE)
4437     return FAILURE;
4438
4439   if (check_scalar && index->rank != 0)
4440     {
4441       gfc_error ("Array index at %L must be scalar", &index->where);
4442       return FAILURE;
4443     }
4444
4445   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4446     {
4447       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4448                  &index->where, gfc_basic_typename (index->ts.type));
4449       return FAILURE;
4450     }
4451
4452   if (index->ts.type == BT_REAL)
4453     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4454                         &index->where) == FAILURE)
4455       return FAILURE;
4456
4457   if ((index->ts.kind != gfc_index_integer_kind
4458        && force_index_integer_kind)
4459       || index->ts.type != BT_INTEGER)
4460     {
4461       gfc_clear_ts (&ts);
4462       ts.type = BT_INTEGER;
4463       ts.kind = gfc_index_integer_kind;
4464
4465       gfc_convert_type_warn (index, &ts, 2, 0);
4466     }
4467
4468   return SUCCESS;
4469 }
4470
4471 /* Resolve one part of an array index.  */
4472
4473 gfc_try
4474 gfc_resolve_index (gfc_expr *index, int check_scalar)
4475 {
4476   return gfc_resolve_index_1 (index, check_scalar, 1);
4477 }
4478
4479 /* Resolve a dim argument to an intrinsic function.  */
4480
4481 gfc_try
4482 gfc_resolve_dim_arg (gfc_expr *dim)
4483 {
4484   if (dim == NULL)
4485     return SUCCESS;
4486
4487   if (gfc_resolve_expr (dim) == FAILURE)
4488     return FAILURE;
4489
4490   if (dim->rank != 0)
4491     {
4492       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4493       return FAILURE;
4494
4495     }
4496
4497   if (dim->ts.type != BT_INTEGER)
4498     {
4499       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4500       return FAILURE;
4501     }
4502
4503   if (dim->ts.kind != gfc_index_integer_kind)
4504     {
4505       gfc_typespec ts;
4506
4507       gfc_clear_ts (&ts);
4508       ts.type = BT_INTEGER;
4509       ts.kind = gfc_index_integer_kind;
4510
4511       gfc_convert_type_warn (dim, &ts, 2, 0);
4512     }
4513
4514   return SUCCESS;
4515 }
4516
4517 /* Given an expression that contains array references, update those array
4518    references to point to the right array specifications.  While this is
4519    filled in during matching, this information is difficult to save and load
4520    in a module, so we take care of it here.
4521
4522    The idea here is that the original array reference comes from the
4523    base symbol.  We traverse the list of reference structures, setting
4524    the stored reference to references.  Component references can
4525    provide an additional array specification.  */
4526
4527 static void
4528 find_array_spec (gfc_expr *e)
4529 {
4530   gfc_array_spec *as;
4531   gfc_component *c;
4532   gfc_ref *ref;
4533
4534   if (e->symtree->n.sym->ts.type == BT_CLASS)
4535     as = CLASS_DATA (e->symtree->n.sym)->as;
4536   else
4537     as = e->symtree->n.sym->as;
4538
4539   for (ref = e->ref; ref; ref = ref->next)
4540     switch (ref->type)
4541       {
4542       case REF_ARRAY:
4543         if (as == NULL)
4544           gfc_internal_error ("find_array_spec(): Missing spec");
4545
4546         ref->u.ar.as = as;
4547         as = NULL;
4548         break;
4549
4550       case REF_COMPONENT:
4551         c = ref->u.c.component;
4552         if (c->attr.dimension)
4553           {
4554             if (as != NULL)
4555               gfc_internal_error ("find_array_spec(): unused as(1)");
4556             as = c->as;
4557           }
4558
4559         break;
4560
4561       case REF_SUBSTRING:
4562         break;
4563       }
4564
4565   if (as != NULL)
4566     gfc_internal_error ("find_array_spec(): unused as(2)");
4567 }
4568
4569
4570 /* Resolve an array reference.  */
4571
4572 static gfc_try
4573 resolve_array_ref (gfc_array_ref *ar)
4574 {
4575   int i, check_scalar;
4576   gfc_expr *e;
4577
4578   for (i = 0; i < ar->dimen + ar->codimen; i++)
4579     {
4580       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4581
4582       /* Do not force gfc_index_integer_kind for the start.  We can
4583          do fine with any integer kind.  This avoids temporary arrays
4584          created for indexing with a vector.  */
4585       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4586         return FAILURE;
4587       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4588         return FAILURE;
4589       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4590         return FAILURE;
4591
4592       e = ar->start[i];
4593
4594       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4595         switch (e->rank)
4596           {
4597           case 0:
4598             ar->dimen_type[i] = DIMEN_ELEMENT;
4599             break;
4600
4601           case 1:
4602             ar->dimen_type[i] = DIMEN_VECTOR;
4603             if (e->expr_type == EXPR_VARIABLE
4604                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4605               ar->start[i] = gfc_get_parentheses (e);
4606             break;
4607
4608           default:
4609             gfc_error ("Array index at %L is an array of rank %d",
4610                        &ar->c_where[i], e->rank);
4611             return FAILURE;
4612           }
4613
4614       /* Fill in the upper bound, which may be lower than the
4615          specified one for something like a(2:10:5), which is
4616          identical to a(2:7:5).  Only relevant for strides not equal
4617          to one.  Don't try a division by zero.  */
4618       if (ar->dimen_type[i] == DIMEN_RANGE
4619           && ar->stride[i] != NULL && ar->stride[i]->expr_type == EXPR_CONSTANT
4620           && mpz_cmp_si (ar->stride[i]->value.integer, 1L) != 0
4621           && mpz_cmp_si (ar->stride[i]->value.integer, 0L) != 0)
4622         {
4623           mpz_t size, end;
4624
4625           if (gfc_ref_dimen_size (ar, i, &size, &end) == SUCCESS)
4626             {
4627               if (ar->end[i] == NULL)
4628                 {
4629                   ar->end[i] =
4630                     gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
4631                                            &ar->where);
4632                   mpz_set (ar->end[i]->value.integer, end);
4633                 }
4634               else if (ar->end[i]->ts.type == BT_INTEGER
4635                        && ar->end[i]->expr_type == EXPR_CONSTANT)
4636                 {
4637                   mpz_set (ar->end[i]->value.integer, end);
4638                 }
4639               else
4640                 gcc_unreachable ();
4641
4642               mpz_clear (size);
4643               mpz_clear (end);
4644             }
4645         }
4646     }
4647
4648   if (ar->type == AR_FULL)
4649     {
4650       if (ar->as->rank == 0)
4651         ar->type = AR_ELEMENT;
4652
4653       /* Make sure array is the same as array(:,:), this way
4654          we don't need to special case all the time.  */
4655       ar->dimen = ar->as->rank;
4656       for (i = 0; i < ar->dimen; i++)
4657         {
4658           ar->dimen_type[i] = DIMEN_RANGE;
4659
4660           gcc_assert (ar->start[i] == NULL);
4661           gcc_assert (ar->end[i] == NULL);
4662           gcc_assert (ar->stride[i] == NULL);
4663         }
4664     }
4665
4666   /* If the reference type is unknown, figure out what kind it is.  */
4667
4668   if (ar->type == AR_UNKNOWN)
4669     {
4670       ar->type = AR_ELEMENT;
4671       for (i = 0; i < ar->dimen; i++)
4672         if (ar->dimen_type[i] == DIMEN_RANGE
4673             || ar->dimen_type[i] == DIMEN_VECTOR)
4674           {
4675             ar->type = AR_SECTION;
4676             break;
4677           }
4678     }
4679
4680   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4681     return FAILURE;
4682
4683   if (ar->as->corank && ar->codimen == 0)
4684     {
4685       int n;
4686       ar->codimen = ar->as->corank;
4687       for (n = ar->dimen; n < ar->dimen + ar->codimen; n++)
4688         ar->dimen_type[n] = DIMEN_THIS_IMAGE;
4689     }
4690
4691   return SUCCESS;
4692 }
4693
4694
4695 static gfc_try
4696 resolve_substring (gfc_ref *ref)
4697 {
4698   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4699
4700   if (ref->u.ss.start != NULL)
4701     {
4702       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4703         return FAILURE;
4704
4705       if (ref->u.ss.start->ts.type != BT_INTEGER)
4706         {
4707           gfc_error ("Substring start index at %L must be of type INTEGER",
4708                      &ref->u.ss.start->where);
4709           return FAILURE;
4710         }
4711
4712       if (ref->u.ss.start->rank != 0)
4713         {
4714           gfc_error ("Substring start index at %L must be scalar",
4715                      &ref->u.ss.start->where);
4716           return FAILURE;
4717         }
4718
4719       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4720           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4721               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4722         {
4723           gfc_error ("Substring start index at %L is less than one",
4724                      &ref->u.ss.start->where);
4725           return FAILURE;
4726         }
4727     }
4728
4729   if (ref->u.ss.end != NULL)
4730     {
4731       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4732         return FAILURE;
4733
4734       if (ref->u.ss.end->ts.type != BT_INTEGER)
4735         {
4736           gfc_error ("Substring end index at %L must be of type INTEGER",
4737                      &ref->u.ss.end->where);
4738           return FAILURE;
4739         }
4740
4741       if (ref->u.ss.end->rank != 0)
4742         {
4743           gfc_error ("Substring end index at %L must be scalar",
4744                      &ref->u.ss.end->where);
4745           return FAILURE;
4746         }
4747
4748       if (ref->u.ss.length != NULL
4749           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4750           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4751               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4752         {
4753           gfc_error ("Substring end index at %L exceeds the string length",
4754                      &ref->u.ss.start->where);
4755           return FAILURE;
4756         }
4757
4758       if (compare_bound_mpz_t (ref->u.ss.end,
4759                                gfc_integer_kinds[k].huge) == CMP_GT
4760           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4761               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4762         {
4763           gfc_error ("Substring end index at %L is too large",
4764                      &ref->u.ss.end->where);
4765           return FAILURE;
4766         }
4767     }
4768
4769   return SUCCESS;
4770 }
4771
4772
4773 /* This function supplies missing substring charlens.  */
4774
4775 void
4776 gfc_resolve_substring_charlen (gfc_expr *e)
4777 {
4778   gfc_ref *char_ref;
4779   gfc_expr *start, *end;
4780
4781   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4782     if (char_ref->type == REF_SUBSTRING)
4783       break;
4784
4785   if (!char_ref)
4786     return;
4787
4788   gcc_assert (char_ref->next == NULL);
4789
4790   if (e->ts.u.cl)
4791     {
4792       if (e->ts.u.cl->length)
4793         gfc_free_expr (e->ts.u.cl->length);
4794       else if (e->expr_type == EXPR_VARIABLE
4795                  && e->symtree->n.sym->attr.dummy)
4796         return;
4797     }
4798
4799   e->ts.type = BT_CHARACTER;
4800   e->ts.kind = gfc_default_character_kind;
4801
4802   if (!e->ts.u.cl)
4803     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4804
4805   if (char_ref->u.ss.start)
4806     start = gfc_copy_expr (char_ref->u.ss.start);
4807   else
4808     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4809
4810   if (char_ref->u.ss.end)
4811     end = gfc_copy_expr (char_ref->u.ss.end);
4812   else if (e->expr_type == EXPR_VARIABLE)
4813     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4814   else
4815     end = NULL;
4816
4817   if (!start || !end)
4818     return;
4819
4820   /* Length = (end - start +1).  */
4821   e->ts.u.cl->length = gfc_subtract (end, start);
4822   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4823                                 gfc_get_int_expr (gfc_default_integer_kind,
4824                                                   NULL, 1));
4825
4826   e->ts.u.cl->length->ts.type = BT_INTEGER;
4827   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4828
4829   /* Make sure that the length is simplified.  */
4830   gfc_simplify_expr (e->ts.u.cl->length, 1);
4831   gfc_resolve_expr (e->ts.u.cl->length);
4832 }
4833
4834
4835 /* Resolve subtype references.  */
4836
4837 static gfc_try
4838 resolve_ref (gfc_expr *expr)
4839 {
4840   int current_part_dimension, n_components, seen_part_dimension;
4841   gfc_ref *ref;
4842
4843   for (ref = expr->ref; ref; ref = ref->next)
4844     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4845       {
4846         find_array_spec (expr);
4847         break;
4848       }
4849
4850   for (ref = expr->ref; ref; ref = ref->next)
4851     switch (ref->type)
4852       {
4853       case REF_ARRAY:
4854         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4855           return FAILURE;
4856         break;
4857
4858       case REF_COMPONENT:
4859         break;
4860
4861       case REF_SUBSTRING:
4862         if (resolve_substring (ref) == FAILURE)
4863           return FAILURE;
4864         break;
4865       }
4866
4867   /* Check constraints on part references.  */
4868
4869   current_part_dimension = 0;
4870   seen_part_dimension = 0;
4871   n_components = 0;
4872
4873   for (ref = expr->ref; ref; ref = ref->next)
4874     {
4875       switch (ref->type)
4876         {
4877         case REF_ARRAY:
4878           switch (ref->u.ar.type)
4879             {
4880             case AR_FULL:
4881               /* Coarray scalar.  */
4882               if (ref->u.ar.as->rank == 0)
4883                 {
4884                   current_part_dimension = 0;
4885                   break;
4886                 }
4887               /* Fall through.  */
4888             case AR_SECTION:
4889               current_part_dimension = 1;
4890               break;
4891
4892             case AR_ELEMENT:
4893               current_part_dimension = 0;
4894               break;
4895
4896             case AR_UNKNOWN:
4897               gfc_internal_error ("resolve_ref(): Bad array reference");
4898             }
4899
4900           break;
4901
4902         case REF_COMPONENT:
4903           if (current_part_dimension || seen_part_dimension)
4904             {
4905               /* F03:C614.  */
4906               if (ref->u.c.component->attr.pointer
4907                   || ref->u.c.component->attr.proc_pointer
4908                   || (ref->u.c.component->ts.type == BT_CLASS
4909                         && CLASS_DATA (ref->u.c.component)->attr.pointer))
4910                 {
4911                   gfc_error ("Component to the right of a part reference "
4912                              "with nonzero rank must not have the POINTER "
4913                              "attribute at %L", &expr->where);
4914                   return FAILURE;
4915                 }
4916               else if (ref->u.c.component->attr.allocatable
4917                         || (ref->u.c.component->ts.type == BT_CLASS
4918                             && CLASS_DATA (ref->u.c.component)->attr.allocatable))
4919
4920                 {
4921                   gfc_error ("Component to the right of a part reference "
4922                              "with nonzero rank must not have the ALLOCATABLE "
4923                              "attribute at %L", &expr->where);
4924                   return FAILURE;
4925                 }
4926             }
4927
4928           n_components++;
4929           break;
4930
4931         case REF_SUBSTRING:
4932           break;
4933         }
4934
4935       if (((ref->type == REF_COMPONENT && n_components > 1)
4936            || ref->next == NULL)
4937           && current_part_dimension
4938           && seen_part_dimension)
4939         {
4940           gfc_error ("Two or more part references with nonzero rank must "
4941                      "not be specified at %L", &expr->where);
4942           return FAILURE;
4943         }
4944
4945       if (ref->type == REF_COMPONENT)
4946         {
4947           if (current_part_dimension)
4948             seen_part_dimension = 1;
4949
4950           /* reset to make sure */
4951           current_part_dimension = 0;
4952         }
4953     }
4954
4955   return SUCCESS;
4956 }
4957
4958
4959 /* Given an expression, determine its shape.  This is easier than it sounds.
4960    Leaves the shape array NULL if it is not possible to determine the shape.  */
4961
4962 static void
4963 expression_shape (gfc_expr *e)
4964 {
4965   mpz_t array[GFC_MAX_DIMENSIONS];
4966   int i;
4967
4968   if (e->rank == 0 || e->shape != NULL)
4969     return;
4970
4971   for (i = 0; i < e->rank; i++)
4972     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4973       goto fail;
4974
4975   e->shape = gfc_get_shape (e->rank);
4976
4977   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4978
4979   return;
4980
4981 fail:
4982   for (i--; i >= 0; i--)
4983     mpz_clear (array[i]);
4984 }
4985
4986
4987 /* Given a variable expression node, compute the rank of the expression by
4988    examining the base symbol and any reference structures it may have.  */
4989
4990 static void
4991 expression_rank (gfc_expr *e)
4992 {
4993   gfc_ref *ref;
4994   int i, rank;
4995
4996   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4997      could lead to serious confusion...  */
4998   gcc_assert (e->expr_type != EXPR_COMPCALL);
4999
5000   if (e->ref == NULL)
5001     {
5002       if (e->expr_type == EXPR_ARRAY)
5003         goto done;
5004       /* Constructors can have a rank different from one via RESHAPE().  */
5005
5006       if (e->symtree == NULL)
5007         {
5008           e->rank = 0;
5009           goto done;
5010         }
5011
5012       e->rank = (e->symtree->n.sym->as == NULL)
5013                 ? 0 : e->symtree->n.sym->as->rank;
5014       goto done;
5015     }
5016
5017   rank = 0;
5018
5019   for (ref = e->ref; ref; ref = ref->next)
5020     {
5021       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.proc_pointer
5022           && ref->u.c.component->attr.function && !ref->next)
5023         rank = ref->u.c.component->as ? ref->u.c.component->as->rank : 0;
5024
5025       if (ref->type != REF_ARRAY)
5026         continue;
5027
5028       if (ref->u.ar.type == AR_FULL)
5029         {
5030           rank = ref->u.ar.as->rank;
5031           break;
5032         }
5033
5034       if (ref->u.ar.type == AR_SECTION)
5035         {
5036           /* Figure out the rank of the section.  */
5037           if (rank != 0)
5038             gfc_internal_error ("expression_rank(): Two array specs");
5039
5040           for (i = 0; i < ref->u.ar.dimen; i++)
5041             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
5042                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
5043               rank++;
5044
5045           break;
5046         }
5047     }
5048
5049   e->rank = rank;
5050
5051 done:
5052   expression_shape (e);
5053 }
5054
5055
5056 /* Resolve a variable expression.  */
5057
5058 static gfc_try
5059 resolve_variable (gfc_expr *e)
5060 {
5061   gfc_symbol *sym;
5062   gfc_try t;
5063
5064   t = SUCCESS;
5065
5066   if (e->symtree == NULL)
5067     return FAILURE;
5068   sym = e->symtree->n.sym;
5069
5070   /* TS 29113, 407b.  */
5071   if (e->ts.type == BT_ASSUMED && !assumed_type_expr_allowed)
5072     {
5073       gfc_error ("Invalid expression with assumed-type variable %s at %L",
5074                  sym->name, &e->where);
5075       return FAILURE;
5076     }
5077
5078   /* TS 29113, 407b.  */
5079   if (e->ts.type == BT_ASSUMED && e->ref
5080       && !(e->ref->type == REF_ARRAY && e->ref->u.ar.type == AR_FULL
5081            && e->ref->next == NULL))
5082     {
5083       gfc_error ("Assumed-type variable %s with designator at %L",
5084                  sym->name, &e->ref->u.ar.where);
5085       return FAILURE;
5086     }
5087
5088   /* If this is an associate-name, it may be parsed with an array reference
5089      in error even though the target is scalar.  Fail directly in this case.
5090      TODO Understand why class scalar expressions must be excluded.  */
5091   if (sym->assoc && !(sym->ts.type == BT_CLASS && e->rank == 0))
5092     {
5093       if (sym->ts.type == BT_CLASS)
5094         gfc_fix_class_refs (e);
5095       if (!sym->attr.dimension && e->ref && e->ref->type == REF_ARRAY)
5096         return FAILURE;
5097     }
5098
5099   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.generic)
5100     sym->ts.u.derived = gfc_find_dt_in_generic (sym->ts.u.derived);
5101
5102   /* On the other hand, the parser may not have known this is an array;
5103      in this case, we have to add a FULL reference.  */
5104   if (sym->assoc && sym->attr.dimension && !e->ref)
5105     {
5106       e->ref = gfc_get_ref ();
5107       e->ref->type = REF_ARRAY;
5108       e->ref->u.ar.type = AR_FULL;
5109       e->ref->u.ar.dimen = 0;
5110     }
5111
5112   if (e->ref && resolve_ref (e) == FAILURE)
5113     return FAILURE;
5114
5115   if (sym->attr.flavor == FL_PROCEDURE
5116       && (!sym->attr.function
5117           || (sym->attr.function && sym->result
5118               && sym->result->attr.proc_pointer
5119               && !sym->result->attr.function)))
5120     {
5121       e->ts.type = BT_PROCEDURE;
5122       goto resolve_procedure;
5123     }
5124
5125   if (sym->ts.type != BT_UNKNOWN)
5126     gfc_variable_attr (e, &e->ts);
5127   else
5128     {
5129       /* Must be a simple variable reference.  */
5130       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
5131         return FAILURE;
5132       e->ts = sym->ts;
5133     }
5134
5135   if (check_assumed_size_reference (sym, e))
5136     return FAILURE;
5137
5138   /* If a PRIVATE variable is used in the specification expression of the
5139      result variable, it might be accessed from outside the module and can
5140      thus not be TREE_PUBLIC() = 0.
5141      TODO: sym->attr.public_used only has to be set for the result variable's
5142      type-parameter expression and not for dummies or automatic variables.
5143      Additionally, it only has to be set if the function is either PUBLIC or
5144      used in a generic interface or TBP; unfortunately,
5145      proc_name->attr.public_used can get set at a later stage.  */
5146   if (specification_expr && sym->attr.access == ACCESS_PRIVATE
5147       && !sym->attr.function && !sym->attr.use_assoc
5148       && gfc_current_ns->proc_name && gfc_current_ns->proc_name->attr.function)
5149     sym->attr.public_used = 1;
5150
5151   /* Deal with forward references to entries during resolve_code, to
5152      satisfy, at least partially, 12.5.2.5.  */
5153   if (gfc_current_ns->entries
5154       && current_entry_id == sym->entry_id
5155       && cs_base
5156       && cs_base->current
5157       && cs_base->current->op != EXEC_ENTRY)
5158     {
5159       gfc_entry_list *entry;
5160       gfc_formal_arglist *formal;
5161       int n;
5162       bool seen;
5163
5164       /* If the symbol is a dummy...  */
5165       if (sym->attr.dummy && sym->ns == gfc_current_ns)
5166         {
5167           entry = gfc_current_ns->entries;
5168           seen = false;
5169
5170           /* ...test if the symbol is a parameter of previous entries.  */
5171           for (; entry && entry->id <= current_entry_id; entry = entry->next)
5172             for (formal = entry->sym->formal; formal; formal = formal->next)
5173               {
5174                 if (formal->sym && sym->name == formal->sym->name)
5175                   seen = true;
5176               }
5177
5178           /*  If it has not been seen as a dummy, this is an error.  */
5179           if (!seen)
5180             {
5181               if (specification_expr)
5182                 gfc_error ("Variable '%s', used in a specification expression"
5183                            ", is referenced at %L before the ENTRY statement "
5184                            "in which it is a parameter",
5185                            sym->name, &cs_base->current->loc);
5186               else
5187                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
5188                            "statement in which it is a parameter",
5189                            sym->name, &cs_base->current->loc);
5190               t = FAILURE;
5191             }
5192         }
5193
5194       /* Now do the same check on the specification expressions.  */
5195       specification_expr = 1;
5196       if (sym->ts.type == BT_CHARACTER
5197           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
5198         t = FAILURE;
5199
5200       if (sym->as)
5201         for (n = 0; n < sym->as->rank; n++)
5202           {
5203              specification_expr = 1;
5204              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
5205                t = FAILURE;
5206              specification_expr = 1;
5207              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
5208                t = FAILURE;
5209           }
5210       specification_expr = 0;
5211
5212       if (t == SUCCESS)
5213         /* Update the symbol's entry level.  */
5214         sym->entry_id = current_entry_id + 1;
5215     }
5216
5217   /* If a symbol has been host_associated mark it.  This is used latter,
5218      to identify if aliasing is possible via host association.  */
5219   if (sym->attr.flavor == FL_VARIABLE
5220         && gfc_current_ns->parent
5221         && (gfc_current_ns->parent == sym->ns
5222               || (gfc_current_ns->parent->parent
5223                     && gfc_current_ns->parent->parent == sym->ns)))
5224     sym->attr.host_assoc = 1;
5225
5226 resolve_procedure:
5227   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
5228     t = FAILURE;
5229
5230   /* F2008, C617 and C1229.  */
5231   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5232       && gfc_is_coindexed (e))
5233     {
5234       gfc_ref *ref, *ref2 = NULL;
5235
5236       for (ref = e->ref; ref; ref = ref->next)
5237         {
5238           if (ref->type == REF_COMPONENT)
5239             ref2 = ref;
5240           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5241             break;
5242         }
5243
5244       for ( ; ref; ref = ref->next)
5245         if (ref->type == REF_COMPONENT)
5246           break;
5247
5248       /* Expression itself is not coindexed object.  */
5249       if (ref && e->ts.type == BT_CLASS)
5250         {
5251           gfc_error ("Polymorphic subobject of coindexed object at %L",
5252                      &e->where);
5253           t = FAILURE;
5254         }
5255
5256       /* Expression itself is coindexed object.  */
5257       if (ref == NULL)
5258         {
5259           gfc_component *c;
5260           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5261           for ( ; c; c = c->next)
5262             if (c->attr.allocatable && c->ts.type == BT_CLASS)
5263               {
5264                 gfc_error ("Coindexed object with polymorphic allocatable "
5265                          "subcomponent at %L", &e->where);
5266                 t = FAILURE;
5267                 break;
5268               }
5269         }
5270     }
5271
5272   return t;
5273 }
5274
5275
5276 /* Checks to see that the correct symbol has been host associated.
5277    The only situation where this arises is that in which a twice
5278    contained function is parsed after the host association is made.
5279    Therefore, on detecting this, change the symbol in the expression
5280    and convert the array reference into an actual arglist if the old
5281    symbol is a variable.  */
5282 static bool
5283 check_host_association (gfc_expr *e)
5284 {
5285   gfc_symbol *sym, *old_sym;
5286   gfc_symtree *st;
5287   int n;
5288   gfc_ref *ref;
5289   gfc_actual_arglist *arg, *tail = NULL;
5290   bool retval = e->expr_type == EXPR_FUNCTION;
5291
5292   /*  If the expression is the result of substitution in
5293       interface.c(gfc_extend_expr) because there is no way in
5294       which the host association can be wrong.  */
5295   if (e->symtree == NULL
5296         || e->symtree->n.sym == NULL
5297         || e->user_operator)
5298     return retval;
5299
5300   old_sym = e->symtree->n.sym;
5301
5302   if (gfc_current_ns->parent
5303         && old_sym->ns != gfc_current_ns)
5304     {
5305       /* Use the 'USE' name so that renamed module symbols are
5306          correctly handled.  */
5307       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5308
5309       if (sym && old_sym != sym
5310               && sym->ts.type == old_sym->ts.type
5311               && sym->attr.flavor == FL_PROCEDURE
5312               && sym->attr.contained)
5313         {
5314           /* Clear the shape, since it might not be valid.  */
5315           gfc_free_shape (&e->shape, e->rank);
5316
5317           /* Give the expression the right symtree!  */
5318           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5319           gcc_assert (st != NULL);
5320
5321           if (old_sym->attr.flavor == FL_PROCEDURE
5322                 || e->expr_type == EXPR_FUNCTION)
5323             {
5324               /* Original was function so point to the new symbol, since
5325                  the actual argument list is already attached to the
5326                  expression. */
5327               e->value.function.esym = NULL;
5328               e->symtree = st;
5329             }
5330           else
5331             {
5332               /* Original was variable so convert array references into
5333                  an actual arglist. This does not need any checking now
5334                  since resolve_function will take care of it.  */
5335               e->value.function.actual = NULL;
5336               e->expr_type = EXPR_FUNCTION;
5337               e->symtree = st;
5338
5339               /* Ambiguity will not arise if the array reference is not
5340                  the last reference.  */
5341               for (ref = e->ref; ref; ref = ref->next)
5342                 if (ref->type == REF_ARRAY && ref->next == NULL)
5343                   break;
5344
5345               gcc_assert (ref->type == REF_ARRAY);
5346
5347               /* Grab the start expressions from the array ref and
5348                  copy them into actual arguments.  */
5349               for (n = 0; n < ref->u.ar.dimen; n++)
5350                 {
5351                   arg = gfc_get_actual_arglist ();
5352                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5353                   if (e->value.function.actual == NULL)
5354                     tail = e->value.function.actual = arg;
5355                   else
5356                     {
5357                       tail->next = arg;
5358                       tail = arg;
5359                     }
5360                 }
5361
5362               /* Dump the reference list and set the rank.  */
5363               gfc_free_ref_list (e->ref);
5364               e->ref = NULL;
5365               e->rank = sym->as ? sym->as->rank : 0;
5366             }
5367
5368           gfc_resolve_expr (e);
5369           sym->refs++;
5370         }
5371     }
5372   /* This might have changed!  */
5373   return e->expr_type == EXPR_FUNCTION;
5374 }
5375
5376
5377 static void
5378 gfc_resolve_character_operator (gfc_expr *e)
5379 {
5380   gfc_expr *op1 = e->value.op.op1;
5381   gfc_expr *op2 = e->value.op.op2;
5382   gfc_expr *e1 = NULL;
5383   gfc_expr *e2 = NULL;
5384
5385   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5386
5387   if (op1->ts.u.cl && op1->ts.u.cl->length)
5388     e1 = gfc_copy_expr (op1->ts.u.cl->length);
5389   else if (op1->expr_type == EXPR_CONSTANT)
5390     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5391                            op1->value.character.length);
5392
5393   if (op2->ts.u.cl && op2->ts.u.cl->length)
5394     e2 = gfc_copy_expr (op2->ts.u.cl->length);
5395   else if (op2->expr_type == EXPR_CONSTANT)
5396     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5397                            op2->value.character.length);
5398
5399   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5400
5401   if (!e1 || !e2)
5402     return;
5403
5404   e->ts.u.cl->length = gfc_add (e1, e2);
5405   e->ts.u.cl->length->ts.type = BT_INTEGER;
5406   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5407   gfc_simplify_expr (e->ts.u.cl->length, 0);
5408   gfc_resolve_expr (e->ts.u.cl->length);
5409
5410   return;
5411 }
5412
5413
5414 /*  Ensure that an character expression has a charlen and, if possible, a
5415     length expression.  */
5416
5417 static void
5418 fixup_charlen (gfc_expr *e)
5419 {
5420   /* The cases fall through so that changes in expression type and the need
5421      for multiple fixes are picked up.  In all circumstances, a charlen should
5422      be available for the middle end to hang a backend_decl on.  */
5423   switch (e->expr_type)
5424     {
5425     case EXPR_OP:
5426       gfc_resolve_character_operator (e);
5427
5428     case EXPR_ARRAY:
5429       if (e->expr_type == EXPR_ARRAY)
5430         gfc_resolve_character_array_constructor (e);
5431
5432     case EXPR_SUBSTRING:
5433       if (!e->ts.u.cl && e->ref)
5434         gfc_resolve_substring_charlen (e);
5435
5436     default:
5437       if (!e->ts.u.cl)
5438         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5439
5440       break;
5441     }
5442 }
5443
5444
5445 /* Update an actual argument to include the passed-object for type-bound
5446    procedures at the right position.  */
5447
5448 static gfc_actual_arglist*
5449 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5450                      const char *name)
5451 {
5452   gcc_assert (argpos > 0);
5453
5454   if (argpos == 1)
5455     {
5456       gfc_actual_arglist* result;
5457
5458       result = gfc_get_actual_arglist ();
5459       result->expr = po;
5460       result->next = lst;
5461       if (name)
5462         result->name = name;
5463
5464       return result;
5465     }
5466
5467   if (lst)
5468     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5469   else
5470     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5471   return lst;
5472 }
5473
5474
5475 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5476
5477 static gfc_expr*
5478 extract_compcall_passed_object (gfc_expr* e)
5479 {
5480   gfc_expr* po;
5481
5482   gcc_assert (e->expr_type == EXPR_COMPCALL);
5483
5484   if (e->value.compcall.base_object)
5485     po = gfc_copy_expr (e->value.compcall.base_object);
5486   else
5487     {
5488       po = gfc_get_expr ();
5489       po->expr_type = EXPR_VARIABLE;
5490       po->symtree = e->symtree;
5491       po->ref = gfc_copy_ref (e->ref);
5492       po->where = e->where;
5493     }
5494
5495   if (gfc_resolve_expr (po) == FAILURE)
5496     return NULL;
5497
5498   return po;
5499 }
5500
5501
5502 /* Update the arglist of an EXPR_COMPCALL expression to include the
5503    passed-object.  */
5504
5505 static gfc_try
5506 update_compcall_arglist (gfc_expr* e)
5507 {
5508   gfc_expr* po;
5509   gfc_typebound_proc* tbp;
5510
5511   tbp = e->value.compcall.tbp;
5512
5513   if (tbp->error)
5514     return FAILURE;
5515
5516   po = extract_compcall_passed_object (e);
5517   if (!po)
5518     return FAILURE;
5519
5520   if (tbp->nopass || e->value.compcall.ignore_pass)
5521     {
5522       gfc_free_expr (po);
5523       return SUCCESS;
5524     }
5525
5526   gcc_assert (tbp->pass_arg_num > 0);
5527   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5528                                                   tbp->pass_arg_num,
5529                                                   tbp->pass_arg);
5530
5531   return SUCCESS;
5532 }
5533
5534
5535 /* Extract the passed object from a PPC call (a copy of it).  */
5536
5537 static gfc_expr*
5538 extract_ppc_passed_object (gfc_expr *e)
5539 {
5540   gfc_expr *po;
5541   gfc_ref **ref;
5542
5543   po = gfc_get_expr ();
5544   po->expr_type = EXPR_VARIABLE;
5545   po->symtree = e->symtree;
5546   po->ref = gfc_copy_ref (e->ref);
5547   po->where = e->where;
5548
5549   /* Remove PPC reference.  */
5550   ref = &po->ref;
5551   while ((*ref)->next)
5552     ref = &(*ref)->next;
5553   gfc_free_ref_list (*ref);
5554   *ref = NULL;
5555
5556   if (gfc_resolve_expr (po) == FAILURE)
5557     return NULL;
5558
5559   return po;
5560 }
5561
5562
5563 /* Update the actual arglist of a procedure pointer component to include the
5564    passed-object.  */
5565
5566 static gfc_try
5567 update_ppc_arglist (gfc_expr* e)
5568 {
5569   gfc_expr* po;
5570   gfc_component *ppc;
5571   gfc_typebound_proc* tb;
5572
5573   if (!gfc_is_proc_ptr_comp (e, &ppc))
5574     return FAILURE;
5575
5576   tb = ppc->tb;
5577
5578   if (tb->error)
5579     return FAILURE;
5580   else if (tb->nopass)
5581     return SUCCESS;
5582
5583   po = extract_ppc_passed_object (e);
5584   if (!po)
5585     return FAILURE;
5586
5587   /* F08:R739.  */
5588   if (po->rank > 0)
5589     {
5590       gfc_error ("Passed-object at %L must be scalar", &e->where);
5591       return FAILURE;
5592     }
5593
5594   /* F08:C611.  */
5595   if (po->ts.type == BT_DERIVED && po->ts.u.derived->attr.abstract)
5596     {
5597       gfc_error ("Base object for procedure-pointer component call at %L is of"
5598                  " ABSTRACT type '%s'", &e->where, po->ts.u.derived->name);
5599       return FAILURE;
5600     }
5601
5602   gcc_assert (tb->pass_arg_num > 0);
5603   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5604                                                   tb->pass_arg_num,
5605                                                   tb->pass_arg);
5606
5607   return SUCCESS;
5608 }
5609
5610
5611 /* Check that the object a TBP is called on is valid, i.e. it must not be
5612    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5613
5614 static gfc_try
5615 check_typebound_baseobject (gfc_expr* e)
5616 {
5617   gfc_expr* base;
5618   gfc_try return_value = FAILURE;
5619
5620   base = extract_compcall_passed_object (e);
5621   if (!base)
5622     return FAILURE;
5623
5624   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5625
5626   /* F08:C611.  */
5627   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5628     {
5629       gfc_error ("Base object for type-bound procedure call at %L is of"
5630                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5631       goto cleanup;
5632     }
5633
5634   /* F08:C1230. If the procedure called is NOPASS,
5635      the base object must be scalar.  */
5636   if (e->value.compcall.tbp->nopass && base->rank > 0)
5637     {
5638       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5639                  " be scalar", &e->where);
5640       goto cleanup;
5641     }
5642
5643   return_value = SUCCESS;
5644
5645 cleanup:
5646   gfc_free_expr (base);
5647   return return_value;
5648 }
5649
5650
5651 /* Resolve a call to a type-bound procedure, either function or subroutine,
5652    statically from the data in an EXPR_COMPCALL expression.  The adapted
5653    arglist and the target-procedure symtree are returned.  */
5654
5655 static gfc_try
5656 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5657                           gfc_actual_arglist** actual)
5658 {
5659   gcc_assert (e->expr_type == EXPR_COMPCALL);
5660   gcc_assert (!e->value.compcall.tbp->is_generic);
5661
5662   /* Update the actual arglist for PASS.  */
5663   if (update_compcall_arglist (e) == FAILURE)
5664     return FAILURE;
5665
5666   *actual = e->value.compcall.actual;
5667   *target = e->value.compcall.tbp->u.specific;
5668
5669   gfc_free_ref_list (e->ref);
5670   e->ref = NULL;
5671   e->value.compcall.actual = NULL;
5672
5673   /* If we find a deferred typebound procedure, check for derived types
5674      that an overriding typebound procedure has not been missed.  */
5675   if (e->value.compcall.name
5676       && !e->value.compcall.tbp->non_overridable
5677       && e->value.compcall.base_object
5678       && e->value.compcall.base_object->ts.type == BT_DERIVED)
5679     {
5680       gfc_symtree *st;
5681       gfc_symbol *derived;
5682
5683       /* Use the derived type of the base_object.  */
5684       derived = e->value.compcall.base_object->ts.u.derived;
5685       st = NULL;
5686
5687       /* If necessary, go through the inheritance chain.  */
5688       while (!st && derived)
5689         {
5690           /* Look for the typebound procedure 'name'.  */
5691           if (derived->f2k_derived && derived->f2k_derived->tb_sym_root)
5692             st = gfc_find_symtree (derived->f2k_derived->tb_sym_root,
5693                                    e->value.compcall.name);
5694           if (!st)
5695             derived = gfc_get_derived_super_type (derived);
5696         }
5697
5698       /* Now find the specific name in the derived type namespace.  */
5699       if (st && st->n.tb && st->n.tb->u.specific)
5700         gfc_find_sym_tree (st->n.tb->u.specific->name,
5701                            derived->ns, 1, &st);
5702       if (st)
5703         *target = st;
5704     }
5705   return SUCCESS;
5706 }
5707
5708
5709 /* Get the ultimate declared type from an expression.  In addition,
5710    return the last class/derived type reference and the copy of the
5711    reference list.  If check_types is set true, derived types are
5712    identified as well as class references.  */
5713 static gfc_symbol*
5714 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5715                         gfc_expr *e, bool check_types)
5716 {
5717   gfc_symbol *declared;
5718   gfc_ref *ref;
5719
5720   declared = NULL;
5721   if (class_ref)
5722     *class_ref = NULL;
5723   if (new_ref)
5724     *new_ref = gfc_copy_ref (e->ref);
5725
5726   for (ref = e->ref; ref; ref = ref->next)
5727     {
5728       if (ref->type != REF_COMPONENT)
5729         continue;
5730
5731       if ((ref->u.c.component->ts.type == BT_CLASS
5732              || (check_types && ref->u.c.component->ts.type == BT_DERIVED))
5733           && ref->u.c.component->attr.flavor != FL_PROCEDURE)
5734         {
5735           declared = ref->u.c.component->ts.u.derived;
5736           if (class_ref)
5737             *class_ref = ref;
5738         }
5739     }
5740
5741   if (declared == NULL)
5742     declared = e->symtree->n.sym->ts.u.derived;
5743
5744   return declared;
5745 }
5746
5747
5748 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5749    which of the specific bindings (if any) matches the arglist and transform
5750    the expression into a call of that binding.  */
5751
5752 static gfc_try
5753 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5754 {
5755   gfc_typebound_proc* genproc;
5756   const char* genname;
5757   gfc_symtree *st;
5758   gfc_symbol *derived;
5759
5760   gcc_assert (e->expr_type == EXPR_COMPCALL);
5761   genname = e->value.compcall.name;
5762   genproc = e->value.compcall.tbp;
5763
5764   if (!genproc->is_generic)
5765     return SUCCESS;
5766
5767   /* Try the bindings on this type and in the inheritance hierarchy.  */
5768   for (; genproc; genproc = genproc->overridden)
5769     {
5770       gfc_tbp_generic* g;
5771
5772       gcc_assert (genproc->is_generic);
5773       for (g = genproc->u.generic; g; g = g->next)
5774         {
5775           gfc_symbol* target;
5776           gfc_actual_arglist* args;
5777           bool matches;
5778
5779           gcc_assert (g->specific);
5780
5781           if (g->specific->error)
5782             continue;
5783
5784           target = g->specific->u.specific->n.sym;
5785
5786           /* Get the right arglist by handling PASS/NOPASS.  */
5787           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5788           if (!g->specific->nopass)
5789             {
5790               gfc_expr* po;
5791               po = extract_compcall_passed_object (e);
5792               if (!po)
5793                 return FAILURE;
5794
5795               gcc_assert (g->specific->pass_arg_num > 0);
5796               gcc_assert (!g->specific->error);
5797               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5798                                           g->specific->pass_arg);
5799             }
5800           resolve_actual_arglist (args, target->attr.proc,
5801                                   is_external_proc (target) && !target->formal);
5802
5803           /* Check if this arglist matches the formal.  */
5804           matches = gfc_arglist_matches_symbol (&args, target);
5805
5806           /* Clean up and break out of the loop if we've found it.  */
5807           gfc_free_actual_arglist (args);
5808           if (matches)
5809             {
5810               e->value.compcall.tbp = g->specific;
5811               genname = g->specific_st->name;
5812               /* Pass along the name for CLASS methods, where the vtab
5813                  procedure pointer component has to be referenced.  */
5814               if (name)
5815                 *name = genname;
5816               goto success;
5817             }
5818         }
5819     }
5820
5821   /* Nothing matching found!  */
5822   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5823              " '%s' at %L", genname, &e->where);
5824   return FAILURE;
5825
5826 success:
5827   /* Make sure that we have the right specific instance for the name.  */
5828   derived = get_declared_from_expr (NULL, NULL, e, true);
5829
5830   st = gfc_find_typebound_proc (derived, NULL, genname, true, &e->where);
5831   if (st)
5832     e->value.compcall.tbp = st->n.tb;
5833
5834   return SUCCESS;
5835 }
5836
5837
5838 /* Resolve a call to a type-bound subroutine.  */
5839
5840 static gfc_try
5841 resolve_typebound_call (gfc_code* c, const char **name)
5842 {
5843   gfc_actual_arglist* newactual;
5844   gfc_symtree* target;
5845
5846   /* Check that's really a SUBROUTINE.  */
5847   if (!c->expr1->value.compcall.tbp->subroutine)
5848     {
5849       gfc_error ("'%s' at %L should be a SUBROUTINE",
5850                  c->expr1->value.compcall.name, &c->loc);
5851       return FAILURE;
5852     }
5853
5854   if (check_typebound_baseobject (c->expr1) == FAILURE)
5855     return FAILURE;
5856
5857   /* Pass along the name for CLASS methods, where the vtab
5858      procedure pointer component has to be referenced.  */
5859   if (name)
5860     *name = c->expr1->value.compcall.name;
5861
5862   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5863     return FAILURE;
5864
5865   /* Transform into an ordinary EXEC_CALL for now.  */
5866
5867   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5868     return FAILURE;
5869
5870   c->ext.actual = newactual;
5871   c->symtree = target;
5872   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5873
5874   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5875
5876   gfc_free_expr (c->expr1);
5877   c->expr1 = gfc_get_expr ();
5878   c->expr1->expr_type = EXPR_FUNCTION;
5879   c->expr1->symtree = target;
5880   c->expr1->where = c->loc;
5881
5882   return resolve_call (c);
5883 }
5884
5885
5886 /* Resolve a component-call expression.  */
5887 static gfc_try
5888 resolve_compcall (gfc_expr* e, const char **name)
5889 {
5890   gfc_actual_arglist* newactual;
5891   gfc_symtree* target;
5892
5893   /* Check that's really a FUNCTION.  */
5894   if (!e->value.compcall.tbp->function)
5895     {
5896       gfc_error ("'%s' at %L should be a FUNCTION",
5897                  e->value.compcall.name, &e->where);
5898       return FAILURE;
5899     }
5900
5901   /* These must not be assign-calls!  */
5902   gcc_assert (!e->value.compcall.assign);
5903
5904   if (check_typebound_baseobject (e) == FAILURE)
5905     return FAILURE;
5906
5907   /* Pass along the name for CLASS methods, where the vtab
5908      procedure pointer component has to be referenced.  */
5909   if (name)
5910     *name = e->value.compcall.name;
5911
5912   if (resolve_typebound_generic_call (e, name) == FAILURE)
5913     return FAILURE;
5914   gcc_assert (!e->value.compcall.tbp->is_generic);
5915
5916   /* Take the rank from the function's symbol.  */
5917   if (e->value.compcall.tbp->u.specific->n.sym->as)
5918     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5919
5920   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5921      arglist to the TBP's binding target.  */
5922
5923   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5924     return FAILURE;
5925
5926   e->value.function.actual = newactual;
5927   e->value.function.name = NULL;
5928   e->value.function.esym = target->n.sym;
5929   e->value.function.isym = NULL;
5930   e->symtree = target;
5931   e->ts = target->n.sym->ts;
5932   e->expr_type = EXPR_FUNCTION;
5933
5934   /* Resolution is not necessary if this is a class subroutine; this
5935      function only has to identify the specific proc. Resolution of
5936      the call will be done next in resolve_typebound_call.  */
5937   return gfc_resolve_expr (e);
5938 }
5939
5940
5941
5942 /* Resolve a typebound function, or 'method'. First separate all
5943    the non-CLASS references by calling resolve_compcall directly.  */
5944
5945 static gfc_try
5946 resolve_typebound_function (gfc_expr* e)
5947 {
5948   gfc_symbol *declared;
5949   gfc_component *c;
5950   gfc_ref *new_ref;
5951   gfc_ref *class_ref;
5952   gfc_symtree *st;
5953   const char *name;
5954   gfc_typespec ts;
5955   gfc_expr *expr;
5956   bool overridable;
5957
5958   st = e->symtree;
5959
5960   /* Deal with typebound operators for CLASS objects.  */
5961   expr = e->value.compcall.base_object;
5962   overridable = !e->value.compcall.tbp->non_overridable;
5963   if (expr && expr->ts.type == BT_CLASS && e->value.compcall.name)
5964     {
5965       /* If the base_object is not a variable, the corresponding actual
5966          argument expression must be stored in e->base_expression so
5967          that the corresponding tree temporary can be used as the base
5968          object in gfc_conv_procedure_call.  */
5969       if (expr->expr_type != EXPR_VARIABLE)
5970         {
5971           gfc_actual_arglist *args;
5972
5973           for (args= e->value.function.actual; args; args = args->next)
5974             {
5975               if (expr == args->expr)
5976                 expr = args->expr;
5977             }
5978         }
5979
5980       /* Since the typebound operators are generic, we have to ensure
5981          that any delays in resolution are corrected and that the vtab
5982          is present.  */
5983       ts = expr->ts;
5984       declared = ts.u.derived;
5985       c = gfc_find_component (declared, "_vptr", true, true);
5986       if (c->ts.u.derived == NULL)
5987         c->ts.u.derived = gfc_find_derived_vtab (declared);
5988
5989       if (resolve_compcall (e, &name) == FAILURE)
5990         return FAILURE;
5991
5992       /* Use the generic name if it is there.  */
5993       name = name ? name : e->value.function.esym->name;
5994       e->symtree = expr->symtree;
5995       e->ref = gfc_copy_ref (expr->ref);
5996       get_declared_from_expr (&class_ref, NULL, e, false);
5997
5998       /* Trim away the extraneous references that emerge from nested
5999          use of interface.c (extend_expr).  */
6000       if (class_ref && class_ref->next)
6001         {
6002           gfc_free_ref_list (class_ref->next);
6003           class_ref->next = NULL;
6004         }
6005       else if (e->ref && !class_ref)
6006         {
6007           gfc_free_ref_list (e->ref);
6008           e->ref = NULL;
6009         }
6010
6011       gfc_add_vptr_component (e);
6012       gfc_add_component_ref (e, name);
6013       e->value.function.esym = NULL;
6014       if (expr->expr_type != EXPR_VARIABLE)
6015         e->base_expr = expr;
6016       return SUCCESS;
6017     }
6018
6019   if (st == NULL)
6020     return resolve_compcall (e, NULL);
6021
6022   if (resolve_ref (e) == FAILURE)
6023     return FAILURE;
6024
6025   /* Get the CLASS declared type.  */
6026   declared = get_declared_from_expr (&class_ref, &new_ref, e, true);
6027
6028   /* Weed out cases of the ultimate component being a derived type.  */
6029   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
6030          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
6031     {
6032       gfc_free_ref_list (new_ref);
6033       return resolve_compcall (e, NULL);
6034     }
6035
6036   c = gfc_find_component (declared, "_data", true, true);
6037   declared = c->ts.u.derived;
6038
6039   /* Treat the call as if it is a typebound procedure, in order to roll
6040      out the correct name for the specific function.  */
6041   if (resolve_compcall (e, &name) == FAILURE)
6042     return FAILURE;
6043   ts = e->ts;
6044
6045   if (overridable)
6046     {
6047       /* Convert the expression to a procedure pointer component call.  */
6048       e->value.function.esym = NULL;
6049       e->symtree = st;
6050
6051       if (new_ref)  
6052         e->ref = new_ref;
6053
6054       /* '_vptr' points to the vtab, which contains the procedure pointers.  */
6055       gfc_add_vptr_component (e);
6056       gfc_add_component_ref (e, name);
6057
6058       /* Recover the typespec for the expression.  This is really only
6059         necessary for generic procedures, where the additional call
6060         to gfc_add_component_ref seems to throw the collection of the
6061         correct typespec.  */
6062       e->ts = ts;
6063     }
6064
6065   return SUCCESS;
6066 }
6067
6068 /* Resolve a typebound subroutine, or 'method'. First separate all
6069    the non-CLASS references by calling resolve_typebound_call
6070    directly.  */
6071
6072 static gfc_try
6073 resolve_typebound_subroutine (gfc_code *code)
6074 {
6075   gfc_symbol *declared;
6076   gfc_component *c;
6077   gfc_ref *new_ref;
6078   gfc_ref *class_ref;
6079   gfc_symtree *st;
6080   const char *name;
6081   gfc_typespec ts;
6082   gfc_expr *expr;
6083   bool overridable;
6084
6085   st = code->expr1->symtree;
6086
6087   /* Deal with typebound operators for CLASS objects.  */
6088   expr = code->expr1->value.compcall.base_object;
6089   overridable = !code->expr1->value.compcall.tbp->non_overridable;
6090   if (expr && expr->ts.type == BT_CLASS && code->expr1->value.compcall.name)
6091     {
6092       /* If the base_object is not a variable, the corresponding actual
6093          argument expression must be stored in e->base_expression so
6094          that the corresponding tree temporary can be used as the base
6095          object in gfc_conv_procedure_call.  */
6096       if (expr->expr_type != EXPR_VARIABLE)
6097         {
6098           gfc_actual_arglist *args;
6099
6100           args= code->expr1->value.function.actual;
6101           for (; args; args = args->next)
6102             if (expr == args->expr)
6103               expr = args->expr;
6104         }
6105
6106       /* Since the typebound operators are generic, we have to ensure
6107          that any delays in resolution are corrected and that the vtab
6108          is present.  */
6109       declared = expr->ts.u.derived;
6110       c = gfc_find_component (declared, "_vptr", true, true);
6111       if (c->ts.u.derived == NULL)
6112         c->ts.u.derived = gfc_find_derived_vtab (declared);
6113
6114       if (resolve_typebound_call (code, &name) == FAILURE)
6115         return FAILURE;
6116
6117       /* Use the generic name if it is there.  */
6118       name = name ? name : code->expr1->value.function.esym->name;
6119       code->expr1->symtree = expr->symtree;
6120       code->expr1->ref = gfc_copy_ref (expr->ref);
6121
6122       /* Trim away the extraneous references that emerge from nested
6123          use of interface.c (extend_expr).  */
6124       get_declared_from_expr (&class_ref, NULL, code->expr1, false);
6125       if (class_ref && class_ref->next)
6126         {
6127           gfc_free_ref_list (class_ref->next);
6128           class_ref->next = NULL;
6129         }
6130       else if (code->expr1->ref && !class_ref)
6131         {
6132           gfc_free_ref_list (code->expr1->ref);
6133           code->expr1->ref = NULL;
6134         }
6135
6136       /* Now use the procedure in the vtable.  */
6137       gfc_add_vptr_component (code->expr1);
6138       gfc_add_component_ref (code->expr1, name);
6139       code->expr1->value.function.esym = NULL;
6140       if (expr->expr_type != EXPR_VARIABLE)
6141         code->expr1->base_expr = expr;
6142       return SUCCESS;
6143     }
6144
6145   if (st == NULL)
6146     return resolve_typebound_call (code, NULL);
6147
6148   if (resolve_ref (code->expr1) == FAILURE)
6149     return FAILURE;
6150
6151   /* Get the CLASS declared type.  */
6152   get_declared_from_expr (&class_ref, &new_ref, code->expr1, true);
6153
6154   /* Weed out cases of the ultimate component being a derived type.  */
6155   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
6156          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
6157     {
6158       gfc_free_ref_list (new_ref);
6159       return resolve_typebound_call (code, NULL);
6160     }
6161
6162   if (resolve_typebound_call (code, &name) == FAILURE)
6163     return FAILURE;
6164   ts = code->expr1->ts;
6165
6166   if (overridable)
6167     {
6168       /* Convert the expression to a procedure pointer component call.  */
6169       code->expr1->value.function.esym = NULL;
6170       code->expr1->symtree = st;
6171
6172       if (new_ref)
6173         code->expr1->ref = new_ref;
6174
6175       /* '_vptr' points to the vtab, which contains the procedure pointers.  */
6176       gfc_add_vptr_component (code->expr1);
6177       gfc_add_component_ref (code->expr1, name);
6178
6179       /* Recover the typespec for the expression.  This is really only
6180         necessary for generic procedures, where the additional call
6181         to gfc_add_component_ref seems to throw the collection of the
6182         correct typespec.  */
6183       code->expr1->ts = ts;
6184     }
6185
6186   return SUCCESS;
6187 }
6188
6189
6190 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
6191
6192 static gfc_try
6193 resolve_ppc_call (gfc_code* c)
6194 {
6195   gfc_component *comp;
6196   bool b;
6197
6198   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
6199   gcc_assert (b);
6200
6201   c->resolved_sym = c->expr1->symtree->n.sym;
6202   c->expr1->expr_type = EXPR_VARIABLE;
6203
6204   if (!comp->attr.subroutine)
6205     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
6206
6207   if (resolve_ref (c->expr1) == FAILURE)
6208     return FAILURE;
6209
6210   if (update_ppc_arglist (c->expr1) == FAILURE)
6211     return FAILURE;
6212
6213   c->ext.actual = c->expr1->value.compcall.actual;
6214
6215   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
6216                               comp->formal == NULL) == FAILURE)
6217     return FAILURE;
6218
6219   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
6220
6221   return SUCCESS;
6222 }
6223
6224
6225 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
6226
6227 static gfc_try
6228 resolve_expr_ppc (gfc_expr* e)
6229 {
6230   gfc_component *comp;
6231   bool b;
6232
6233   b = gfc_is_proc_ptr_comp (e, &comp);
6234   gcc_assert (b);
6235
6236   /* Convert to EXPR_FUNCTION.  */
6237   e->expr_type = EXPR_FUNCTION;
6238   e->value.function.isym = NULL;
6239   e->value.function.actual = e->value.compcall.actual;
6240   e->ts = comp->ts;
6241   if (comp->as != NULL)
6242     e->rank = comp->as->rank;
6243
6244   if (!comp->attr.function)
6245     gfc_add_function (&comp->attr, comp->name, &e->where);
6246
6247   if (resolve_ref (e) == FAILURE)
6248     return FAILURE;
6249
6250   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
6251                               comp->formal == NULL) == FAILURE)
6252     return FAILURE;
6253
6254   if (update_ppc_arglist (e) == FAILURE)
6255     return FAILURE;
6256
6257   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
6258
6259   return SUCCESS;
6260 }
6261
6262
6263 static bool
6264 gfc_is_expandable_expr (gfc_expr *e)
6265 {
6266   gfc_constructor *con;
6267
6268   if (e->expr_type == EXPR_ARRAY)
6269     {
6270       /* Traverse the constructor looking for variables that are flavor
6271          parameter.  Parameters must be expanded since they are fully used at
6272          compile time.  */
6273       con = gfc_constructor_first (e->value.constructor);
6274       for (; con; con = gfc_constructor_next (con))
6275         {
6276           if (con->expr->expr_type == EXPR_VARIABLE
6277               && con->expr->symtree
6278               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
6279               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
6280             return true;
6281           if (con->expr->expr_type == EXPR_ARRAY
6282               && gfc_is_expandable_expr (con->expr))
6283             return true;
6284         }
6285     }
6286
6287   return false;
6288 }
6289
6290 /* Resolve an expression.  That is, make sure that types of operands agree
6291    with their operators, intrinsic operators are converted to function calls
6292    for overloaded types and unresolved function references are resolved.  */
6293
6294 gfc_try
6295 gfc_resolve_expr (gfc_expr *e)
6296 {
6297   gfc_try t;
6298   bool inquiry_save;
6299
6300   if (e == NULL)
6301     return SUCCESS;
6302
6303   /* inquiry_argument only applies to variables.  */
6304   inquiry_save = inquiry_argument;
6305   if (e->expr_type != EXPR_VARIABLE)
6306     inquiry_argument = false;
6307
6308   switch (e->expr_type)
6309     {
6310     case EXPR_OP:
6311       t = resolve_operator (e);
6312       break;
6313
6314     case EXPR_FUNCTION:
6315     case EXPR_VARIABLE:
6316
6317       if (check_host_association (e))
6318         t = resolve_function (e);
6319       else
6320         {
6321           t = resolve_variable (e);
6322           if (t == SUCCESS)
6323             expression_rank (e);
6324         }
6325
6326       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6327           && e->ref->type != REF_SUBSTRING)
6328         gfc_resolve_substring_charlen (e);
6329
6330       break;
6331
6332     case EXPR_COMPCALL:
6333       t = resolve_typebound_function (e);
6334       break;
6335
6336     case EXPR_SUBSTRING:
6337       t = resolve_ref (e);
6338       break;
6339
6340     case EXPR_CONSTANT:
6341     case EXPR_NULL:
6342       t = SUCCESS;
6343       break;
6344
6345     case EXPR_PPC:
6346       t = resolve_expr_ppc (e);
6347       break;
6348
6349     case EXPR_ARRAY:
6350       t = FAILURE;
6351       if (resolve_ref (e) == FAILURE)
6352         break;
6353
6354       t = gfc_resolve_array_constructor (e);
6355       /* Also try to expand a constructor.  */
6356       if (t == SUCCESS)
6357         {
6358           expression_rank (e);
6359           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6360             gfc_expand_constructor (e, false);
6361         }
6362
6363       /* This provides the opportunity for the length of constructors with
6364          character valued function elements to propagate the string length
6365          to the expression.  */
6366       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
6367         {
6368           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6369              here rather then add a duplicate test for it above.  */ 
6370           gfc_expand_constructor (e, false);
6371           t = gfc_resolve_character_array_constructor (e);
6372         }
6373
6374       break;
6375
6376     case EXPR_STRUCTURE:
6377       t = resolve_ref (e);
6378       if (t == FAILURE)
6379         break;
6380
6381       t = resolve_structure_cons (e, 0);
6382       if (t == FAILURE)
6383         break;
6384
6385       t = gfc_simplify_expr (e, 0);
6386       break;
6387
6388     default:
6389       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6390     }
6391
6392   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
6393     fixup_charlen (e);
6394
6395   inquiry_argument = inquiry_save;
6396
6397   return t;
6398 }
6399
6400
6401 /* Resolve an expression from an iterator.  They must be scalar and have
6402    INTEGER or (optionally) REAL type.  */
6403
6404 static gfc_try
6405 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6406                            const char *name_msgid)
6407 {
6408   if (gfc_resolve_expr (expr) == FAILURE)
6409     return FAILURE;
6410
6411   if (expr->rank != 0)
6412     {
6413       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6414       return FAILURE;
6415     }
6416
6417   if (expr->ts.type != BT_INTEGER)
6418     {
6419       if (expr->ts.type == BT_REAL)
6420         {
6421           if (real_ok)
6422             return gfc_notify_std (GFC_STD_F95_DEL,
6423                                    "Deleted feature: %s at %L must be integer",
6424                                    _(name_msgid), &expr->where);
6425           else
6426             {
6427               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6428                          &expr->where);
6429               return FAILURE;
6430             }
6431         }
6432       else
6433         {
6434           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6435           return FAILURE;
6436         }
6437     }
6438   return SUCCESS;
6439 }
6440
6441
6442 /* Resolve the expressions in an iterator structure.  If REAL_OK is
6443    false allow only INTEGER type iterators, otherwise allow REAL types.  */
6444
6445 gfc_try
6446 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
6447 {
6448   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
6449       == FAILURE)
6450     return FAILURE;
6451
6452   if (gfc_check_vardef_context (iter->var, false, false, _("iterator variable"))
6453       == FAILURE)
6454     return FAILURE;
6455
6456   if (gfc_resolve_iterator_expr (iter->start, real_ok,
6457                                  "Start expression in DO loop") == FAILURE)
6458     return FAILURE;
6459
6460   if (gfc_resolve_iterator_expr (iter->end, real_ok,
6461                                  "End expression in DO loop") == FAILURE)
6462     return FAILURE;
6463
6464   if (gfc_resolve_iterator_expr (iter->step, real_ok,
6465                                  "Step expression in DO loop") == FAILURE)
6466     return FAILURE;
6467
6468   if (iter->step->expr_type == EXPR_CONSTANT)
6469     {
6470       if ((iter->step->ts.type == BT_INTEGER
6471            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6472           || (iter->step->ts.type == BT_REAL
6473               && mpfr_sgn (iter->step->value.real) == 0))
6474         {
6475           gfc_error ("Step expression in DO loop at %L cannot be zero",
6476                      &iter->step->where);
6477           return FAILURE;
6478         }
6479     }
6480
6481   /* Convert start, end, and step to the same type as var.  */
6482   if (iter->start->ts.kind != iter->var->ts.kind
6483       || iter->start->ts.type != iter->var->ts.type)
6484     gfc_convert_type (iter->start, &iter->var->ts, 2);
6485
6486   if (iter->end->ts.kind != iter->var->ts.kind
6487       || iter->end->ts.type != iter->var->ts.type)
6488     gfc_convert_type (iter->end, &iter->var->ts, 2);
6489
6490   if (iter->step->ts.kind != iter->var->ts.kind
6491       || iter->step->ts.type != iter->var->ts.type)
6492     gfc_convert_type (iter->step, &iter->var->ts, 2);
6493
6494   if (iter->start->expr_type == EXPR_CONSTANT
6495       && iter->end->expr_type == EXPR_CONSTANT
6496       && iter->step->expr_type == EXPR_CONSTANT)
6497     {
6498       int sgn, cmp;
6499       if (iter->start->ts.type == BT_INTEGER)
6500         {
6501           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6502           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6503         }
6504       else
6505         {
6506           sgn = mpfr_sgn (iter->step->value.real);
6507           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6508         }
6509       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
6510         gfc_warning ("DO loop at %L will be executed zero times",
6511                      &iter->step->where);
6512     }
6513
6514   return SUCCESS;
6515 }
6516
6517
6518 /* Traversal function for find_forall_index.  f == 2 signals that
6519    that variable itself is not to be checked - only the references.  */
6520
6521 static bool
6522 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6523 {
6524   if (expr->expr_type != EXPR_VARIABLE)
6525     return false;
6526   
6527   /* A scalar assignment  */
6528   if (!expr->ref || *f == 1)
6529     {
6530       if (expr->symtree->n.sym == sym)
6531         return true;
6532       else
6533         return false;
6534     }
6535
6536   if (*f == 2)
6537     *f = 1;
6538   return false;
6539 }
6540
6541
6542 /* Check whether the FORALL index appears in the expression or not.
6543    Returns SUCCESS if SYM is found in EXPR.  */
6544
6545 gfc_try
6546 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6547 {
6548   if (gfc_traverse_expr (expr, sym, forall_index, f))
6549     return SUCCESS;
6550   else
6551     return FAILURE;
6552 }
6553
6554
6555 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6556    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6557    INTEGERs, and if stride is a constant it must be nonzero.
6558    Furthermore "A subscript or stride in a forall-triplet-spec shall
6559    not contain a reference to any index-name in the
6560    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6561
6562 static void
6563 resolve_forall_iterators (gfc_forall_iterator *it)
6564 {
6565   gfc_forall_iterator *iter, *iter2;
6566
6567   for (iter = it; iter; iter = iter->next)
6568     {
6569       if (gfc_resolve_expr (iter->var) == SUCCESS
6570           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6571         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6572                    &iter->var->where);
6573
6574       if (gfc_resolve_expr (iter->start) == SUCCESS
6575           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6576         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6577                    &iter->start->where);
6578       if (iter->var->ts.kind != iter->start->ts.kind)
6579         gfc_convert_type (iter->start, &iter->var->ts, 1);
6580
6581       if (gfc_resolve_expr (iter->end) == SUCCESS
6582           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6583         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6584                    &iter->end->where);
6585       if (iter->var->ts.kind != iter->end->ts.kind)
6586         gfc_convert_type (iter->end, &iter->var->ts, 1);
6587
6588       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6589         {
6590           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6591             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6592                        &iter->stride->where, "INTEGER");
6593
6594           if (iter->stride->expr_type == EXPR_CONSTANT
6595               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6596             gfc_error ("FORALL stride expression at %L cannot be zero",
6597                        &iter->stride->where);
6598         }
6599       if (iter->var->ts.kind != iter->stride->ts.kind)
6600         gfc_convert_type (iter->stride, &iter->var->ts, 1);
6601     }
6602
6603   for (iter = it; iter; iter = iter->next)
6604     for (iter2 = iter; iter2; iter2 = iter2->next)
6605       {
6606         if (find_forall_index (iter2->start,
6607                                iter->var->symtree->n.sym, 0) == SUCCESS
6608             || find_forall_index (iter2->end,
6609                                   iter->var->symtree->n.sym, 0) == SUCCESS
6610             || find_forall_index (iter2->stride,
6611                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6612           gfc_error ("FORALL index '%s' may not appear in triplet "
6613                      "specification at %L", iter->var->symtree->name,
6614                      &iter2->start->where);
6615       }
6616 }
6617
6618
6619 /* Given a pointer to a symbol that is a derived type, see if it's
6620    inaccessible, i.e. if it's defined in another module and the components are
6621    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6622    inaccessible components are found, nonzero otherwise.  */
6623
6624 static int
6625 derived_inaccessible (gfc_symbol *sym)
6626 {
6627   gfc_component *c;
6628
6629   if (sym->attr.use_assoc && sym->attr.private_comp)
6630     return 1;
6631
6632   for (c = sym->components; c; c = c->next)
6633     {
6634         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6635           return 1;
6636     }
6637
6638   return 0;
6639 }
6640
6641
6642 /* Resolve the argument of a deallocate expression.  The expression must be
6643    a pointer or a full array.  */
6644
6645 static gfc_try
6646 resolve_deallocate_expr (gfc_expr *e)
6647 {
6648   symbol_attribute attr;
6649   int allocatable, pointer;
6650   gfc_ref *ref;
6651   gfc_symbol *sym;
6652   gfc_component *c;
6653
6654   if (gfc_resolve_expr (e) == FAILURE)
6655     return FAILURE;
6656
6657   if (e->expr_type != EXPR_VARIABLE)
6658     goto bad;
6659
6660   sym = e->symtree->n.sym;
6661
6662   if (sym->ts.type == BT_CLASS)
6663     {
6664       allocatable = CLASS_DATA (sym)->attr.allocatable;
6665       pointer = CLASS_DATA (sym)->attr.class_pointer;
6666     }
6667   else
6668     {
6669       allocatable = sym->attr.allocatable;
6670       pointer = sym->attr.pointer;
6671     }
6672   for (ref = e->ref; ref; ref = ref->next)
6673     {
6674       switch (ref->type)
6675         {
6676         case REF_ARRAY:
6677           if (ref->u.ar.type != AR_FULL
6678               && !(ref->u.ar.type == AR_ELEMENT && ref->u.ar.as->rank == 0
6679                    && ref->u.ar.codimen && gfc_ref_this_image (ref)))
6680             allocatable = 0;
6681           break;
6682
6683         case REF_COMPONENT:
6684           c = ref->u.c.component;
6685           if (c->ts.type == BT_CLASS)
6686             {
6687               allocatable = CLASS_DATA (c)->attr.allocatable;
6688               pointer = CLASS_DATA (c)->attr.class_pointer;
6689             }
6690           else
6691             {
6692               allocatable = c->attr.allocatable;
6693               pointer = c->attr.pointer;
6694             }
6695           break;
6696
6697         case REF_SUBSTRING:
6698           allocatable = 0;
6699           break;
6700         }
6701     }
6702
6703   attr = gfc_expr_attr (e);
6704
6705   if (allocatable == 0 && attr.pointer == 0)
6706     {
6707     bad:
6708       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6709                  &e->where);
6710       return FAILURE;
6711     }
6712
6713   /* F2008, C644.  */
6714   if (gfc_is_coindexed (e))
6715     {
6716       gfc_error ("Coindexed allocatable object at %L", &e->where);
6717       return FAILURE;
6718     }
6719
6720   if (pointer
6721       && gfc_check_vardef_context (e, true, true, _("DEALLOCATE object"))
6722          == FAILURE)
6723     return FAILURE;
6724   if (gfc_check_vardef_context (e, false, true, _("DEALLOCATE object"))
6725       == FAILURE)
6726     return FAILURE;
6727
6728   return SUCCESS;
6729 }
6730
6731
6732 /* Returns true if the expression e contains a reference to the symbol sym.  */
6733 static bool
6734 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6735 {
6736   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6737     return true;
6738
6739   return false;
6740 }
6741
6742 bool
6743 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6744 {
6745   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6746 }
6747
6748
6749 /* Given the expression node e for an allocatable/pointer of derived type to be
6750    allocated, get the expression node to be initialized afterwards (needed for
6751    derived types with default initializers, and derived types with allocatable
6752    components that need nullification.)  */
6753
6754 gfc_expr *
6755 gfc_expr_to_initialize (gfc_expr *e)
6756 {
6757   gfc_expr *result;
6758   gfc_ref *ref;
6759   int i;
6760
6761   result = gfc_copy_expr (e);
6762
6763   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6764   for (ref = result->ref; ref; ref = ref->next)
6765     if (ref->type == REF_ARRAY && ref->next == NULL)
6766       {
6767         ref->u.ar.type = AR_FULL;
6768
6769         for (i = 0; i < ref->u.ar.dimen; i++)
6770           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6771
6772         break;
6773       }
6774
6775   gfc_free_shape (&result->shape, result->rank);
6776
6777   /* Recalculate rank, shape, etc.  */
6778   gfc_resolve_expr (result);
6779   return result;
6780 }
6781
6782
6783 /* If the last ref of an expression is an array ref, return a copy of the
6784    expression with that one removed.  Otherwise, a copy of the original
6785    expression.  This is used for allocate-expressions and pointer assignment
6786    LHS, where there may be an array specification that needs to be stripped
6787    off when using gfc_check_vardef_context.  */
6788
6789 static gfc_expr*
6790 remove_last_array_ref (gfc_expr* e)
6791 {
6792   gfc_expr* e2;
6793   gfc_ref** r;
6794
6795   e2 = gfc_copy_expr (e);
6796   for (r = &e2->ref; *r; r = &(*r)->next)
6797     if ((*r)->type == REF_ARRAY && !(*r)->next)
6798       {
6799         gfc_free_ref_list (*r);
6800         *r = NULL;
6801         break;
6802       }
6803
6804   return e2;
6805 }
6806
6807
6808 /* Used in resolve_allocate_expr to check that a allocation-object and
6809    a source-expr are conformable.  This does not catch all possible 
6810    cases; in particular a runtime checking is needed.  */
6811
6812 static gfc_try
6813 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6814 {
6815   gfc_ref *tail;
6816   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6817   
6818   /* First compare rank.  */
6819   if (tail && e1->rank != tail->u.ar.as->rank)
6820     {
6821       gfc_error ("Source-expr at %L must be scalar or have the "
6822                  "same rank as the allocate-object at %L",
6823                  &e1->where, &e2->where);
6824       return FAILURE;
6825     }
6826
6827   if (e1->shape)
6828     {
6829       int i;
6830       mpz_t s;
6831
6832       mpz_init (s);
6833
6834       for (i = 0; i < e1->rank; i++)
6835         {
6836           if (tail->u.ar.end[i])
6837             {
6838               mpz_set (s, tail->u.ar.end[i]->value.integer);
6839               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6840               mpz_add_ui (s, s, 1);
6841             }
6842           else
6843             {
6844               mpz_set (s, tail->u.ar.start[i]->value.integer);
6845             }
6846
6847           if (mpz_cmp (e1->shape[i], s) != 0)
6848             {
6849               gfc_error ("Source-expr at %L and allocate-object at %L must "
6850                          "have the same shape", &e1->where, &e2->where);
6851               mpz_clear (s);
6852               return FAILURE;
6853             }
6854         }
6855
6856       mpz_clear (s);
6857     }
6858
6859   return SUCCESS;
6860 }
6861
6862
6863 /* Resolve the expression in an ALLOCATE statement, doing the additional
6864    checks to see whether the expression is OK or not.  The expression must
6865    have a trailing array reference that gives the size of the array.  */
6866
6867 static gfc_try
6868 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6869 {
6870   int i, pointer, allocatable, dimension, is_abstract;
6871   int codimension;
6872   bool coindexed;
6873   symbol_attribute attr;
6874   gfc_ref *ref, *ref2;
6875   gfc_expr *e2;
6876   gfc_array_ref *ar;
6877   gfc_symbol *sym = NULL;
6878   gfc_alloc *a;
6879   gfc_component *c;
6880   gfc_try t;
6881
6882   /* Mark the utmost array component as being in allocate to allow DIMEN_STAR
6883      checking of coarrays.  */
6884   for (ref = e->ref; ref; ref = ref->next)
6885     if (ref->next == NULL)
6886       break;
6887
6888   if (ref && ref->type == REF_ARRAY)
6889     ref->u.ar.in_allocate = true;
6890
6891   if (gfc_resolve_expr (e) == FAILURE)
6892     goto failure;
6893
6894   /* Make sure the expression is allocatable or a pointer.  If it is
6895      pointer, the next-to-last reference must be a pointer.  */
6896
6897   ref2 = NULL;
6898   if (e->symtree)
6899     sym = e->symtree->n.sym;
6900
6901   /* Check whether ultimate component is abstract and CLASS.  */
6902   is_abstract = 0;
6903
6904   if (e->expr_type != EXPR_VARIABLE)
6905     {
6906       allocatable = 0;
6907       attr = gfc_expr_attr (e);
6908       pointer = attr.pointer;
6909       dimension = attr.dimension;
6910       codimension = attr.codimension;
6911     }
6912   else
6913     {
6914       if (sym->ts.type == BT_CLASS && CLASS_DATA (sym))
6915         {
6916           allocatable = CLASS_DATA (sym)->attr.allocatable;
6917           pointer = CLASS_DATA (sym)->attr.class_pointer;
6918           dimension = CLASS_DATA (sym)->attr.dimension;
6919           codimension = CLASS_DATA (sym)->attr.codimension;
6920           is_abstract = CLASS_DATA (sym)->attr.abstract;
6921         }
6922       else
6923         {
6924           allocatable = sym->attr.allocatable;
6925           pointer = sym->attr.pointer;
6926           dimension = sym->attr.dimension;
6927           codimension = sym->attr.codimension;
6928         }
6929
6930       coindexed = false;
6931
6932       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6933         {
6934           switch (ref->type)
6935             {
6936               case REF_ARRAY:
6937                 if (ref->u.ar.codimen > 0)
6938                   {
6939                     int n;
6940                     for (n = ref->u.ar.dimen;
6941                          n < ref->u.ar.dimen + ref->u.ar.codimen; n++)
6942                       if (ref->u.ar.dimen_type[n] != DIMEN_THIS_IMAGE)
6943                         {
6944                           coindexed = true;
6945                           break;
6946                         }
6947                    }
6948
6949                 if (ref->next != NULL)
6950                   pointer = 0;
6951                 break;
6952
6953               case REF_COMPONENT:
6954                 /* F2008, C644.  */
6955                 if (coindexed)
6956                   {
6957                     gfc_error ("Coindexed allocatable object at %L",
6958                                &e->where);
6959                     goto failure;
6960                   }
6961
6962                 c = ref->u.c.component;
6963                 if (c->ts.type == BT_CLASS)
6964                   {
6965                     allocatable = CLASS_DATA (c)->attr.allocatable;
6966                     pointer = CLASS_DATA (c)->attr.class_pointer;
6967                     dimension = CLASS_DATA (c)->attr.dimension;
6968                     codimension = CLASS_DATA (c)->attr.codimension;
6969                     is_abstract = CLASS_DATA (c)->attr.abstract;
6970                   }
6971                 else
6972                   {
6973                     allocatable = c->attr.allocatable;
6974                     pointer = c->attr.pointer;
6975                     dimension = c->attr.dimension;
6976                     codimension = c->attr.codimension;
6977                     is_abstract = c->attr.abstract;
6978                   }
6979                 break;
6980
6981               case REF_SUBSTRING:
6982                 allocatable = 0;
6983                 pointer = 0;
6984                 break;
6985             }
6986         }
6987     }
6988
6989   /* Check for F08:C628.  */
6990   if (allocatable == 0 && pointer == 0)
6991     {
6992       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6993                  &e->where);
6994       goto failure;
6995     }
6996
6997   /* Some checks for the SOURCE tag.  */
6998   if (code->expr3)
6999     {
7000       /* Check F03:C631.  */
7001       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
7002         {
7003           gfc_error ("Type of entity at %L is type incompatible with "
7004                       "source-expr at %L", &e->where, &code->expr3->where);
7005           goto failure;
7006         }
7007
7008       /* Check F03:C632 and restriction following Note 6.18.  */
7009       if (code->expr3->rank > 0
7010           && conformable_arrays (code->expr3, e) == FAILURE)
7011         goto failure;
7012
7013       /* Check F03:C633.  */
7014       if (code->expr3->ts.kind != e->ts.kind)
7015         {
7016           gfc_error ("The allocate-object at %L and the source-expr at %L "
7017                       "shall have the same kind type parameter",
7018                       &e->where, &code->expr3->where);
7019           goto failure;
7020         }
7021
7022       /* Check F2008, C642.  */
7023       if (code->expr3->ts.type == BT_DERIVED
7024           && ((codimension && gfc_expr_attr (code->expr3).lock_comp)
7025               || (code->expr3->ts.u.derived->from_intmod
7026                      == INTMOD_ISO_FORTRAN_ENV
7027                   && code->expr3->ts.u.derived->intmod_sym_id
7028                      == ISOFORTRAN_LOCK_TYPE)))
7029         {
7030           gfc_error ("The source-expr at %L shall neither be of type "
7031                      "LOCK_TYPE nor have a LOCK_TYPE component if "
7032                       "allocate-object at %L is a coarray",
7033                       &code->expr3->where, &e->where);
7034           goto failure;
7035         }
7036     }
7037
7038   /* Check F08:C629.  */
7039   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
7040       && !code->expr3)
7041     {
7042       gcc_assert (e->ts.type == BT_CLASS);
7043       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
7044                  "type-spec or source-expr", sym->name, &e->where);
7045       goto failure;
7046     }
7047
7048   if (code->ext.alloc.ts.type == BT_CHARACTER && !e->ts.deferred)
7049     {
7050       int cmp = gfc_dep_compare_expr (e->ts.u.cl->length,
7051                                       code->ext.alloc.ts.u.cl->length);
7052       if (cmp == 1 || cmp == -1 || cmp == -3)
7053         {
7054           gfc_error ("Allocating %s at %L with type-spec requires the same "
7055                      "character-length parameter as in the declaration",
7056                      sym->name, &e->where);
7057           goto failure;
7058         }
7059     }
7060
7061   /* In the variable definition context checks, gfc_expr_attr is used
7062      on the expression.  This is fooled by the array specification
7063      present in e, thus we have to eliminate that one temporarily.  */
7064   e2 = remove_last_array_ref (e);
7065   t = SUCCESS;
7066   if (t == SUCCESS && pointer)
7067     t = gfc_check_vardef_context (e2, true, true, _("ALLOCATE object"));
7068   if (t == SUCCESS)
7069     t = gfc_check_vardef_context (e2, false, true, _("ALLOCATE object"));
7070   gfc_free_expr (e2);
7071   if (t == FAILURE)
7072     goto failure;
7073
7074   if (e->ts.type == BT_CLASS && CLASS_DATA (e)->attr.dimension
7075         && !code->expr3 && code->ext.alloc.ts.type == BT_DERIVED)
7076     {
7077       /* For class arrays, the initialization with SOURCE is done
7078          using _copy and trans_call. It is convenient to exploit that
7079          when the allocated type is different from the declared type but
7080          no SOURCE exists by setting expr3.  */
7081       code->expr3 = gfc_default_initializer (&code->ext.alloc.ts); 
7082     }
7083   else if (!code->expr3)
7084     {
7085       /* Set up default initializer if needed.  */
7086       gfc_typespec ts;
7087       gfc_expr *init_e;
7088
7089       if (code->ext.alloc.ts.type == BT_DERIVED)
7090         ts = code->ext.alloc.ts;
7091       else
7092         ts = e->ts;
7093
7094       if (ts.type == BT_CLASS)
7095         ts = ts.u.derived->components->ts;
7096
7097       if (ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&ts)))
7098         {
7099           gfc_code *init_st = gfc_get_code ();
7100           init_st->loc = code->loc;
7101           init_st->op = EXEC_INIT_ASSIGN;
7102           init_st->expr1 = gfc_expr_to_initialize (e);
7103           init_st->expr2 = init_e;
7104           init_st->next = code->next;
7105           code->next = init_st;
7106         }
7107     }
7108   else if (code->expr3->mold && code->expr3->ts.type == BT_DERIVED)
7109     {
7110       /* Default initialization via MOLD (non-polymorphic).  */
7111       gfc_expr *rhs = gfc_default_initializer (&code->expr3->ts);
7112       gfc_resolve_expr (rhs);
7113       gfc_free_expr (code->expr3);
7114       code->expr3 = rhs;
7115     }
7116
7117   if (e->ts.type == BT_CLASS)
7118     {
7119       /* Make sure the vtab symbol is present when
7120          the module variables are generated.  */
7121       gfc_typespec ts = e->ts;
7122       if (code->expr3)
7123         ts = code->expr3->ts;
7124       else if (code->ext.alloc.ts.type == BT_DERIVED)
7125         ts = code->ext.alloc.ts;
7126       gfc_find_derived_vtab (ts.u.derived);
7127       if (dimension)
7128         e = gfc_expr_to_initialize (e);
7129     }
7130
7131   if (dimension == 0 && codimension == 0)
7132     goto success;
7133
7134   /* Make sure the last reference node is an array specification.  */
7135
7136   if (!ref2 || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
7137       || (dimension && ref2->u.ar.dimen == 0))
7138     {
7139       gfc_error ("Array specification required in ALLOCATE statement "
7140                  "at %L", &e->where);
7141       goto failure;
7142     }
7143
7144   /* Make sure that the array section reference makes sense in the
7145     context of an ALLOCATE specification.  */
7146
7147   ar = &ref2->u.ar;
7148
7149   if (codimension)
7150     for (i = ar->dimen; i < ar->dimen + ar->codimen; i++)
7151       if (ar->dimen_type[i] == DIMEN_THIS_IMAGE)
7152         {
7153           gfc_error ("Coarray specification required in ALLOCATE statement "
7154                      "at %L", &e->where);
7155           goto failure;
7156         }
7157
7158   for (i = 0; i < ar->dimen; i++)
7159     {
7160       if (ref2->u.ar.type == AR_ELEMENT)
7161         goto check_symbols;
7162
7163       switch (ar->dimen_type[i])
7164         {
7165         case DIMEN_ELEMENT:
7166           break;
7167
7168         case DIMEN_RANGE:
7169           if (ar->start[i] != NULL
7170               && ar->end[i] != NULL
7171               && ar->stride[i] == NULL)
7172             break;
7173
7174           /* Fall Through...  */
7175
7176         case DIMEN_UNKNOWN:
7177         case DIMEN_VECTOR:
7178         case DIMEN_STAR:
7179         case DIMEN_THIS_IMAGE:
7180           gfc_error ("Bad array specification in ALLOCATE statement at %L",
7181                      &e->where);
7182           goto failure;
7183         }
7184
7185 check_symbols:
7186       for (a = code->ext.alloc.list; a; a = a->next)
7187         {
7188           sym = a->expr->symtree->n.sym;
7189
7190           /* TODO - check derived type components.  */
7191           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
7192             continue;
7193
7194           if ((ar->start[i] != NULL
7195                && gfc_find_sym_in_expr (sym, ar->start[i]))
7196               || (ar->end[i] != NULL
7197                   && gfc_find_sym_in_expr (sym, ar->end[i])))
7198             {
7199               gfc_error ("'%s' must not appear in the array specification at "
7200                          "%L in the same ALLOCATE statement where it is "
7201                          "itself allocated", sym->name, &ar->where);
7202               goto failure;
7203             }
7204         }
7205     }
7206
7207   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
7208     {
7209       if (ar->dimen_type[i] == DIMEN_ELEMENT
7210           || ar->dimen_type[i] == DIMEN_RANGE)
7211         {
7212           if (i == (ar->dimen + ar->codimen - 1))
7213             {
7214               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
7215                          "statement at %L", &e->where);
7216               goto failure;
7217             }
7218           break;
7219         }
7220
7221       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
7222           && ar->stride[i] == NULL)
7223         break;
7224
7225       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
7226                  &e->where);
7227       goto failure;
7228     }
7229
7230 success:
7231   return SUCCESS;
7232
7233 failure:
7234   return FAILURE;
7235 }
7236
7237 static void
7238 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
7239 {
7240   gfc_expr *stat, *errmsg, *pe, *qe;
7241   gfc_alloc *a, *p, *q;
7242
7243   stat = code->expr1;
7244   errmsg = code->expr2;
7245
7246   /* Check the stat variable.  */
7247   if (stat)
7248     {
7249       gfc_check_vardef_context (stat, false, false, _("STAT variable"));
7250
7251       if ((stat->ts.type != BT_INTEGER
7252            && !(stat->ref && (stat->ref->type == REF_ARRAY
7253                               || stat->ref->type == REF_COMPONENT)))
7254           || stat->rank > 0)
7255         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
7256                    "variable", &stat->where);
7257
7258       for (p = code->ext.alloc.list; p; p = p->next)
7259         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
7260           {
7261             gfc_ref *ref1, *ref2;
7262             bool found = true;
7263
7264             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
7265                  ref1 = ref1->next, ref2 = ref2->next)
7266               {
7267                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7268                   continue;
7269                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7270                   {
7271                     found = false;
7272                     break;
7273                   }
7274               }
7275
7276             if (found)
7277               {
7278                 gfc_error ("Stat-variable at %L shall not be %sd within "
7279                            "the same %s statement", &stat->where, fcn, fcn);
7280                 break;
7281               }
7282           }
7283     }
7284
7285   /* Check the errmsg variable.  */
7286   if (errmsg)
7287     {
7288       if (!stat)
7289         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
7290                      &errmsg->where);
7291
7292       gfc_check_vardef_context (errmsg, false, false, _("ERRMSG variable"));
7293
7294       if ((errmsg->ts.type != BT_CHARACTER
7295            && !(errmsg->ref
7296                 && (errmsg->ref->type == REF_ARRAY
7297                     || errmsg->ref->type == REF_COMPONENT)))
7298           || errmsg->rank > 0 )
7299         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
7300                    "variable", &errmsg->where);
7301
7302       for (p = code->ext.alloc.list; p; p = p->next)
7303         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
7304           {
7305             gfc_ref *ref1, *ref2;
7306             bool found = true;
7307
7308             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
7309                  ref1 = ref1->next, ref2 = ref2->next)
7310               {
7311                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7312                   continue;
7313                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7314                   {
7315                     found = false;
7316                     break;
7317                   }
7318               }
7319
7320             if (found)
7321               {
7322                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
7323                            "the same %s statement", &errmsg->where, fcn, fcn);
7324                 break;
7325               }
7326           }
7327     }
7328
7329   /* Check that an allocate-object appears only once in the statement.  
7330      FIXME: Checking derived types is disabled.  */
7331   for (p = code->ext.alloc.list; p; p = p->next)
7332     {
7333       pe = p->expr;
7334       for (q = p->next; q; q = q->next)
7335         {
7336           qe = q->expr;
7337           if (pe->symtree->n.sym->name == qe->symtree->n.sym->name)
7338             {
7339               /* This is a potential collision.  */
7340               gfc_ref *pr = pe->ref;
7341               gfc_ref *qr = qe->ref;
7342               
7343               /* Follow the references  until
7344                  a) They start to differ, in which case there is no error;
7345                  you can deallocate a%b and a%c in a single statement
7346                  b) Both of them stop, which is an error
7347                  c) One of them stops, which is also an error.  */
7348               while (1)
7349                 {
7350                   if (pr == NULL && qr == NULL)
7351                     {
7352                       gfc_error ("Allocate-object at %L also appears at %L",
7353                                  &pe->where, &qe->where);
7354                       break;
7355                     }
7356                   else if (pr != NULL && qr == NULL)
7357                     {
7358                       gfc_error ("Allocate-object at %L is subobject of"
7359                                  " object at %L", &pe->where, &qe->where);
7360                       break;
7361                     }
7362                   else if (pr == NULL && qr != NULL)
7363                     {
7364                       gfc_error ("Allocate-object at %L is subobject of"
7365                                  " object at %L", &qe->where, &pe->where);
7366                       break;
7367                     }
7368                   /* Here, pr != NULL && qr != NULL  */
7369                   gcc_assert(pr->type == qr->type);
7370                   if (pr->type == REF_ARRAY)
7371                     {
7372                       /* Handle cases like allocate(v(3)%x(3), v(2)%x(3)),
7373                          which are legal.  */
7374                       gcc_assert (qr->type == REF_ARRAY);
7375
7376                       if (pr->next && qr->next)
7377                         {
7378                           gfc_array_ref *par = &(pr->u.ar);
7379                           gfc_array_ref *qar = &(qr->u.ar);
7380                           if (gfc_dep_compare_expr (par->start[0],
7381                                                     qar->start[0]) != 0)
7382                               break;
7383                         }
7384                     }
7385                   else
7386                     {
7387                       if (pr->u.c.component->name != qr->u.c.component->name)
7388                         break;
7389                     }
7390                   
7391                   pr = pr->next;
7392                   qr = qr->next;
7393                 }
7394             }
7395         }
7396     }
7397
7398   if (strcmp (fcn, "ALLOCATE") == 0)
7399     {
7400       for (a = code->ext.alloc.list; a; a = a->next)
7401         resolve_allocate_expr (a->expr, code);
7402     }
7403   else
7404     {
7405       for (a = code->ext.alloc.list; a; a = a->next)
7406         resolve_deallocate_expr (a->expr);
7407     }
7408 }
7409
7410
7411 /************ SELECT CASE resolution subroutines ************/
7412
7413 /* Callback function for our mergesort variant.  Determines interval
7414    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7415    op1 > op2.  Assumes we're not dealing with the default case.  
7416    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7417    There are nine situations to check.  */
7418
7419 static int
7420 compare_cases (const gfc_case *op1, const gfc_case *op2)
7421 {
7422   int retval;
7423
7424   if (op1->low == NULL) /* op1 = (:L)  */
7425     {
7426       /* op2 = (:N), so overlap.  */
7427       retval = 0;
7428       /* op2 = (M:) or (M:N),  L < M  */
7429       if (op2->low != NULL
7430           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7431         retval = -1;
7432     }
7433   else if (op1->high == NULL) /* op1 = (K:)  */
7434     {
7435       /* op2 = (M:), so overlap.  */
7436       retval = 0;
7437       /* op2 = (:N) or (M:N), K > N  */
7438       if (op2->high != NULL
7439           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7440         retval = 1;
7441     }
7442   else /* op1 = (K:L)  */
7443     {
7444       if (op2->low == NULL)       /* op2 = (:N), K > N  */
7445         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7446                  ? 1 : 0;
7447       else if (op2->high == NULL) /* op2 = (M:), L < M  */
7448         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7449                  ? -1 : 0;
7450       else                      /* op2 = (M:N)  */
7451         {
7452           retval =  0;
7453           /* L < M  */
7454           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7455             retval =  -1;
7456           /* K > N  */
7457           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7458             retval =  1;
7459         }
7460     }
7461
7462   return retval;
7463 }
7464
7465
7466 /* Merge-sort a double linked case list, detecting overlap in the
7467    process.  LIST is the head of the double linked case list before it
7468    is sorted.  Returns the head of the sorted list if we don't see any
7469    overlap, or NULL otherwise.  */
7470
7471 static gfc_case *
7472 check_case_overlap (gfc_case *list)
7473 {
7474   gfc_case *p, *q, *e, *tail;
7475   int insize, nmerges, psize, qsize, cmp, overlap_seen;
7476
7477   /* If the passed list was empty, return immediately.  */
7478   if (!list)
7479     return NULL;
7480
7481   overlap_seen = 0;
7482   insize = 1;
7483
7484   /* Loop unconditionally.  The only exit from this loop is a return
7485      statement, when we've finished sorting the case list.  */
7486   for (;;)
7487     {
7488       p = list;
7489       list = NULL;
7490       tail = NULL;
7491
7492       /* Count the number of merges we do in this pass.  */
7493       nmerges = 0;
7494
7495       /* Loop while there exists a merge to be done.  */
7496       while (p)
7497         {
7498           int i;
7499
7500           /* Count this merge.  */
7501           nmerges++;
7502
7503           /* Cut the list in two pieces by stepping INSIZE places
7504              forward in the list, starting from P.  */
7505           psize = 0;
7506           q = p;
7507           for (i = 0; i < insize; i++)
7508             {
7509               psize++;
7510               q = q->right;
7511               if (!q)
7512                 break;
7513             }
7514           qsize = insize;
7515
7516           /* Now we have two lists.  Merge them!  */
7517           while (psize > 0 || (qsize > 0 && q != NULL))
7518             {
7519               /* See from which the next case to merge comes from.  */
7520               if (psize == 0)
7521                 {
7522                   /* P is empty so the next case must come from Q.  */
7523                   e = q;
7524                   q = q->right;
7525                   qsize--;
7526                 }
7527               else if (qsize == 0 || q == NULL)
7528                 {
7529                   /* Q is empty.  */
7530                   e = p;
7531                   p = p->right;
7532                   psize--;
7533                 }
7534               else
7535                 {
7536                   cmp = compare_cases (p, q);
7537                   if (cmp < 0)
7538                     {
7539                       /* The whole case range for P is less than the
7540                          one for Q.  */
7541                       e = p;
7542                       p = p->right;
7543                       psize--;
7544                     }
7545                   else if (cmp > 0)
7546                     {
7547                       /* The whole case range for Q is greater than
7548                          the case range for P.  */
7549                       e = q;
7550                       q = q->right;
7551                       qsize--;
7552                     }
7553                   else
7554                     {
7555                       /* The cases overlap, or they are the same
7556                          element in the list.  Either way, we must
7557                          issue an error and get the next case from P.  */
7558                       /* FIXME: Sort P and Q by line number.  */
7559                       gfc_error ("CASE label at %L overlaps with CASE "
7560                                  "label at %L", &p->where, &q->where);
7561                       overlap_seen = 1;
7562                       e = p;
7563                       p = p->right;
7564                       psize--;
7565                     }
7566                 }
7567
7568                 /* Add the next element to the merged list.  */
7569               if (tail)
7570                 tail->right = e;
7571               else
7572                 list = e;
7573               e->left = tail;
7574               tail = e;
7575             }
7576
7577           /* P has now stepped INSIZE places along, and so has Q.  So
7578              they're the same.  */
7579           p = q;
7580         }
7581       tail->right = NULL;
7582
7583       /* If we have done only one merge or none at all, we've
7584          finished sorting the cases.  */
7585       if (nmerges <= 1)
7586         {
7587           if (!overlap_seen)
7588             return list;
7589           else
7590             return NULL;
7591         }
7592
7593       /* Otherwise repeat, merging lists twice the size.  */
7594       insize *= 2;
7595     }
7596 }
7597
7598
7599 /* Check to see if an expression is suitable for use in a CASE statement.
7600    Makes sure that all case expressions are scalar constants of the same
7601    type.  Return FAILURE if anything is wrong.  */
7602
7603 static gfc_try
7604 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7605 {
7606   if (e == NULL) return SUCCESS;
7607
7608   if (e->ts.type != case_expr->ts.type)
7609     {
7610       gfc_error ("Expression in CASE statement at %L must be of type %s",
7611                  &e->where, gfc_basic_typename (case_expr->ts.type));
7612       return FAILURE;
7613     }
7614
7615   /* C805 (R808) For a given case-construct, each case-value shall be of
7616      the same type as case-expr.  For character type, length differences
7617      are allowed, but the kind type parameters shall be the same.  */
7618
7619   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7620     {
7621       gfc_error ("Expression in CASE statement at %L must be of kind %d",
7622                  &e->where, case_expr->ts.kind);
7623       return FAILURE;
7624     }
7625
7626   /* Convert the case value kind to that of case expression kind,
7627      if needed */
7628
7629   if (e->ts.kind != case_expr->ts.kind)
7630     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7631
7632   if (e->rank != 0)
7633     {
7634       gfc_error ("Expression in CASE statement at %L must be scalar",
7635                  &e->where);
7636       return FAILURE;
7637     }
7638
7639   return SUCCESS;
7640 }
7641
7642
7643 /* Given a completely parsed select statement, we:
7644
7645      - Validate all expressions and code within the SELECT.
7646      - Make sure that the selection expression is not of the wrong type.
7647      - Make sure that no case ranges overlap.
7648      - Eliminate unreachable cases and unreachable code resulting from
7649        removing case labels.
7650
7651    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7652    they are a hassle for code generation, and to prevent that, we just
7653    cut them out here.  This is not necessary for overlapping cases
7654    because they are illegal and we never even try to generate code.
7655
7656    We have the additional caveat that a SELECT construct could have
7657    been a computed GOTO in the source code. Fortunately we can fairly
7658    easily work around that here: The case_expr for a "real" SELECT CASE
7659    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7660    we have to do is make sure that the case_expr is a scalar integer
7661    expression.  */
7662
7663 static void
7664 resolve_select (gfc_code *code)
7665 {
7666   gfc_code *body;
7667   gfc_expr *case_expr;
7668   gfc_case *cp, *default_case, *tail, *head;
7669   int seen_unreachable;
7670   int seen_logical;
7671   int ncases;
7672   bt type;
7673   gfc_try t;
7674
7675   if (code->expr1 == NULL)
7676     {
7677       /* This was actually a computed GOTO statement.  */
7678       case_expr = code->expr2;
7679       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7680         gfc_error ("Selection expression in computed GOTO statement "
7681                    "at %L must be a scalar integer expression",
7682                    &case_expr->where);
7683
7684       /* Further checking is not necessary because this SELECT was built
7685          by the compiler, so it should always be OK.  Just move the
7686          case_expr from expr2 to expr so that we can handle computed
7687          GOTOs as normal SELECTs from here on.  */
7688       code->expr1 = code->expr2;
7689       code->expr2 = NULL;
7690       return;
7691     }
7692
7693   case_expr = code->expr1;
7694
7695   type = case_expr->ts.type;
7696   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7697     {
7698       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7699                  &case_expr->where, gfc_typename (&case_expr->ts));
7700
7701       /* Punt. Going on here just produce more garbage error messages.  */
7702       return;
7703     }
7704
7705   /* Raise a warning if an INTEGER case value exceeds the range of
7706      the case-expr. Later, all expressions will be promoted to the
7707      largest kind of all case-labels.  */
7708
7709   if (type == BT_INTEGER)
7710     for (body = code->block; body; body = body->block)
7711       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7712         {
7713           if (cp->low
7714               && gfc_check_integer_range (cp->low->value.integer,
7715                                           case_expr->ts.kind) != ARITH_OK)
7716             gfc_warning ("Expression in CASE statement at %L is "
7717                          "not in the range of %s", &cp->low->where,
7718                          gfc_typename (&case_expr->ts));
7719
7720           if (cp->high
7721               && cp->low != cp->high
7722               && gfc_check_integer_range (cp->high->value.integer,
7723                                           case_expr->ts.kind) != ARITH_OK)
7724             gfc_warning ("Expression in CASE statement at %L is "
7725                          "not in the range of %s", &cp->high->where,
7726                          gfc_typename (&case_expr->ts));
7727         }
7728
7729   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7730      of the SELECT CASE expression and its CASE values.  Walk the lists
7731      of case values, and if we find a mismatch, promote case_expr to
7732      the appropriate kind.  */
7733
7734   if (type == BT_LOGICAL || type == BT_INTEGER)
7735     {
7736       for (body = code->block; body; body = body->block)
7737         {
7738           /* Walk the case label list.  */
7739           for (cp = body->ext.block.case_list; cp; cp = cp->next)
7740             {
7741               /* Intercept the DEFAULT case.  It does not have a kind.  */
7742               if (cp->low == NULL && cp->high == NULL)
7743                 continue;
7744
7745               /* Unreachable case ranges are discarded, so ignore.  */
7746               if (cp->low != NULL && cp->high != NULL
7747                   && cp->low != cp->high
7748                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7749                 continue;
7750
7751               if (cp->low != NULL
7752                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7753                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7754
7755               if (cp->high != NULL
7756                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7757                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7758             }
7759          }
7760     }
7761
7762   /* Assume there is no DEFAULT case.  */
7763   default_case = NULL;
7764   head = tail = NULL;
7765   ncases = 0;
7766   seen_logical = 0;
7767
7768   for (body = code->block; body; body = body->block)
7769     {
7770       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7771       t = SUCCESS;
7772       seen_unreachable = 0;
7773
7774       /* Walk the case label list, making sure that all case labels
7775          are legal.  */
7776       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7777         {
7778           /* Count the number of cases in the whole construct.  */
7779           ncases++;
7780
7781           /* Intercept the DEFAULT case.  */
7782           if (cp->low == NULL && cp->high == NULL)
7783             {
7784               if (default_case != NULL)
7785                 {
7786                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7787                              "by a second DEFAULT CASE at %L",
7788                              &default_case->where, &cp->where);
7789                   t = FAILURE;
7790                   break;
7791                 }
7792               else
7793                 {
7794                   default_case = cp;
7795                   continue;
7796                 }
7797             }
7798
7799           /* Deal with single value cases and case ranges.  Errors are
7800              issued from the validation function.  */
7801           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7802               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7803             {
7804               t = FAILURE;
7805               break;
7806             }
7807
7808           if (type == BT_LOGICAL
7809               && ((cp->low == NULL || cp->high == NULL)
7810                   || cp->low != cp->high))
7811             {
7812               gfc_error ("Logical range in CASE statement at %L is not "
7813                          "allowed", &cp->low->where);
7814               t = FAILURE;
7815               break;
7816             }
7817
7818           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7819             {
7820               int value;
7821               value = cp->low->value.logical == 0 ? 2 : 1;
7822               if (value & seen_logical)
7823                 {
7824                   gfc_error ("Constant logical value in CASE statement "
7825                              "is repeated at %L",
7826                              &cp->low->where);
7827                   t = FAILURE;
7828                   break;
7829                 }
7830               seen_logical |= value;
7831             }
7832
7833           if (cp->low != NULL && cp->high != NULL
7834               && cp->low != cp->high
7835               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7836             {
7837               if (gfc_option.warn_surprising)
7838                 gfc_warning ("Range specification at %L can never "
7839                              "be matched", &cp->where);
7840
7841               cp->unreachable = 1;
7842               seen_unreachable = 1;
7843             }
7844           else
7845             {
7846               /* If the case range can be matched, it can also overlap with
7847                  other cases.  To make sure it does not, we put it in a
7848                  double linked list here.  We sort that with a merge sort
7849                  later on to detect any overlapping cases.  */
7850               if (!head)
7851                 {
7852                   head = tail = cp;
7853                   head->right = head->left = NULL;
7854                 }
7855               else
7856                 {
7857                   tail->right = cp;
7858                   tail->right->left = tail;
7859                   tail = tail->right;
7860                   tail->right = NULL;
7861                 }
7862             }
7863         }
7864
7865       /* It there was a failure in the previous case label, give up
7866          for this case label list.  Continue with the next block.  */
7867       if (t == FAILURE)
7868         continue;
7869
7870       /* See if any case labels that are unreachable have been seen.
7871          If so, we eliminate them.  This is a bit of a kludge because
7872          the case lists for a single case statement (label) is a
7873          single forward linked lists.  */
7874       if (seen_unreachable)
7875       {
7876         /* Advance until the first case in the list is reachable.  */
7877         while (body->ext.block.case_list != NULL
7878                && body->ext.block.case_list->unreachable)
7879           {
7880             gfc_case *n = body->ext.block.case_list;
7881             body->ext.block.case_list = body->ext.block.case_list->next;
7882             n->next = NULL;
7883             gfc_free_case_list (n);
7884           }
7885
7886         /* Strip all other unreachable cases.  */
7887         if (body->ext.block.case_list)
7888           {
7889             for (cp = body->ext.block.case_list; cp->next; cp = cp->next)
7890               {
7891                 if (cp->next->unreachable)
7892                   {
7893                     gfc_case *n = cp->next;
7894                     cp->next = cp->next->next;
7895                     n->next = NULL;
7896                     gfc_free_case_list (n);
7897                   }
7898               }
7899           }
7900       }
7901     }
7902
7903   /* See if there were overlapping cases.  If the check returns NULL,
7904      there was overlap.  In that case we don't do anything.  If head
7905      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7906      then used during code generation for SELECT CASE constructs with
7907      a case expression of a CHARACTER type.  */
7908   if (head)
7909     {
7910       head = check_case_overlap (head);
7911
7912       /* Prepend the default_case if it is there.  */
7913       if (head != NULL && default_case)
7914         {
7915           default_case->left = NULL;
7916           default_case->right = head;
7917           head->left = default_case;
7918         }
7919     }
7920
7921   /* Eliminate dead blocks that may be the result if we've seen
7922      unreachable case labels for a block.  */
7923   for (body = code; body && body->block; body = body->block)
7924     {
7925       if (body->block->ext.block.case_list == NULL)
7926         {
7927           /* Cut the unreachable block from the code chain.  */
7928           gfc_code *c = body->block;
7929           body->block = c->block;
7930
7931           /* Kill the dead block, but not the blocks below it.  */
7932           c->block = NULL;
7933           gfc_free_statements (c);
7934         }
7935     }
7936
7937   /* More than two cases is legal but insane for logical selects.
7938      Issue a warning for it.  */
7939   if (gfc_option.warn_surprising && type == BT_LOGICAL
7940       && ncases > 2)
7941     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7942                  &code->loc);
7943 }
7944
7945
7946 /* Check if a derived type is extensible.  */
7947
7948 bool
7949 gfc_type_is_extensible (gfc_symbol *sym)
7950 {
7951   return !(sym->attr.is_bind_c || sym->attr.sequence);
7952 }
7953
7954
7955 /* Resolve an associate-name:  Resolve target and ensure the type-spec is
7956    correct as well as possibly the array-spec.  */
7957
7958 static void
7959 resolve_assoc_var (gfc_symbol* sym, bool resolve_target)
7960 {
7961   gfc_expr* target;
7962
7963   gcc_assert (sym->assoc);
7964   gcc_assert (sym->attr.flavor == FL_VARIABLE);
7965
7966   /* If this is for SELECT TYPE, the target may not yet be set.  In that
7967      case, return.  Resolution will be called later manually again when
7968      this is done.  */
7969   target = sym->assoc->target;
7970   if (!target)
7971     return;
7972   gcc_assert (!sym->assoc->dangling);
7973
7974   if (resolve_target && gfc_resolve_expr (target) != SUCCESS)
7975     return;
7976
7977   /* For variable targets, we get some attributes from the target.  */
7978   if (target->expr_type == EXPR_VARIABLE)
7979     {
7980       gfc_symbol* tsym;
7981
7982       gcc_assert (target->symtree);
7983       tsym = target->symtree->n.sym;
7984
7985       sym->attr.asynchronous = tsym->attr.asynchronous;
7986       sym->attr.volatile_ = tsym->attr.volatile_;
7987
7988       sym->attr.target = tsym->attr.target
7989                          || gfc_expr_attr (target).pointer;
7990     }
7991
7992   /* Get type if this was not already set.  Note that it can be
7993      some other type than the target in case this is a SELECT TYPE
7994      selector!  So we must not update when the type is already there.  */
7995   if (sym->ts.type == BT_UNKNOWN)
7996     sym->ts = target->ts;
7997   gcc_assert (sym->ts.type != BT_UNKNOWN);
7998
7999   /* See if this is a valid association-to-variable.  */
8000   sym->assoc->variable = (target->expr_type == EXPR_VARIABLE
8001                           && !gfc_has_vector_subscript (target));
8002
8003   /* Finally resolve if this is an array or not.  */
8004   if (sym->attr.dimension && target->rank == 0)
8005     {
8006       gfc_error ("Associate-name '%s' at %L is used as array",
8007                  sym->name, &sym->declared_at);
8008       sym->attr.dimension = 0;
8009       return;
8010     }
8011
8012   /* We cannot deal with class selectors that need temporaries.  */
8013   if (target->ts.type == BT_CLASS
8014         && gfc_ref_needs_temporary_p (target->ref))
8015     {
8016       gfc_error ("CLASS selector at %L needs a temporary which is not "
8017                  "yet implemented", &target->where);
8018       return;
8019     }
8020
8021   if (target->ts.type != BT_CLASS && target->rank > 0)
8022     sym->attr.dimension = 1;
8023   else if (target->ts.type == BT_CLASS)
8024     gfc_fix_class_refs (target);
8025
8026   /* The associate-name will have a correct type by now. Make absolutely
8027      sure that it has not picked up a dimension attribute.  */
8028   if (sym->ts.type == BT_CLASS)
8029     sym->attr.dimension = 0;
8030
8031   if (sym->attr.dimension)
8032     {
8033       sym->as = gfc_get_array_spec ();
8034       sym->as->rank = target->rank;
8035       sym->as->type = AS_DEFERRED;
8036
8037       /* Target must not be coindexed, thus the associate-variable
8038          has no corank.  */
8039       sym->as->corank = 0;
8040     }
8041 }
8042
8043
8044 /* Resolve a SELECT TYPE statement.  */
8045
8046 static void
8047 resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
8048 {
8049   gfc_symbol *selector_type;
8050   gfc_code *body, *new_st, *if_st, *tail;
8051   gfc_code *class_is = NULL, *default_case = NULL;
8052   gfc_case *c;
8053   gfc_symtree *st;
8054   char name[GFC_MAX_SYMBOL_LEN];
8055   gfc_namespace *ns;
8056   int error = 0;
8057
8058   ns = code->ext.block.ns;
8059   gfc_resolve (ns);
8060
8061   /* Check for F03:C813.  */
8062   if (code->expr1->ts.type != BT_CLASS
8063       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
8064     {
8065       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
8066                  "at %L", &code->loc);
8067       return;
8068     }
8069
8070   if (!code->expr1->symtree->n.sym->attr.class_ok)
8071     return;
8072
8073   if (code->expr2)
8074     {
8075       if (code->expr1->symtree->n.sym->attr.untyped)
8076         code->expr1->symtree->n.sym->ts = code->expr2->ts;
8077       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
8078     }
8079   else
8080     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
8081
8082   /* Loop over TYPE IS / CLASS IS cases.  */
8083   for (body = code->block; body; body = body->block)
8084     {
8085       c = body->ext.block.case_list;
8086
8087       /* Check F03:C815.  */
8088       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
8089           && !gfc_type_is_extensible (c->ts.u.derived))
8090         {
8091           gfc_error ("Derived type '%s' at %L must be extensible",
8092                      c->ts.u.derived->name, &c->where);
8093           error++;
8094           continue;
8095         }
8096
8097       /* Check F03:C816.  */
8098       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
8099           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
8100         {
8101           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
8102                      c->ts.u.derived->name, &c->where, selector_type->name);
8103           error++;
8104           continue;
8105         }
8106
8107       /* Intercept the DEFAULT case.  */
8108       if (c->ts.type == BT_UNKNOWN)
8109         {
8110           /* Check F03:C818.  */
8111           if (default_case)
8112             {
8113               gfc_error ("The DEFAULT CASE at %L cannot be followed "
8114                          "by a second DEFAULT CASE at %L",
8115                          &default_case->ext.block.case_list->where, &c->where);
8116               error++;
8117               continue;
8118             }
8119
8120           default_case = body;
8121         }
8122     }
8123     
8124   if (error > 0)
8125     return;
8126
8127   /* Transform SELECT TYPE statement to BLOCK and associate selector to
8128      target if present.  If there are any EXIT statements referring to the
8129      SELECT TYPE construct, this is no problem because the gfc_code
8130      reference stays the same and EXIT is equally possible from the BLOCK
8131      it is changed to.  */
8132   code->op = EXEC_BLOCK;
8133   if (code->expr2)
8134     {
8135       gfc_association_list* assoc;
8136
8137       assoc = gfc_get_association_list ();
8138       assoc->st = code->expr1->symtree;
8139       assoc->target = gfc_copy_expr (code->expr2);
8140       assoc->target->where = code->expr2->where;
8141       /* assoc->variable will be set by resolve_assoc_var.  */
8142       
8143       code->ext.block.assoc = assoc;
8144       code->expr1->symtree->n.sym->assoc = assoc;
8145
8146       resolve_assoc_var (code->expr1->symtree->n.sym, false);
8147     }
8148   else
8149     code->ext.block.assoc = NULL;
8150
8151   /* Add EXEC_SELECT to switch on type.  */
8152   new_st = gfc_get_code ();
8153   new_st->op = code->op;
8154   new_st->expr1 = code->expr1;
8155   new_st->expr2 = code->expr2;
8156   new_st->block = code->block;
8157   code->expr1 = code->expr2 =  NULL;
8158   code->block = NULL;
8159   if (!ns->code)
8160     ns->code = new_st;
8161   else
8162     ns->code->next = new_st;
8163   code = new_st;
8164   code->op = EXEC_SELECT;
8165   gfc_add_vptr_component (code->expr1);
8166   gfc_add_hash_component (code->expr1);
8167
8168   /* Loop over TYPE IS / CLASS IS cases.  */
8169   for (body = code->block; body; body = body->block)
8170     {
8171       c = body->ext.block.case_list;
8172
8173       if (c->ts.type == BT_DERIVED)
8174         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
8175                                              c->ts.u.derived->hash_value);
8176
8177       else if (c->ts.type == BT_UNKNOWN)
8178         continue;
8179
8180       /* Associate temporary to selector.  This should only be done
8181          when this case is actually true, so build a new ASSOCIATE
8182          that does precisely this here (instead of using the
8183          'global' one).  */
8184
8185       if (c->ts.type == BT_CLASS)
8186         sprintf (name, "__tmp_class_%s", c->ts.u.derived->name);
8187       else
8188         sprintf (name, "__tmp_type_%s", c->ts.u.derived->name);
8189       st = gfc_find_symtree (ns->sym_root, name);
8190       gcc_assert (st->n.sym->assoc);
8191       st->n.sym->assoc->target = gfc_get_variable_expr (code->expr1->symtree);
8192       st->n.sym->assoc->target->where = code->expr1->where;
8193       if (c->ts.type == BT_DERIVED)
8194         gfc_add_data_component (st->n.sym->assoc->target);
8195
8196       new_st = gfc_get_code ();
8197       new_st->op = EXEC_BLOCK;
8198       new_st->ext.block.ns = gfc_build_block_ns (ns);
8199       new_st->ext.block.ns->code = body->next;
8200       body->next = new_st;
8201
8202       /* Chain in the new list only if it is marked as dangling.  Otherwise
8203          there is a CASE label overlap and this is already used.  Just ignore,
8204          the error is diagnosed elsewhere.  */
8205       if (st->n.sym->assoc->dangling)
8206         {
8207           new_st->ext.block.assoc = st->n.sym->assoc;
8208           st->n.sym->assoc->dangling = 0;
8209         }
8210
8211       resolve_assoc_var (st->n.sym, false);
8212     }
8213     
8214   /* Take out CLASS IS cases for separate treatment.  */
8215   body = code;
8216   while (body && body->block)
8217     {
8218       if (body->block->ext.block.case_list->ts.type == BT_CLASS)
8219         {
8220           /* Add to class_is list.  */
8221           if (class_is == NULL)
8222             { 
8223               class_is = body->block;
8224               tail = class_is;
8225             }
8226           else
8227             {
8228               for (tail = class_is; tail->block; tail = tail->block) ;
8229               tail->block = body->block;
8230               tail = tail->block;
8231             }
8232           /* Remove from EXEC_SELECT list.  */
8233           body->block = body->block->block;
8234           tail->block = NULL;
8235         }
8236       else
8237         body = body->block;
8238     }
8239
8240   if (class_is)
8241     {
8242       gfc_symbol *vtab;
8243       
8244       if (!default_case)
8245         {
8246           /* Add a default case to hold the CLASS IS cases.  */
8247           for (tail = code; tail->block; tail = tail->block) ;
8248           tail->block = gfc_get_code ();
8249           tail = tail->block;
8250           tail->op = EXEC_SELECT_TYPE;
8251           tail->ext.block.case_list = gfc_get_case ();
8252           tail->ext.block.case_list->ts.type = BT_UNKNOWN;
8253           tail->next = NULL;
8254           default_case = tail;
8255         }
8256
8257       /* More than one CLASS IS block?  */
8258       if (class_is->block)
8259         {
8260           gfc_code **c1,*c2;
8261           bool swapped;
8262           /* Sort CLASS IS blocks by extension level.  */
8263           do
8264             {
8265               swapped = false;
8266               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
8267                 {
8268                   c2 = (*c1)->block;
8269                   /* F03:C817 (check for doubles).  */
8270                   if ((*c1)->ext.block.case_list->ts.u.derived->hash_value
8271                       == c2->ext.block.case_list->ts.u.derived->hash_value)
8272                     {
8273                       gfc_error ("Double CLASS IS block in SELECT TYPE "
8274                                  "statement at %L",
8275                                  &c2->ext.block.case_list->where);
8276                       return;
8277                     }
8278                   if ((*c1)->ext.block.case_list->ts.u.derived->attr.extension
8279                       < c2->ext.block.case_list->ts.u.derived->attr.extension)
8280                     {
8281                       /* Swap.  */
8282                       (*c1)->block = c2->block;
8283                       c2->block = *c1;
8284                       *c1 = c2;
8285                       swapped = true;
8286                     }
8287                 }
8288             }
8289           while (swapped);
8290         }
8291         
8292       /* Generate IF chain.  */
8293       if_st = gfc_get_code ();
8294       if_st->op = EXEC_IF;
8295       new_st = if_st;
8296       for (body = class_is; body; body = body->block)
8297         {
8298           new_st->block = gfc_get_code ();
8299           new_st = new_st->block;
8300           new_st->op = EXEC_IF;
8301           /* Set up IF condition: Call _gfortran_is_extension_of.  */
8302           new_st->expr1 = gfc_get_expr ();
8303           new_st->expr1->expr_type = EXPR_FUNCTION;
8304           new_st->expr1->ts.type = BT_LOGICAL;
8305           new_st->expr1->ts.kind = 4;
8306           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
8307           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
8308           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
8309           /* Set up arguments.  */
8310           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
8311           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
8312           new_st->expr1->value.function.actual->expr->where = code->loc;
8313           gfc_add_vptr_component (new_st->expr1->value.function.actual->expr);
8314           vtab = gfc_find_derived_vtab (body->ext.block.case_list->ts.u.derived);
8315           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
8316           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
8317           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
8318           new_st->next = body->next;
8319         }
8320         if (default_case->next)
8321           {
8322             new_st->block = gfc_get_code ();
8323             new_st = new_st->block;
8324             new_st->op = EXEC_IF;
8325             new_st->next = default_case->next;
8326           }
8327           
8328         /* Replace CLASS DEFAULT code by the IF chain.  */
8329         default_case->next = if_st;
8330     }
8331
8332   /* Resolve the internal code.  This can not be done earlier because
8333      it requires that the sym->assoc of selectors is set already.  */
8334   gfc_current_ns = ns;
8335   gfc_resolve_blocks (code->block, gfc_current_ns);
8336   gfc_current_ns = old_ns;
8337
8338   resolve_select (code);
8339 }
8340
8341
8342 /* Resolve a transfer statement. This is making sure that:
8343    -- a derived type being transferred has only non-pointer components
8344    -- a derived type being transferred doesn't have private components, unless 
8345       it's being transferred from the module where the type was defined
8346    -- we're not trying to transfer a whole assumed size array.  */
8347
8348 static void
8349 resolve_transfer (gfc_code *code)
8350 {
8351   gfc_typespec *ts;
8352   gfc_symbol *sym;
8353   gfc_ref *ref;
8354   gfc_expr *exp;
8355
8356   exp = code->expr1;
8357
8358   while (exp != NULL && exp->expr_type == EXPR_OP
8359          && exp->value.op.op == INTRINSIC_PARENTHESES)
8360     exp = exp->value.op.op1;
8361
8362   if (exp && exp->expr_type == EXPR_NULL && exp->ts.type == BT_UNKNOWN)
8363     {
8364       gfc_error ("NULL intrinsic at %L in data transfer statement requires "
8365                  "MOLD=", &exp->where);
8366       return;
8367     }
8368
8369   if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
8370                       && exp->expr_type != EXPR_FUNCTION))
8371     return;
8372
8373   /* If we are reading, the variable will be changed.  Note that
8374      code->ext.dt may be NULL if the TRANSFER is related to
8375      an INQUIRE statement -- but in this case, we are not reading, either.  */
8376   if (code->ext.dt && code->ext.dt->dt_io_kind->value.iokind == M_READ
8377       && gfc_check_vardef_context (exp, false, false, _("item in READ"))
8378          == FAILURE)
8379     return;
8380
8381   sym = exp->symtree->n.sym;
8382   ts = &sym->ts;
8383
8384   /* Go to actual component transferred.  */
8385   for (ref = exp->ref; ref; ref = ref->next)
8386     if (ref->type == REF_COMPONENT)
8387       ts = &ref->u.c.component->ts;
8388
8389   if (ts->type == BT_CLASS)
8390     {
8391       /* FIXME: Test for defined input/output.  */
8392       gfc_error ("Data transfer element at %L cannot be polymorphic unless "
8393                 "it is processed by a defined input/output procedure",
8394                 &code->loc);
8395       return;
8396     }
8397
8398   if (ts->type == BT_DERIVED)
8399     {
8400       /* Check that transferred derived type doesn't contain POINTER
8401          components.  */
8402       if (ts->u.derived->attr.pointer_comp)
8403         {
8404           gfc_error ("Data transfer element at %L cannot have POINTER "
8405                      "components unless it is processed by a defined "
8406                      "input/output procedure", &code->loc);
8407           return;
8408         }
8409
8410       /* F08:C935.  */
8411       if (ts->u.derived->attr.proc_pointer_comp)
8412         {
8413           gfc_error ("Data transfer element at %L cannot have "
8414                      "procedure pointer components", &code->loc);
8415           return;
8416         }
8417
8418       if (ts->u.derived->attr.alloc_comp)
8419         {
8420           gfc_error ("Data transfer element at %L cannot have ALLOCATABLE "
8421                      "components unless it is processed by a defined "
8422                      "input/output procedure", &code->loc);
8423           return;
8424         }
8425
8426       if (derived_inaccessible (ts->u.derived))
8427         {
8428           gfc_error ("Data transfer element at %L cannot have "
8429                      "PRIVATE components",&code->loc);
8430           return;
8431         }
8432     }
8433
8434   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE && exp->ref
8435       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
8436     {
8437       gfc_error ("Data transfer element at %L cannot be a full reference to "
8438                  "an assumed-size array", &code->loc);
8439       return;
8440     }
8441 }
8442
8443
8444 /*********** Toplevel code resolution subroutines ***********/
8445
8446 /* Find the set of labels that are reachable from this block.  We also
8447    record the last statement in each block.  */
8448      
8449 static void
8450 find_reachable_labels (gfc_code *block)
8451 {
8452   gfc_code *c;
8453
8454   if (!block)
8455     return;
8456
8457   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
8458
8459   /* Collect labels in this block.  We don't keep those corresponding
8460      to END {IF|SELECT}, these are checked in resolve_branch by going
8461      up through the code_stack.  */
8462   for (c = block; c; c = c->next)
8463     {
8464       if (c->here && c->op != EXEC_END_NESTED_BLOCK)
8465         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
8466     }
8467
8468   /* Merge with labels from parent block.  */
8469   if (cs_base->prev)
8470     {
8471       gcc_assert (cs_base->prev->reachable_labels);
8472       bitmap_ior_into (cs_base->reachable_labels,
8473                        cs_base->prev->reachable_labels);
8474     }
8475 }
8476
8477
8478 static void
8479 resolve_lock_unlock (gfc_code *code)
8480 {
8481   if (code->expr1->ts.type != BT_DERIVED
8482       || code->expr1->expr_type != EXPR_VARIABLE
8483       || code->expr1->ts.u.derived->from_intmod != INTMOD_ISO_FORTRAN_ENV
8484       || code->expr1->ts.u.derived->intmod_sym_id != ISOFORTRAN_LOCK_TYPE
8485       || code->expr1->rank != 0
8486       || (!gfc_is_coarray (code->expr1) && !gfc_is_coindexed (code->expr1)))
8487     gfc_error ("Lock variable at %L must be a scalar of type LOCK_TYPE",
8488                &code->expr1->where);
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   if (code->expr2
8498       && gfc_check_vardef_context (code->expr2, false, false,
8499                                    _("STAT variable")) == FAILURE)
8500     return;
8501
8502   /* Check ERRMSG.  */
8503   if (code->expr3
8504       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8505           || code->expr3->expr_type != EXPR_VARIABLE))
8506     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8507                &code->expr3->where);
8508
8509   if (code->expr3
8510       && gfc_check_vardef_context (code->expr3, false, false,
8511                                    _("ERRMSG variable")) == FAILURE)
8512     return;
8513
8514   /* Check ACQUIRED_LOCK.  */
8515   if (code->expr4
8516       && (code->expr4->ts.type != BT_LOGICAL || code->expr4->rank != 0
8517           || code->expr4->expr_type != EXPR_VARIABLE))
8518     gfc_error ("ACQUIRED_LOCK= argument at %L must be a scalar LOGICAL "
8519                "variable", &code->expr4->where);
8520
8521   if (code->expr4
8522       && gfc_check_vardef_context (code->expr4, false, false,
8523                                    _("ACQUIRED_LOCK variable")) == FAILURE)
8524     return;
8525 }
8526
8527
8528 static void
8529 resolve_sync (gfc_code *code)
8530 {
8531   /* Check imageset. The * case matches expr1 == NULL.  */
8532   if (code->expr1)
8533     {
8534       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
8535         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
8536                    "INTEGER expression", &code->expr1->where);
8537       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
8538           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
8539         gfc_error ("Imageset argument at %L must between 1 and num_images()",
8540                    &code->expr1->where);
8541       else if (code->expr1->expr_type == EXPR_ARRAY
8542                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
8543         {
8544            gfc_constructor *cons;
8545            cons = gfc_constructor_first (code->expr1->value.constructor);
8546            for (; cons; cons = gfc_constructor_next (cons))
8547              if (cons->expr->expr_type == EXPR_CONSTANT
8548                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
8549                gfc_error ("Imageset argument at %L must between 1 and "
8550                           "num_images()", &cons->expr->where);
8551         }
8552     }
8553
8554   /* Check STAT.  */
8555   if (code->expr2
8556       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8557           || code->expr2->expr_type != EXPR_VARIABLE))
8558     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8559                &code->expr2->where);
8560
8561   /* Check ERRMSG.  */
8562   if (code->expr3
8563       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8564           || code->expr3->expr_type != EXPR_VARIABLE))
8565     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8566                &code->expr3->where);
8567 }
8568
8569
8570 /* Given a branch to a label, see if the branch is conforming.
8571    The code node describes where the branch is located.  */
8572
8573 static void
8574 resolve_branch (gfc_st_label *label, gfc_code *code)
8575 {
8576   code_stack *stack;
8577
8578   if (label == NULL)
8579     return;
8580
8581   /* Step one: is this a valid branching target?  */
8582
8583   if (label->defined == ST_LABEL_UNKNOWN)
8584     {
8585       gfc_error ("Label %d referenced at %L is never defined", label->value,
8586                  &label->where);
8587       return;
8588     }
8589
8590   if (label->defined != ST_LABEL_TARGET)
8591     {
8592       gfc_error ("Statement at %L is not a valid branch target statement "
8593                  "for the branch statement at %L", &label->where, &code->loc);
8594       return;
8595     }
8596
8597   /* Step two: make sure this branch is not a branch to itself ;-)  */
8598
8599   if (code->here == label)
8600     {
8601       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
8602       return;
8603     }
8604
8605   /* Step three:  See if the label is in the same block as the
8606      branching statement.  The hard work has been done by setting up
8607      the bitmap reachable_labels.  */
8608
8609   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8610     {
8611       /* Check now whether there is a CRITICAL construct; if so, check
8612          whether the label is still visible outside of the CRITICAL block,
8613          which is invalid.  */
8614       for (stack = cs_base; stack; stack = stack->prev)
8615         {
8616           if (stack->current->op == EXEC_CRITICAL
8617               && bitmap_bit_p (stack->reachable_labels, label->value))
8618             gfc_error ("GOTO statement at %L leaves CRITICAL construct for "
8619                       "label at %L", &code->loc, &label->where);
8620           else if (stack->current->op == EXEC_DO_CONCURRENT
8621                    && bitmap_bit_p (stack->reachable_labels, label->value))
8622             gfc_error ("GOTO statement at %L leaves DO CONCURRENT construct "
8623                       "for label at %L", &code->loc, &label->where);
8624         }
8625
8626       return;
8627     }
8628
8629   /* Step four:  If we haven't found the label in the bitmap, it may
8630     still be the label of the END of the enclosing block, in which
8631     case we find it by going up the code_stack.  */
8632
8633   for (stack = cs_base; stack; stack = stack->prev)
8634     {
8635       if (stack->current->next && stack->current->next->here == label)
8636         break;
8637       if (stack->current->op == EXEC_CRITICAL)
8638         {
8639           /* Note: A label at END CRITICAL does not leave the CRITICAL
8640              construct as END CRITICAL is still part of it.  */
8641           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8642                       " at %L", &code->loc, &label->where);
8643           return;
8644         }
8645       else if (stack->current->op == EXEC_DO_CONCURRENT)
8646         {
8647           gfc_error ("GOTO statement at %L leaves DO CONCURRENT construct for "
8648                      "label at %L", &code->loc, &label->where);
8649           return;
8650         }
8651     }
8652
8653   if (stack)
8654     {
8655       gcc_assert (stack->current->next->op == EXEC_END_NESTED_BLOCK);
8656       return;
8657     }
8658
8659   /* The label is not in an enclosing block, so illegal.  This was
8660      allowed in Fortran 66, so we allow it as extension.  No
8661      further checks are necessary in this case.  */
8662   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
8663                   "as the GOTO statement at %L", &label->where,
8664                   &code->loc);
8665   return;
8666 }
8667
8668
8669 /* Check whether EXPR1 has the same shape as EXPR2.  */
8670
8671 static gfc_try
8672 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8673 {
8674   mpz_t shape[GFC_MAX_DIMENSIONS];
8675   mpz_t shape2[GFC_MAX_DIMENSIONS];
8676   gfc_try result = FAILURE;
8677   int i;
8678
8679   /* Compare the rank.  */
8680   if (expr1->rank != expr2->rank)
8681     return result;
8682
8683   /* Compare the size of each dimension.  */
8684   for (i=0; i<expr1->rank; i++)
8685     {
8686       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
8687         goto ignore;
8688
8689       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
8690         goto ignore;
8691
8692       if (mpz_cmp (shape[i], shape2[i]))
8693         goto over;
8694     }
8695
8696   /* When either of the two expression is an assumed size array, we
8697      ignore the comparison of dimension sizes.  */
8698 ignore:
8699   result = SUCCESS;
8700
8701 over:
8702   gfc_clear_shape (shape, i);
8703   gfc_clear_shape (shape2, i);
8704   return result;
8705 }
8706
8707
8708 /* Check whether a WHERE assignment target or a WHERE mask expression
8709    has the same shape as the outmost WHERE mask expression.  */
8710
8711 static void
8712 resolve_where (gfc_code *code, gfc_expr *mask)
8713 {
8714   gfc_code *cblock;
8715   gfc_code *cnext;
8716   gfc_expr *e = NULL;
8717
8718   cblock = code->block;
8719
8720   /* Store the first WHERE mask-expr of the WHERE statement or construct.
8721      In case of nested WHERE, only the outmost one is stored.  */
8722   if (mask == NULL) /* outmost WHERE */
8723     e = cblock->expr1;
8724   else /* inner WHERE */
8725     e = mask;
8726
8727   while (cblock)
8728     {
8729       if (cblock->expr1)
8730         {
8731           /* Check if the mask-expr has a consistent shape with the
8732              outmost WHERE mask-expr.  */
8733           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
8734             gfc_error ("WHERE mask at %L has inconsistent shape",
8735                        &cblock->expr1->where);
8736          }
8737
8738       /* the assignment statement of a WHERE statement, or the first
8739          statement in where-body-construct of a WHERE construct */
8740       cnext = cblock->next;
8741       while (cnext)
8742         {
8743           switch (cnext->op)
8744             {
8745             /* WHERE assignment statement */
8746             case EXEC_ASSIGN:
8747
8748               /* Check shape consistent for WHERE assignment target.  */
8749               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
8750                gfc_error ("WHERE assignment target at %L has "
8751                           "inconsistent shape", &cnext->expr1->where);
8752               break;
8753
8754   
8755             case EXEC_ASSIGN_CALL:
8756               resolve_call (cnext);
8757               if (!cnext->resolved_sym->attr.elemental)
8758                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8759                           &cnext->ext.actual->expr->where);
8760               break;
8761
8762             /* WHERE or WHERE construct is part of a where-body-construct */
8763             case EXEC_WHERE:
8764               resolve_where (cnext, e);
8765               break;
8766
8767             default:
8768               gfc_error ("Unsupported statement inside WHERE at %L",
8769                          &cnext->loc);
8770             }
8771          /* the next statement within the same where-body-construct */
8772          cnext = cnext->next;
8773        }
8774     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8775     cblock = cblock->block;
8776   }
8777 }
8778
8779
8780 /* Resolve assignment in FORALL construct.
8781    NVAR is the number of FORALL index variables, and VAR_EXPR records the
8782    FORALL index variables.  */
8783
8784 static void
8785 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8786 {
8787   int n;
8788
8789   for (n = 0; n < nvar; n++)
8790     {
8791       gfc_symbol *forall_index;
8792
8793       forall_index = var_expr[n]->symtree->n.sym;
8794
8795       /* Check whether the assignment target is one of the FORALL index
8796          variable.  */
8797       if ((code->expr1->expr_type == EXPR_VARIABLE)
8798           && (code->expr1->symtree->n.sym == forall_index))
8799         gfc_error ("Assignment to a FORALL index variable at %L",
8800                    &code->expr1->where);
8801       else
8802         {
8803           /* If one of the FORALL index variables doesn't appear in the
8804              assignment variable, then there could be a many-to-one
8805              assignment.  Emit a warning rather than an error because the
8806              mask could be resolving this problem.  */
8807           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
8808             gfc_warning ("The FORALL with index '%s' is not used on the "
8809                          "left side of the assignment at %L and so might "
8810                          "cause multiple assignment to this object",
8811                          var_expr[n]->symtree->name, &code->expr1->where);
8812         }
8813     }
8814 }
8815
8816
8817 /* Resolve WHERE statement in FORALL construct.  */
8818
8819 static void
8820 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
8821                                   gfc_expr **var_expr)
8822 {
8823   gfc_code *cblock;
8824   gfc_code *cnext;
8825
8826   cblock = code->block;
8827   while (cblock)
8828     {
8829       /* the assignment statement of a WHERE statement, or the first
8830          statement in where-body-construct of a WHERE construct */
8831       cnext = cblock->next;
8832       while (cnext)
8833         {
8834           switch (cnext->op)
8835             {
8836             /* WHERE assignment statement */
8837             case EXEC_ASSIGN:
8838               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
8839               break;
8840   
8841             /* WHERE operator assignment statement */
8842             case EXEC_ASSIGN_CALL:
8843               resolve_call (cnext);
8844               if (!cnext->resolved_sym->attr.elemental)
8845                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8846                           &cnext->ext.actual->expr->where);
8847               break;
8848
8849             /* WHERE or WHERE construct is part of a where-body-construct */
8850             case EXEC_WHERE:
8851               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
8852               break;
8853
8854             default:
8855               gfc_error ("Unsupported statement inside WHERE at %L",
8856                          &cnext->loc);
8857             }
8858           /* the next statement within the same where-body-construct */
8859           cnext = cnext->next;
8860         }
8861       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8862       cblock = cblock->block;
8863     }
8864 }
8865
8866
8867 /* Traverse the FORALL body to check whether the following errors exist:
8868    1. For assignment, check if a many-to-one assignment happens.
8869    2. For WHERE statement, check the WHERE body to see if there is any
8870       many-to-one assignment.  */
8871
8872 static void
8873 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
8874 {
8875   gfc_code *c;
8876
8877   c = code->block->next;
8878   while (c)
8879     {
8880       switch (c->op)
8881         {
8882         case EXEC_ASSIGN:
8883         case EXEC_POINTER_ASSIGN:
8884           gfc_resolve_assign_in_forall (c, nvar, var_expr);
8885           break;
8886
8887         case EXEC_ASSIGN_CALL:
8888           resolve_call (c);
8889           break;
8890
8891         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
8892            there is no need to handle it here.  */
8893         case EXEC_FORALL:
8894           break;
8895         case EXEC_WHERE:
8896           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
8897           break;
8898         default:
8899           break;
8900         }
8901       /* The next statement in the FORALL body.  */
8902       c = c->next;
8903     }
8904 }
8905
8906
8907 /* Counts the number of iterators needed inside a forall construct, including
8908    nested forall constructs. This is used to allocate the needed memory 
8909    in gfc_resolve_forall.  */
8910
8911 static int 
8912 gfc_count_forall_iterators (gfc_code *code)
8913 {
8914   int max_iters, sub_iters, current_iters;
8915   gfc_forall_iterator *fa;
8916
8917   gcc_assert(code->op == EXEC_FORALL);
8918   max_iters = 0;
8919   current_iters = 0;
8920
8921   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8922     current_iters ++;
8923   
8924   code = code->block->next;
8925
8926   while (code)
8927     {          
8928       if (code->op == EXEC_FORALL)
8929         {
8930           sub_iters = gfc_count_forall_iterators (code);
8931           if (sub_iters > max_iters)
8932             max_iters = sub_iters;
8933         }
8934       code = code->next;
8935     }
8936
8937   return current_iters + max_iters;
8938 }
8939
8940
8941 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8942    gfc_resolve_forall_body to resolve the FORALL body.  */
8943
8944 static void
8945 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8946 {
8947   static gfc_expr **var_expr;
8948   static int total_var = 0;
8949   static int nvar = 0;
8950   int old_nvar, tmp;
8951   gfc_forall_iterator *fa;
8952   int i;
8953
8954   old_nvar = nvar;
8955
8956   /* Start to resolve a FORALL construct   */
8957   if (forall_save == 0)
8958     {
8959       /* Count the total number of FORALL index in the nested FORALL
8960          construct in order to allocate the VAR_EXPR with proper size.  */
8961       total_var = gfc_count_forall_iterators (code);
8962
8963       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8964       var_expr = XCNEWVEC (gfc_expr *, total_var);
8965     }
8966
8967   /* The information about FORALL iterator, including FORALL index start, end
8968      and stride. The FORALL index can not appear in start, end or stride.  */
8969   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8970     {
8971       /* Check if any outer FORALL index name is the same as the current
8972          one.  */
8973       for (i = 0; i < nvar; i++)
8974         {
8975           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8976             {
8977               gfc_error ("An outer FORALL construct already has an index "
8978                          "with this name %L", &fa->var->where);
8979             }
8980         }
8981
8982       /* Record the current FORALL index.  */
8983       var_expr[nvar] = gfc_copy_expr (fa->var);
8984
8985       nvar++;
8986
8987       /* No memory leak.  */
8988       gcc_assert (nvar <= total_var);
8989     }
8990
8991   /* Resolve the FORALL body.  */
8992   gfc_resolve_forall_body (code, nvar, var_expr);
8993
8994   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8995   gfc_resolve_blocks (code->block, ns);
8996
8997   tmp = nvar;
8998   nvar = old_nvar;
8999   /* Free only the VAR_EXPRs allocated in this frame.  */
9000   for (i = nvar; i < tmp; i++)
9001      gfc_free_expr (var_expr[i]);
9002
9003   if (nvar == 0)
9004     {
9005       /* We are in the outermost FORALL construct.  */
9006       gcc_assert (forall_save == 0);
9007
9008       /* VAR_EXPR is not needed any more.  */
9009       free (var_expr);
9010       total_var = 0;
9011     }
9012 }
9013
9014
9015 /* Resolve a BLOCK construct statement.  */
9016
9017 static void
9018 resolve_block_construct (gfc_code* code)
9019 {
9020   /* Resolve the BLOCK's namespace.  */
9021   gfc_resolve (code->ext.block.ns);
9022
9023   /* For an ASSOCIATE block, the associations (and their targets) are already
9024      resolved during resolve_symbol.  */
9025 }
9026
9027
9028 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
9029    DO code nodes.  */
9030
9031 static void resolve_code (gfc_code *, gfc_namespace *);
9032
9033 void
9034 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
9035 {
9036   gfc_try t;
9037
9038   for (; b; b = b->block)
9039     {
9040       t = gfc_resolve_expr (b->expr1);
9041       if (gfc_resolve_expr (b->expr2) == FAILURE)
9042         t = FAILURE;
9043
9044       switch (b->op)
9045         {
9046         case EXEC_IF:
9047           if (t == SUCCESS && b->expr1 != NULL
9048               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
9049             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9050                        &b->expr1->where);
9051           break;
9052
9053         case EXEC_WHERE:
9054           if (t == SUCCESS
9055               && b->expr1 != NULL
9056               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
9057             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
9058                        &b->expr1->where);
9059           break;
9060
9061         case EXEC_GOTO:
9062           resolve_branch (b->label1, b);
9063           break;
9064
9065         case EXEC_BLOCK:
9066           resolve_block_construct (b);
9067           break;
9068
9069         case EXEC_SELECT:
9070         case EXEC_SELECT_TYPE:
9071         case EXEC_FORALL:
9072         case EXEC_DO:
9073         case EXEC_DO_WHILE:
9074         case EXEC_DO_CONCURRENT:
9075         case EXEC_CRITICAL:
9076         case EXEC_READ:
9077         case EXEC_WRITE:
9078         case EXEC_IOLENGTH:
9079         case EXEC_WAIT:
9080           break;
9081
9082         case EXEC_OMP_ATOMIC:
9083         case EXEC_OMP_CRITICAL:
9084         case EXEC_OMP_DO:
9085         case EXEC_OMP_MASTER:
9086         case EXEC_OMP_ORDERED:
9087         case EXEC_OMP_PARALLEL:
9088         case EXEC_OMP_PARALLEL_DO:
9089         case EXEC_OMP_PARALLEL_SECTIONS:
9090         case EXEC_OMP_PARALLEL_WORKSHARE:
9091         case EXEC_OMP_SECTIONS:
9092         case EXEC_OMP_SINGLE:
9093         case EXEC_OMP_TASK:
9094         case EXEC_OMP_TASKWAIT:
9095         case EXEC_OMP_TASKYIELD:
9096         case EXEC_OMP_WORKSHARE:
9097           break;
9098
9099         default:
9100           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
9101         }
9102
9103       resolve_code (b->next, ns);
9104     }
9105 }
9106
9107
9108 /* Does everything to resolve an ordinary assignment.  Returns true
9109    if this is an interface assignment.  */
9110 static bool
9111 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
9112 {
9113   bool rval = false;
9114   gfc_expr *lhs;
9115   gfc_expr *rhs;
9116   int llen = 0;
9117   int rlen = 0;
9118   int n;
9119   gfc_ref *ref;
9120
9121   if (gfc_extend_assign (code, ns) == SUCCESS)
9122     {
9123       gfc_expr** rhsptr;
9124
9125       if (code->op == EXEC_ASSIGN_CALL)
9126         {
9127           lhs = code->ext.actual->expr;
9128           rhsptr = &code->ext.actual->next->expr;
9129         }
9130       else
9131         {
9132           gfc_actual_arglist* args;
9133           gfc_typebound_proc* tbp;
9134
9135           gcc_assert (code->op == EXEC_COMPCALL);
9136
9137           args = code->expr1->value.compcall.actual;
9138           lhs = args->expr;
9139           rhsptr = &args->next->expr;
9140
9141           tbp = code->expr1->value.compcall.tbp;
9142           gcc_assert (!tbp->is_generic);
9143         }
9144
9145       /* Make a temporary rhs when there is a default initializer
9146          and rhs is the same symbol as the lhs.  */
9147       if ((*rhsptr)->expr_type == EXPR_VARIABLE
9148             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
9149             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
9150             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
9151         *rhsptr = gfc_get_parentheses (*rhsptr);
9152
9153       return true;
9154     }
9155
9156   lhs = code->expr1;
9157   rhs = code->expr2;
9158
9159   if (rhs->is_boz
9160       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
9161                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
9162                          &code->loc) == FAILURE)
9163     return false;
9164
9165   /* Handle the case of a BOZ literal on the RHS.  */
9166   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
9167     {
9168       int rc;
9169       if (gfc_option.warn_surprising)
9170         gfc_warning ("BOZ literal at %L is bitwise transferred "
9171                      "non-integer symbol '%s'", &code->loc,
9172                      lhs->symtree->n.sym->name);
9173
9174       if (!gfc_convert_boz (rhs, &lhs->ts))
9175         return false;
9176       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
9177         {
9178           if (rc == ARITH_UNDERFLOW)
9179             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
9180                        ". This check can be disabled with the option "
9181                        "-fno-range-check", &rhs->where);
9182           else if (rc == ARITH_OVERFLOW)
9183             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
9184                        ". This check can be disabled with the option "
9185                        "-fno-range-check", &rhs->where);
9186           else if (rc == ARITH_NAN)
9187             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
9188                        ". This check can be disabled with the option "
9189                        "-fno-range-check", &rhs->where);
9190           return false;
9191         }
9192     }
9193
9194   if (lhs->ts.type == BT_CHARACTER
9195         && gfc_option.warn_character_truncation)
9196     {
9197       if (lhs->ts.u.cl != NULL
9198             && lhs->ts.u.cl->length != NULL
9199             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9200         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
9201
9202       if (rhs->expr_type == EXPR_CONSTANT)
9203         rlen = rhs->value.character.length;
9204
9205       else if (rhs->ts.u.cl != NULL
9206                  && rhs->ts.u.cl->length != NULL
9207                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9208         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
9209
9210       if (rlen && llen && rlen > llen)
9211         gfc_warning_now ("CHARACTER expression will be truncated "
9212                          "in assignment (%d/%d) at %L",
9213                          llen, rlen, &code->loc);
9214     }
9215
9216   /* Ensure that a vector index expression for the lvalue is evaluated
9217      to a temporary if the lvalue symbol is referenced in it.  */
9218   if (lhs->rank)
9219     {
9220       for (ref = lhs->ref; ref; ref= ref->next)
9221         if (ref->type == REF_ARRAY)
9222           {
9223             for (n = 0; n < ref->u.ar.dimen; n++)
9224               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
9225                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
9226                                            ref->u.ar.start[n]))
9227                 ref->u.ar.start[n]
9228                         = gfc_get_parentheses (ref->u.ar.start[n]);
9229           }
9230     }
9231
9232   if (gfc_pure (NULL))
9233     {
9234       if (lhs->ts.type == BT_DERIVED
9235             && lhs->expr_type == EXPR_VARIABLE
9236             && lhs->ts.u.derived->attr.pointer_comp
9237             && rhs->expr_type == EXPR_VARIABLE
9238             && (gfc_impure_variable (rhs->symtree->n.sym)
9239                 || gfc_is_coindexed (rhs)))
9240         {
9241           /* F2008, C1283.  */
9242           if (gfc_is_coindexed (rhs))
9243             gfc_error ("Coindexed expression at %L is assigned to "
9244                         "a derived type variable with a POINTER "
9245                         "component in a PURE procedure",
9246                         &rhs->where);
9247           else
9248             gfc_error ("The impure variable at %L is assigned to "
9249                         "a derived type variable with a POINTER "
9250                         "component in a PURE procedure (12.6)",
9251                         &rhs->where);
9252           return rval;
9253         }
9254
9255       /* Fortran 2008, C1283.  */
9256       if (gfc_is_coindexed (lhs))
9257         {
9258           gfc_error ("Assignment to coindexed variable at %L in a PURE "
9259                      "procedure", &rhs->where);
9260           return rval;
9261         }
9262     }
9263
9264   if (gfc_implicit_pure (NULL))
9265     {
9266       if (lhs->expr_type == EXPR_VARIABLE
9267             && lhs->symtree->n.sym != gfc_current_ns->proc_name
9268             && lhs->symtree->n.sym->ns != gfc_current_ns)
9269         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9270
9271       if (lhs->ts.type == BT_DERIVED
9272             && lhs->expr_type == EXPR_VARIABLE
9273             && lhs->ts.u.derived->attr.pointer_comp
9274             && rhs->expr_type == EXPR_VARIABLE
9275             && (gfc_impure_variable (rhs->symtree->n.sym)
9276                 || gfc_is_coindexed (rhs)))
9277         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9278
9279       /* Fortran 2008, C1283.  */
9280       if (gfc_is_coindexed (lhs))
9281         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9282     }
9283
9284   /* F03:7.4.1.2.  */
9285   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
9286      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
9287   if (lhs->ts.type == BT_CLASS)
9288     {
9289       gfc_error ("Variable must not be polymorphic in intrinsic assignment at "
9290                  "%L - check that there is a matching specific subroutine "
9291                  "for '=' operator", &lhs->where);
9292       return false;
9293     }
9294
9295   /* F2008, Section 7.2.1.2.  */
9296   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
9297     {
9298       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
9299                  "component in assignment at %L", &lhs->where);
9300       return false;
9301     }
9302
9303   gfc_check_assign (lhs, rhs, 1);
9304   return false;
9305 }
9306
9307
9308 /* Given a block of code, recursively resolve everything pointed to by this
9309    code block.  */
9310
9311 static void
9312 resolve_code (gfc_code *code, gfc_namespace *ns)
9313 {
9314   int omp_workshare_save;
9315   int forall_save, do_concurrent_save;
9316   code_stack frame;
9317   gfc_try t;
9318
9319   frame.prev = cs_base;
9320   frame.head = code;
9321   cs_base = &frame;
9322
9323   find_reachable_labels (code);
9324
9325   for (; code; code = code->next)
9326     {
9327       frame.current = code;
9328       forall_save = forall_flag;
9329       do_concurrent_save = do_concurrent_flag;
9330
9331       if (code->op == EXEC_FORALL)
9332         {
9333           forall_flag = 1;
9334           gfc_resolve_forall (code, ns, forall_save);
9335           forall_flag = 2;
9336         }
9337       else if (code->block)
9338         {
9339           omp_workshare_save = -1;
9340           switch (code->op)
9341             {
9342             case EXEC_OMP_PARALLEL_WORKSHARE:
9343               omp_workshare_save = omp_workshare_flag;
9344               omp_workshare_flag = 1;
9345               gfc_resolve_omp_parallel_blocks (code, ns);
9346               break;
9347             case EXEC_OMP_PARALLEL:
9348             case EXEC_OMP_PARALLEL_DO:
9349             case EXEC_OMP_PARALLEL_SECTIONS:
9350             case EXEC_OMP_TASK:
9351               omp_workshare_save = omp_workshare_flag;
9352               omp_workshare_flag = 0;
9353               gfc_resolve_omp_parallel_blocks (code, ns);
9354               break;
9355             case EXEC_OMP_DO:
9356               gfc_resolve_omp_do_blocks (code, ns);
9357               break;
9358             case EXEC_SELECT_TYPE:
9359               /* Blocks are handled in resolve_select_type because we have
9360                  to transform the SELECT TYPE into ASSOCIATE first.  */
9361               break;
9362             case EXEC_DO_CONCURRENT:
9363               do_concurrent_flag = 1;
9364               gfc_resolve_blocks (code->block, ns);
9365               do_concurrent_flag = 2;
9366               break;
9367             case EXEC_OMP_WORKSHARE:
9368               omp_workshare_save = omp_workshare_flag;
9369               omp_workshare_flag = 1;
9370               /* FALL THROUGH */
9371             default:
9372               gfc_resolve_blocks (code->block, ns);
9373               break;
9374             }
9375
9376           if (omp_workshare_save != -1)
9377             omp_workshare_flag = omp_workshare_save;
9378         }
9379
9380       t = SUCCESS;
9381       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
9382         t = gfc_resolve_expr (code->expr1);
9383       forall_flag = forall_save;
9384       do_concurrent_flag = do_concurrent_save;
9385
9386       if (gfc_resolve_expr (code->expr2) == FAILURE)
9387         t = FAILURE;
9388
9389       if (code->op == EXEC_ALLOCATE
9390           && gfc_resolve_expr (code->expr3) == FAILURE)
9391         t = FAILURE;
9392
9393       switch (code->op)
9394         {
9395         case EXEC_NOP:
9396         case EXEC_END_BLOCK:
9397         case EXEC_END_NESTED_BLOCK:
9398         case EXEC_CYCLE:
9399         case EXEC_PAUSE:
9400         case EXEC_STOP:
9401         case EXEC_ERROR_STOP:
9402         case EXEC_EXIT:
9403         case EXEC_CONTINUE:
9404         case EXEC_DT_END:
9405         case EXEC_ASSIGN_CALL:
9406         case EXEC_CRITICAL:
9407           break;
9408
9409         case EXEC_SYNC_ALL:
9410         case EXEC_SYNC_IMAGES:
9411         case EXEC_SYNC_MEMORY:
9412           resolve_sync (code);
9413           break;
9414
9415         case EXEC_LOCK:
9416         case EXEC_UNLOCK:
9417           resolve_lock_unlock (code);
9418           break;
9419
9420         case EXEC_ENTRY:
9421           /* Keep track of which entry we are up to.  */
9422           current_entry_id = code->ext.entry->id;
9423           break;
9424
9425         case EXEC_WHERE:
9426           resolve_where (code, NULL);
9427           break;
9428
9429         case EXEC_GOTO:
9430           if (code->expr1 != NULL)
9431             {
9432               if (code->expr1->ts.type != BT_INTEGER)
9433                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
9434                            "INTEGER variable", &code->expr1->where);
9435               else if (code->expr1->symtree->n.sym->attr.assign != 1)
9436                 gfc_error ("Variable '%s' has not been assigned a target "
9437                            "label at %L", code->expr1->symtree->n.sym->name,
9438                            &code->expr1->where);
9439             }
9440           else
9441             resolve_branch (code->label1, code);
9442           break;
9443
9444         case EXEC_RETURN:
9445           if (code->expr1 != NULL
9446                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
9447             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
9448                        "INTEGER return specifier", &code->expr1->where);
9449           break;
9450
9451         case EXEC_INIT_ASSIGN:
9452         case EXEC_END_PROCEDURE:
9453           break;
9454
9455         case EXEC_ASSIGN:
9456           if (t == FAILURE)
9457             break;
9458
9459           if (gfc_check_vardef_context (code->expr1, false, false,
9460                                         _("assignment")) == FAILURE)
9461             break;
9462
9463           if (resolve_ordinary_assign (code, ns))
9464             {
9465               if (code->op == EXEC_COMPCALL)
9466                 goto compcall;
9467               else
9468                 goto call;
9469             }
9470           break;
9471
9472         case EXEC_LABEL_ASSIGN:
9473           if (code->label1->defined == ST_LABEL_UNKNOWN)
9474             gfc_error ("Label %d referenced at %L is never defined",
9475                        code->label1->value, &code->label1->where);
9476           if (t == SUCCESS
9477               && (code->expr1->expr_type != EXPR_VARIABLE
9478                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
9479                   || code->expr1->symtree->n.sym->ts.kind
9480                      != gfc_default_integer_kind
9481                   || code->expr1->symtree->n.sym->as != NULL))
9482             gfc_error ("ASSIGN statement at %L requires a scalar "
9483                        "default INTEGER variable", &code->expr1->where);
9484           break;
9485
9486         case EXEC_POINTER_ASSIGN:
9487           {
9488             gfc_expr* e;
9489
9490             if (t == FAILURE)
9491               break;
9492
9493             /* This is both a variable definition and pointer assignment
9494                context, so check both of them.  For rank remapping, a final
9495                array ref may be present on the LHS and fool gfc_expr_attr
9496                used in gfc_check_vardef_context.  Remove it.  */
9497             e = remove_last_array_ref (code->expr1);
9498             t = gfc_check_vardef_context (e, true, false,
9499                                           _("pointer assignment"));
9500             if (t == SUCCESS)
9501               t = gfc_check_vardef_context (e, false, false,
9502                                             _("pointer assignment"));
9503             gfc_free_expr (e);
9504             if (t == FAILURE)
9505               break;
9506
9507             gfc_check_pointer_assign (code->expr1, code->expr2);
9508             break;
9509           }
9510
9511         case EXEC_ARITHMETIC_IF:
9512           if (t == SUCCESS
9513               && code->expr1->ts.type != BT_INTEGER
9514               && code->expr1->ts.type != BT_REAL)
9515             gfc_error ("Arithmetic IF statement at %L requires a numeric "
9516                        "expression", &code->expr1->where);
9517
9518           resolve_branch (code->label1, code);
9519           resolve_branch (code->label2, code);
9520           resolve_branch (code->label3, code);
9521           break;
9522
9523         case EXEC_IF:
9524           if (t == SUCCESS && code->expr1 != NULL
9525               && (code->expr1->ts.type != BT_LOGICAL
9526                   || code->expr1->rank != 0))
9527             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9528                        &code->expr1->where);
9529           break;
9530
9531         case EXEC_CALL:
9532         call:
9533           resolve_call (code);
9534           break;
9535
9536         case EXEC_COMPCALL:
9537         compcall:
9538           resolve_typebound_subroutine (code);
9539           break;
9540
9541         case EXEC_CALL_PPC:
9542           resolve_ppc_call (code);
9543           break;
9544
9545         case EXEC_SELECT:
9546           /* Select is complicated. Also, a SELECT construct could be
9547              a transformed computed GOTO.  */
9548           resolve_select (code);
9549           break;
9550
9551         case EXEC_SELECT_TYPE:
9552           resolve_select_type (code, ns);
9553           break;
9554
9555         case EXEC_BLOCK:
9556           resolve_block_construct (code);
9557           break;
9558
9559         case EXEC_DO:
9560           if (code->ext.iterator != NULL)
9561             {
9562               gfc_iterator *iter = code->ext.iterator;
9563               if (gfc_resolve_iterator (iter, true) != FAILURE)
9564                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
9565             }
9566           break;
9567
9568         case EXEC_DO_WHILE:
9569           if (code->expr1 == NULL)
9570             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
9571           if (t == SUCCESS
9572               && (code->expr1->rank != 0
9573                   || code->expr1->ts.type != BT_LOGICAL))
9574             gfc_error ("Exit condition of DO WHILE loop at %L must be "
9575                        "a scalar LOGICAL expression", &code->expr1->where);
9576           break;
9577
9578         case EXEC_ALLOCATE:
9579           if (t == SUCCESS)
9580             resolve_allocate_deallocate (code, "ALLOCATE");
9581
9582           break;
9583
9584         case EXEC_DEALLOCATE:
9585           if (t == SUCCESS)
9586             resolve_allocate_deallocate (code, "DEALLOCATE");
9587
9588           break;
9589
9590         case EXEC_OPEN:
9591           if (gfc_resolve_open (code->ext.open) == FAILURE)
9592             break;
9593
9594           resolve_branch (code->ext.open->err, code);
9595           break;
9596
9597         case EXEC_CLOSE:
9598           if (gfc_resolve_close (code->ext.close) == FAILURE)
9599             break;
9600
9601           resolve_branch (code->ext.close->err, code);
9602           break;
9603
9604         case EXEC_BACKSPACE:
9605         case EXEC_ENDFILE:
9606         case EXEC_REWIND:
9607         case EXEC_FLUSH:
9608           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
9609             break;
9610
9611           resolve_branch (code->ext.filepos->err, code);
9612           break;
9613
9614         case EXEC_INQUIRE:
9615           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9616               break;
9617
9618           resolve_branch (code->ext.inquire->err, code);
9619           break;
9620
9621         case EXEC_IOLENGTH:
9622           gcc_assert (code->ext.inquire != NULL);
9623           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9624             break;
9625
9626           resolve_branch (code->ext.inquire->err, code);
9627           break;
9628
9629         case EXEC_WAIT:
9630           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
9631             break;
9632
9633           resolve_branch (code->ext.wait->err, code);
9634           resolve_branch (code->ext.wait->end, code);
9635           resolve_branch (code->ext.wait->eor, code);
9636           break;
9637
9638         case EXEC_READ:
9639         case EXEC_WRITE:
9640           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
9641             break;
9642
9643           resolve_branch (code->ext.dt->err, code);
9644           resolve_branch (code->ext.dt->end, code);
9645           resolve_branch (code->ext.dt->eor, code);
9646           break;
9647
9648         case EXEC_TRANSFER:
9649           resolve_transfer (code);
9650           break;
9651
9652         case EXEC_DO_CONCURRENT:
9653         case EXEC_FORALL:
9654           resolve_forall_iterators (code->ext.forall_iterator);
9655
9656           if (code->expr1 != NULL
9657               && (code->expr1->ts.type != BT_LOGICAL || code->expr1->rank))
9658             gfc_error ("FORALL mask clause at %L requires a scalar LOGICAL "
9659                        "expression", &code->expr1->where);
9660           break;
9661
9662         case EXEC_OMP_ATOMIC:
9663         case EXEC_OMP_BARRIER:
9664         case EXEC_OMP_CRITICAL:
9665         case EXEC_OMP_FLUSH:
9666         case EXEC_OMP_DO:
9667         case EXEC_OMP_MASTER:
9668         case EXEC_OMP_ORDERED:
9669         case EXEC_OMP_SECTIONS:
9670         case EXEC_OMP_SINGLE:
9671         case EXEC_OMP_TASKWAIT:
9672         case EXEC_OMP_TASKYIELD:
9673         case EXEC_OMP_WORKSHARE:
9674           gfc_resolve_omp_directive (code, ns);
9675           break;
9676
9677         case EXEC_OMP_PARALLEL:
9678         case EXEC_OMP_PARALLEL_DO:
9679         case EXEC_OMP_PARALLEL_SECTIONS:
9680         case EXEC_OMP_PARALLEL_WORKSHARE:
9681         case EXEC_OMP_TASK:
9682           omp_workshare_save = omp_workshare_flag;
9683           omp_workshare_flag = 0;
9684           gfc_resolve_omp_directive (code, ns);
9685           omp_workshare_flag = omp_workshare_save;
9686           break;
9687
9688         default:
9689           gfc_internal_error ("resolve_code(): Bad statement code");
9690         }
9691     }
9692
9693   cs_base = frame.prev;
9694 }
9695
9696
9697 /* Resolve initial values and make sure they are compatible with
9698    the variable.  */
9699
9700 static void
9701 resolve_values (gfc_symbol *sym)
9702 {
9703   gfc_try t;
9704
9705   if (sym->value == NULL)
9706     return;
9707
9708   if (sym->value->expr_type == EXPR_STRUCTURE)
9709     t= resolve_structure_cons (sym->value, 1);
9710   else 
9711     t = gfc_resolve_expr (sym->value);
9712
9713   if (t == FAILURE)
9714     return;
9715
9716   gfc_check_assign_symbol (sym, sym->value);
9717 }
9718
9719
9720 /* Verify the binding labels for common blocks that are BIND(C).  The label
9721    for a BIND(C) common block must be identical in all scoping units in which
9722    the common block is declared.  Further, the binding label can not collide
9723    with any other global entity in the program.  */
9724
9725 static void
9726 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
9727 {
9728   if (comm_block_tree->n.common->is_bind_c == 1)
9729     {
9730       gfc_gsymbol *binding_label_gsym;
9731       gfc_gsymbol *comm_name_gsym;
9732       const char * bind_label = comm_block_tree->n.common->binding_label 
9733         ? comm_block_tree->n.common->binding_label : "";
9734
9735       /* See if a global symbol exists by the common block's name.  It may
9736          be NULL if the common block is use-associated.  */
9737       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
9738                                          comm_block_tree->n.common->name);
9739       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
9740         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
9741                    "with the global entity '%s' at %L",
9742                    bind_label,
9743                    comm_block_tree->n.common->name,
9744                    &(comm_block_tree->n.common->where),
9745                    comm_name_gsym->name, &(comm_name_gsym->where));
9746       else if (comm_name_gsym != NULL
9747                && strcmp (comm_name_gsym->name,
9748                           comm_block_tree->n.common->name) == 0)
9749         {
9750           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
9751              as expected.  */
9752           if (comm_name_gsym->binding_label == NULL)
9753             /* No binding label for common block stored yet; save this one.  */
9754             comm_name_gsym->binding_label = bind_label;
9755           else if (strcmp (comm_name_gsym->binding_label, bind_label) != 0)
9756               {
9757                 /* Common block names match but binding labels do not.  */
9758                 gfc_error ("Binding label '%s' for common block '%s' at %L "
9759                            "does not match the binding label '%s' for common "
9760                            "block '%s' at %L",
9761                            bind_label,
9762                            comm_block_tree->n.common->name,
9763                            &(comm_block_tree->n.common->where),
9764                            comm_name_gsym->binding_label,
9765                            comm_name_gsym->name,
9766                            &(comm_name_gsym->where));
9767                 return;
9768               }
9769         }
9770
9771       /* There is no binding label (NAME="") so we have nothing further to
9772          check and nothing to add as a global symbol for the label.  */
9773       if (!comm_block_tree->n.common->binding_label)
9774         return;
9775       
9776       binding_label_gsym =
9777         gfc_find_gsymbol (gfc_gsym_root,
9778                           comm_block_tree->n.common->binding_label);
9779       if (binding_label_gsym == NULL)
9780         {
9781           /* Need to make a global symbol for the binding label to prevent
9782              it from colliding with another.  */
9783           binding_label_gsym =
9784             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
9785           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
9786           binding_label_gsym->type = GSYM_COMMON;
9787         }
9788       else
9789         {
9790           /* If comm_name_gsym is NULL, the name common block is use
9791              associated and the name could be colliding.  */
9792           if (binding_label_gsym->type != GSYM_COMMON)
9793             gfc_error ("Binding label '%s' for common block '%s' at %L "
9794                        "collides with the global entity '%s' at %L",
9795                        comm_block_tree->n.common->binding_label,
9796                        comm_block_tree->n.common->name,
9797                        &(comm_block_tree->n.common->where),
9798                        binding_label_gsym->name,
9799                        &(binding_label_gsym->where));
9800           else if (comm_name_gsym != NULL
9801                    && (strcmp (binding_label_gsym->name,
9802                                comm_name_gsym->binding_label) != 0)
9803                    && (strcmp (binding_label_gsym->sym_name,
9804                                comm_name_gsym->name) != 0))
9805             gfc_error ("Binding label '%s' for common block '%s' at %L "
9806                        "collides with global entity '%s' at %L",
9807                        binding_label_gsym->name, binding_label_gsym->sym_name,
9808                        &(comm_block_tree->n.common->where),
9809                        comm_name_gsym->name, &(comm_name_gsym->where));
9810         }
9811     }
9812   
9813   return;
9814 }
9815
9816
9817 /* Verify any BIND(C) derived types in the namespace so we can report errors
9818    for them once, rather than for each variable declared of that type.  */
9819
9820 static void
9821 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
9822 {
9823   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
9824       && derived_sym->attr.is_bind_c == 1)
9825     verify_bind_c_derived_type (derived_sym);
9826   
9827   return;
9828 }
9829
9830
9831 /* Verify that any binding labels used in a given namespace do not collide 
9832    with the names or binding labels of any global symbols.  */
9833
9834 static void
9835 gfc_verify_binding_labels (gfc_symbol *sym)
9836 {
9837   int has_error = 0;
9838   
9839   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
9840       && sym->attr.flavor != FL_DERIVED && sym->binding_label)
9841     {
9842       gfc_gsymbol *bind_c_sym;
9843
9844       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
9845       if (bind_c_sym != NULL 
9846           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
9847         {
9848           if (sym->attr.if_source == IFSRC_DECL 
9849               && (bind_c_sym->type != GSYM_SUBROUTINE 
9850                   && bind_c_sym->type != GSYM_FUNCTION) 
9851               && ((sym->attr.contained == 1 
9852                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
9853                   || (sym->attr.use_assoc == 1 
9854                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
9855             {
9856               /* Make sure global procedures don't collide with anything.  */
9857               gfc_error ("Binding label '%s' at %L collides with the global "
9858                          "entity '%s' at %L", sym->binding_label,
9859                          &(sym->declared_at), bind_c_sym->name,
9860                          &(bind_c_sym->where));
9861               has_error = 1;
9862             }
9863           else if (sym->attr.contained == 0 
9864                    && (sym->attr.if_source == IFSRC_IFBODY 
9865                        && sym->attr.flavor == FL_PROCEDURE) 
9866                    && (bind_c_sym->sym_name != NULL 
9867                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
9868             {
9869               /* Make sure procedures in interface bodies don't collide.  */
9870               gfc_error ("Binding label '%s' in interface body at %L collides "
9871                          "with the global entity '%s' at %L",
9872                          sym->binding_label,
9873                          &(sym->declared_at), bind_c_sym->name,
9874                          &(bind_c_sym->where));
9875               has_error = 1;
9876             }
9877           else if (sym->attr.contained == 0 
9878                    && sym->attr.if_source == IFSRC_UNKNOWN)
9879             if ((sym->attr.use_assoc && bind_c_sym->mod_name
9880                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
9881                 || sym->attr.use_assoc == 0)
9882               {
9883                 gfc_error ("Binding label '%s' at %L collides with global "
9884                            "entity '%s' at %L", sym->binding_label,
9885                            &(sym->declared_at), bind_c_sym->name,
9886                            &(bind_c_sym->where));
9887                 has_error = 1;
9888               }
9889
9890           if (has_error != 0)
9891             /* Clear the binding label to prevent checking multiple times.  */
9892             sym->binding_label = NULL;
9893         }
9894       else if (bind_c_sym == NULL)
9895         {
9896           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
9897           bind_c_sym->where = sym->declared_at;
9898           bind_c_sym->sym_name = sym->name;
9899
9900           if (sym->attr.use_assoc == 1)
9901             bind_c_sym->mod_name = sym->module;
9902           else
9903             if (sym->ns->proc_name != NULL)
9904               bind_c_sym->mod_name = sym->ns->proc_name->name;
9905
9906           if (sym->attr.contained == 0)
9907             {
9908               if (sym->attr.subroutine)
9909                 bind_c_sym->type = GSYM_SUBROUTINE;
9910               else if (sym->attr.function)
9911                 bind_c_sym->type = GSYM_FUNCTION;
9912             }
9913         }
9914     }
9915   return;
9916 }
9917
9918
9919 /* Resolve an index expression.  */
9920
9921 static gfc_try
9922 resolve_index_expr (gfc_expr *e)
9923 {
9924   if (gfc_resolve_expr (e) == FAILURE)
9925     return FAILURE;
9926
9927   if (gfc_simplify_expr (e, 0) == FAILURE)
9928     return FAILURE;
9929
9930   if (gfc_specification_expr (e) == FAILURE)
9931     return FAILURE;
9932
9933   return SUCCESS;
9934 }
9935
9936
9937 /* Resolve a charlen structure.  */
9938
9939 static gfc_try
9940 resolve_charlen (gfc_charlen *cl)
9941 {
9942   int i, k;
9943
9944   if (cl->resolved)
9945     return SUCCESS;
9946
9947   cl->resolved = 1;
9948
9949
9950   if (cl->length_from_typespec)
9951     {
9952       if (gfc_resolve_expr (cl->length) == FAILURE)
9953         return FAILURE;
9954
9955       if (gfc_simplify_expr (cl->length, 0) == FAILURE)
9956         return FAILURE;
9957     }
9958   else
9959     {
9960       specification_expr = 1;
9961
9962       if (resolve_index_expr (cl->length) == FAILURE)
9963         {
9964           specification_expr = 0;
9965           return FAILURE;
9966         }
9967     }
9968
9969   /* "If the character length parameter value evaluates to a negative
9970      value, the length of character entities declared is zero."  */
9971   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
9972     {
9973       if (gfc_option.warn_surprising)
9974         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
9975                          " the length has been set to zero",
9976                          &cl->length->where, i);
9977       gfc_replace_expr (cl->length,
9978                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
9979     }
9980
9981   /* Check that the character length is not too large.  */
9982   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
9983   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
9984       && cl->length->ts.type == BT_INTEGER
9985       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
9986     {
9987       gfc_error ("String length at %L is too large", &cl->length->where);
9988       return FAILURE;
9989     }
9990
9991   return SUCCESS;
9992 }
9993
9994
9995 /* Test for non-constant shape arrays.  */
9996
9997 static bool
9998 is_non_constant_shape_array (gfc_symbol *sym)
9999 {
10000   gfc_expr *e;
10001   int i;
10002   bool not_constant;
10003
10004   not_constant = false;
10005   if (sym->as != NULL)
10006     {
10007       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
10008          has not been simplified; parameter array references.  Do the
10009          simplification now.  */
10010       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
10011         {
10012           e = sym->as->lower[i];
10013           if (e && (resolve_index_expr (e) == FAILURE
10014                     || !gfc_is_constant_expr (e)))
10015             not_constant = true;
10016           e = sym->as->upper[i];
10017           if (e && (resolve_index_expr (e) == FAILURE
10018                     || !gfc_is_constant_expr (e)))
10019             not_constant = true;
10020         }
10021     }
10022   return not_constant;
10023 }
10024
10025 /* Given a symbol and an initialization expression, add code to initialize
10026    the symbol to the function entry.  */
10027 static void
10028 build_init_assign (gfc_symbol *sym, gfc_expr *init)
10029 {
10030   gfc_expr *lval;
10031   gfc_code *init_st;
10032   gfc_namespace *ns = sym->ns;
10033
10034   /* Search for the function namespace if this is a contained
10035      function without an explicit result.  */
10036   if (sym->attr.function && sym == sym->result
10037       && sym->name != sym->ns->proc_name->name)
10038     {
10039       ns = ns->contained;
10040       for (;ns; ns = ns->sibling)
10041         if (strcmp (ns->proc_name->name, sym->name) == 0)
10042           break;
10043     }
10044
10045   if (ns == NULL)
10046     {
10047       gfc_free_expr (init);
10048       return;
10049     }
10050
10051   /* Build an l-value expression for the result.  */
10052   lval = gfc_lval_expr_from_sym (sym);
10053
10054   /* Add the code at scope entry.  */
10055   init_st = gfc_get_code ();
10056   init_st->next = ns->code;
10057   ns->code = init_st;
10058
10059   /* Assign the default initializer to the l-value.  */
10060   init_st->loc = sym->declared_at;
10061   init_st->op = EXEC_INIT_ASSIGN;
10062   init_st->expr1 = lval;
10063   init_st->expr2 = init;
10064 }
10065
10066 /* Assign the default initializer to a derived type variable or result.  */
10067
10068 static void
10069 apply_default_init (gfc_symbol *sym)
10070 {
10071   gfc_expr *init = NULL;
10072
10073   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
10074     return;
10075
10076   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
10077     init = gfc_default_initializer (&sym->ts);
10078
10079   if (init == NULL && sym->ts.type != BT_CLASS)
10080     return;
10081
10082   build_init_assign (sym, init);
10083   sym->attr.referenced = 1;
10084 }
10085
10086 /* Build an initializer for a local integer, real, complex, logical, or
10087    character variable, based on the command line flags finit-local-zero,
10088    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
10089    null if the symbol should not have a default initialization.  */
10090 static gfc_expr *
10091 build_default_init_expr (gfc_symbol *sym)
10092 {
10093   int char_len;
10094   gfc_expr *init_expr;
10095   int i;
10096
10097   /* These symbols should never have a default initialization.  */
10098   if (sym->attr.allocatable
10099       || sym->attr.external
10100       || sym->attr.dummy
10101       || sym->attr.pointer
10102       || sym->attr.in_equivalence
10103       || sym->attr.in_common
10104       || sym->attr.data
10105       || sym->module
10106       || sym->attr.cray_pointee
10107       || sym->attr.cray_pointer
10108       || sym->assoc)
10109     return NULL;
10110
10111   /* Now we'll try to build an initializer expression.  */
10112   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
10113                                      &sym->declared_at);
10114
10115   /* We will only initialize integers, reals, complex, logicals, and
10116      characters, and only if the corresponding command-line flags
10117      were set.  Otherwise, we free init_expr and return null.  */
10118   switch (sym->ts.type)
10119     {    
10120     case BT_INTEGER:
10121       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
10122         mpz_set_si (init_expr->value.integer, 
10123                          gfc_option.flag_init_integer_value);
10124       else
10125         {
10126           gfc_free_expr (init_expr);
10127           init_expr = NULL;
10128         }
10129       break;
10130
10131     case BT_REAL:
10132       switch (gfc_option.flag_init_real)
10133         {
10134         case GFC_INIT_REAL_SNAN:
10135           init_expr->is_snan = 1;
10136           /* Fall through.  */
10137         case GFC_INIT_REAL_NAN:
10138           mpfr_set_nan (init_expr->value.real);
10139           break;
10140
10141         case GFC_INIT_REAL_INF:
10142           mpfr_set_inf (init_expr->value.real, 1);
10143           break;
10144
10145         case GFC_INIT_REAL_NEG_INF:
10146           mpfr_set_inf (init_expr->value.real, -1);
10147           break;
10148
10149         case GFC_INIT_REAL_ZERO:
10150           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
10151           break;
10152
10153         default:
10154           gfc_free_expr (init_expr);
10155           init_expr = NULL;
10156           break;
10157         }
10158       break;
10159           
10160     case BT_COMPLEX:
10161       switch (gfc_option.flag_init_real)
10162         {
10163         case GFC_INIT_REAL_SNAN:
10164           init_expr->is_snan = 1;
10165           /* Fall through.  */
10166         case GFC_INIT_REAL_NAN:
10167           mpfr_set_nan (mpc_realref (init_expr->value.complex));
10168           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
10169           break;
10170
10171         case GFC_INIT_REAL_INF:
10172           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
10173           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
10174           break;
10175
10176         case GFC_INIT_REAL_NEG_INF:
10177           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
10178           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
10179           break;
10180
10181         case GFC_INIT_REAL_ZERO:
10182           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
10183           break;
10184
10185         default:
10186           gfc_free_expr (init_expr);
10187           init_expr = NULL;
10188           break;
10189         }
10190       break;
10191           
10192     case BT_LOGICAL:
10193       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
10194         init_expr->value.logical = 0;
10195       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
10196         init_expr->value.logical = 1;
10197       else
10198         {
10199           gfc_free_expr (init_expr);
10200           init_expr = NULL;
10201         }
10202       break;
10203           
10204     case BT_CHARACTER:
10205       /* For characters, the length must be constant in order to 
10206          create a default initializer.  */
10207       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
10208           && sym->ts.u.cl->length
10209           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
10210         {
10211           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
10212           init_expr->value.character.length = char_len;
10213           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
10214           for (i = 0; i < char_len; i++)
10215             init_expr->value.character.string[i]
10216               = (unsigned char) gfc_option.flag_init_character_value;
10217         }
10218       else
10219         {
10220           gfc_free_expr (init_expr);
10221           init_expr = NULL;
10222         }
10223       if (!init_expr && gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
10224           && sym->ts.u.cl->length)
10225         {
10226           gfc_actual_arglist *arg;
10227           init_expr = gfc_get_expr ();
10228           init_expr->where = sym->declared_at;
10229           init_expr->ts = sym->ts;
10230           init_expr->expr_type = EXPR_FUNCTION;
10231           init_expr->value.function.isym =
10232                 gfc_intrinsic_function_by_id (GFC_ISYM_REPEAT);
10233           init_expr->value.function.name = "repeat";
10234           arg = gfc_get_actual_arglist ();
10235           arg->expr = gfc_get_character_expr (sym->ts.kind, &sym->declared_at,
10236                                               NULL, 1);
10237           arg->expr->value.character.string[0]
10238                 = gfc_option.flag_init_character_value;
10239           arg->next = gfc_get_actual_arglist ();
10240           arg->next->expr = gfc_copy_expr (sym->ts.u.cl->length);
10241           init_expr->value.function.actual = arg;
10242         }
10243       break;
10244           
10245     default:
10246      gfc_free_expr (init_expr);
10247      init_expr = NULL;
10248     }
10249   return init_expr;
10250 }
10251
10252 /* Add an initialization expression to a local variable.  */
10253 static void
10254 apply_default_init_local (gfc_symbol *sym)
10255 {
10256   gfc_expr *init = NULL;
10257
10258   /* The symbol should be a variable or a function return value.  */
10259   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
10260       || (sym->attr.function && sym->result != sym))
10261     return;
10262
10263   /* Try to build the initializer expression.  If we can't initialize
10264      this symbol, then init will be NULL.  */
10265   init = build_default_init_expr (sym);
10266   if (init == NULL)
10267     return;
10268
10269   /* For saved variables, we don't want to add an initializer at function
10270      entry, so we just add a static initializer. Note that automatic variables
10271      are stack allocated even with -fno-automatic.  */
10272   if (sym->attr.save || sym->ns->save_all 
10273       || (gfc_option.flag_max_stack_var_size == 0
10274           && (!sym->attr.dimension || !is_non_constant_shape_array (sym))))
10275     {
10276       /* Don't clobber an existing initializer!  */
10277       gcc_assert (sym->value == NULL);
10278       sym->value = init;
10279       return;
10280     }
10281
10282   build_init_assign (sym, init);
10283 }
10284
10285
10286 /* Resolution of common features of flavors variable and procedure.  */
10287
10288 static gfc_try
10289 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
10290 {
10291   gfc_array_spec *as;
10292
10293   /* Avoid double diagnostics for function result symbols.  */
10294   if ((sym->result || sym->attr.result) && !sym->attr.dummy
10295       && (sym->ns != gfc_current_ns))
10296     return SUCCESS;
10297
10298   if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
10299     as = CLASS_DATA (sym)->as;
10300   else
10301     as = sym->as;
10302
10303   /* Constraints on deferred shape variable.  */
10304   if (as == NULL || as->type != AS_DEFERRED)
10305     {
10306       bool pointer, allocatable, dimension;
10307
10308       if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
10309         {
10310           pointer = CLASS_DATA (sym)->attr.class_pointer;
10311           allocatable = CLASS_DATA (sym)->attr.allocatable;
10312           dimension = CLASS_DATA (sym)->attr.dimension;
10313         }
10314       else
10315         {
10316           pointer = sym->attr.pointer;
10317           allocatable = sym->attr.allocatable;
10318           dimension = sym->attr.dimension;
10319         }
10320
10321       if (allocatable)
10322         {
10323           if (dimension)
10324             {
10325               gfc_error ("Allocatable array '%s' at %L must have "
10326                          "a deferred shape", sym->name, &sym->declared_at);
10327               return FAILURE;
10328             }
10329           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
10330                                    "may not be ALLOCATABLE", sym->name,
10331                                    &sym->declared_at) == FAILURE)
10332             return FAILURE;
10333         }
10334
10335       if (pointer && dimension)
10336         {
10337           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
10338                      sym->name, &sym->declared_at);
10339           return FAILURE;
10340         }
10341     }
10342   else
10343     {
10344       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
10345           && sym->ts.type != BT_CLASS && !sym->assoc)
10346         {
10347           gfc_error ("Array '%s' at %L cannot have a deferred shape",
10348                      sym->name, &sym->declared_at);
10349           return FAILURE;
10350          }
10351     }
10352
10353   /* Constraints on polymorphic variables.  */
10354   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
10355     {
10356       /* F03:C502.  */
10357       if (sym->attr.class_ok
10358           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
10359         {
10360           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
10361                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
10362                      &sym->declared_at);
10363           return FAILURE;
10364         }
10365
10366       /* F03:C509.  */
10367       /* Assume that use associated symbols were checked in the module ns.
10368          Class-variables that are associate-names are also something special
10369          and excepted from the test.  */
10370       if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
10371         {
10372           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
10373                      "or pointer", sym->name, &sym->declared_at);
10374           return FAILURE;
10375         }
10376     }
10377     
10378   return SUCCESS;
10379 }
10380
10381
10382 /* Additional checks for symbols with flavor variable and derived
10383    type.  To be called from resolve_fl_variable.  */
10384
10385 static gfc_try
10386 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
10387 {
10388   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
10389
10390   /* Check to see if a derived type is blocked from being host
10391      associated by the presence of another class I symbol in the same
10392      namespace.  14.6.1.3 of the standard and the discussion on
10393      comp.lang.fortran.  */
10394   if (sym->ns != sym->ts.u.derived->ns
10395       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
10396     {
10397       gfc_symbol *s;
10398       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
10399       if (s && s->attr.generic)
10400         s = gfc_find_dt_in_generic (s);
10401       if (s && s->attr.flavor != FL_DERIVED)
10402         {
10403           gfc_error ("The type '%s' cannot be host associated at %L "
10404                      "because it is blocked by an incompatible object "
10405                      "of the same name declared at %L",
10406                      sym->ts.u.derived->name, &sym->declared_at,
10407                      &s->declared_at);
10408           return FAILURE;
10409         }
10410     }
10411
10412   /* 4th constraint in section 11.3: "If an object of a type for which
10413      component-initialization is specified (R429) appears in the
10414      specification-part of a module and does not have the ALLOCATABLE
10415      or POINTER attribute, the object shall have the SAVE attribute."
10416
10417      The check for initializers is performed with
10418      gfc_has_default_initializer because gfc_default_initializer generates
10419      a hidden default for allocatable components.  */
10420   if (!(sym->value || no_init_flag) && sym->ns->proc_name
10421       && sym->ns->proc_name->attr.flavor == FL_MODULE
10422       && !sym->ns->save_all && !sym->attr.save
10423       && !sym->attr.pointer && !sym->attr.allocatable
10424       && gfc_has_default_initializer (sym->ts.u.derived)
10425       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
10426                          "module variable '%s' at %L, needed due to "
10427                          "the default initialization", sym->name,
10428                          &sym->declared_at) == FAILURE)
10429     return FAILURE;
10430
10431   /* Assign default initializer.  */
10432   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
10433       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
10434     {
10435       sym->value = gfc_default_initializer (&sym->ts);
10436     }
10437
10438   return SUCCESS;
10439 }
10440
10441
10442 /* Resolve symbols with flavor variable.  */
10443
10444 static gfc_try
10445 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
10446 {
10447   int no_init_flag, automatic_flag;
10448   gfc_expr *e;
10449   const char *auto_save_msg;
10450
10451   auto_save_msg = "Automatic object '%s' at %L cannot have the "
10452                   "SAVE attribute";
10453
10454   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10455     return FAILURE;
10456
10457   /* Set this flag to check that variables are parameters of all entries.
10458      This check is effected by the call to gfc_resolve_expr through
10459      is_non_constant_shape_array.  */
10460   specification_expr = 1;
10461
10462   if (sym->ns->proc_name
10463       && (sym->ns->proc_name->attr.flavor == FL_MODULE
10464           || sym->ns->proc_name->attr.is_main_program)
10465       && !sym->attr.use_assoc
10466       && !sym->attr.allocatable
10467       && !sym->attr.pointer
10468       && is_non_constant_shape_array (sym))
10469     {
10470       /* The shape of a main program or module array needs to be
10471          constant.  */
10472       gfc_error ("The module or main program array '%s' at %L must "
10473                  "have constant shape", sym->name, &sym->declared_at);
10474       specification_expr = 0;
10475       return FAILURE;
10476     }
10477
10478   /* Constraints on deferred type parameter.  */
10479   if (sym->ts.deferred && !(sym->attr.pointer || sym->attr.allocatable))
10480     {
10481       gfc_error ("Entity '%s' at %L has a deferred type parameter and "
10482                  "requires either the pointer or allocatable attribute",
10483                      sym->name, &sym->declared_at);
10484       return FAILURE;
10485     }
10486
10487   if (sym->ts.type == BT_CHARACTER)
10488     {
10489       /* Make sure that character string variables with assumed length are
10490          dummy arguments.  */
10491       e = sym->ts.u.cl->length;
10492       if (e == NULL && !sym->attr.dummy && !sym->attr.result
10493           && !sym->ts.deferred)
10494         {
10495           gfc_error ("Entity with assumed character length at %L must be a "
10496                      "dummy argument or a PARAMETER", &sym->declared_at);
10497           return FAILURE;
10498         }
10499
10500       if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
10501         {
10502           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10503           return FAILURE;
10504         }
10505
10506       if (!gfc_is_constant_expr (e)
10507           && !(e->expr_type == EXPR_VARIABLE
10508                && e->symtree->n.sym->attr.flavor == FL_PARAMETER))
10509         {
10510           if (!sym->attr.use_assoc && sym->ns->proc_name
10511               && (sym->ns->proc_name->attr.flavor == FL_MODULE
10512                   || sym->ns->proc_name->attr.is_main_program))
10513             {
10514               gfc_error ("'%s' at %L must have constant character length "
10515                         "in this context", sym->name, &sym->declared_at);
10516               return FAILURE;
10517             }
10518           if (sym->attr.in_common)
10519             {
10520               gfc_error ("COMMON variable '%s' at %L must have constant "
10521                          "character length", sym->name, &sym->declared_at);
10522               return FAILURE;
10523             }
10524         }
10525     }
10526
10527   if (sym->value == NULL && sym->attr.referenced)
10528     apply_default_init_local (sym); /* Try to apply a default initialization.  */
10529
10530   /* Determine if the symbol may not have an initializer.  */
10531   no_init_flag = automatic_flag = 0;
10532   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
10533       || sym->attr.intrinsic || sym->attr.result)
10534     no_init_flag = 1;
10535   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
10536            && is_non_constant_shape_array (sym))
10537     {
10538       no_init_flag = automatic_flag = 1;
10539
10540       /* Also, they must not have the SAVE attribute.
10541          SAVE_IMPLICIT is checked below.  */
10542       if (sym->as && sym->attr.codimension)
10543         {
10544           int corank = sym->as->corank;
10545           sym->as->corank = 0;
10546           no_init_flag = automatic_flag = is_non_constant_shape_array (sym);
10547           sym->as->corank = corank;
10548         }
10549       if (automatic_flag && sym->attr.save == SAVE_EXPLICIT)
10550         {
10551           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10552           return FAILURE;
10553         }
10554     }
10555
10556   /* Ensure that any initializer is simplified.  */
10557   if (sym->value)
10558     gfc_simplify_expr (sym->value, 1);
10559
10560   /* Reject illegal initializers.  */
10561   if (!sym->mark && sym->value)
10562     {
10563       if (sym->attr.allocatable || (sym->ts.type == BT_CLASS
10564                                     && CLASS_DATA (sym)->attr.allocatable))
10565         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
10566                    sym->name, &sym->declared_at);
10567       else if (sym->attr.external)
10568         gfc_error ("External '%s' at %L cannot have an initializer",
10569                    sym->name, &sym->declared_at);
10570       else if (sym->attr.dummy
10571         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
10572         gfc_error ("Dummy '%s' at %L cannot have an initializer",
10573                    sym->name, &sym->declared_at);
10574       else if (sym->attr.intrinsic)
10575         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
10576                    sym->name, &sym->declared_at);
10577       else if (sym->attr.result)
10578         gfc_error ("Function result '%s' at %L cannot have an initializer",
10579                    sym->name, &sym->declared_at);
10580       else if (automatic_flag)
10581         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
10582                    sym->name, &sym->declared_at);
10583       else
10584         goto no_init_error;
10585       return FAILURE;
10586     }
10587
10588 no_init_error:
10589   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
10590     return resolve_fl_variable_derived (sym, no_init_flag);
10591
10592   return SUCCESS;
10593 }
10594
10595
10596 /* Resolve a procedure.  */
10597
10598 static gfc_try
10599 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
10600 {
10601   gfc_formal_arglist *arg;
10602
10603   if (sym->attr.function
10604       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10605     return FAILURE;
10606
10607   if (sym->ts.type == BT_CHARACTER)
10608     {
10609       gfc_charlen *cl = sym->ts.u.cl;
10610
10611       if (cl && cl->length && gfc_is_constant_expr (cl->length)
10612              && resolve_charlen (cl) == FAILURE)
10613         return FAILURE;
10614
10615       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
10616           && sym->attr.proc == PROC_ST_FUNCTION)
10617         {
10618           gfc_error ("Character-valued statement function '%s' at %L must "
10619                      "have constant length", sym->name, &sym->declared_at);
10620           return FAILURE;
10621         }
10622     }
10623
10624   /* Ensure that derived type for are not of a private type.  Internal
10625      module procedures are excluded by 2.2.3.3 - i.e., they are not
10626      externally accessible and can access all the objects accessible in
10627      the host.  */
10628   if (!(sym->ns->parent
10629         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
10630       && gfc_check_symbol_access (sym))
10631     {
10632       gfc_interface *iface;
10633
10634       for (arg = sym->formal; arg; arg = arg->next)
10635         {
10636           if (arg->sym
10637               && arg->sym->ts.type == BT_DERIVED
10638               && !arg->sym->ts.u.derived->attr.use_assoc
10639               && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10640               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
10641                                  "PRIVATE type and cannot be a dummy argument"
10642                                  " of '%s', which is PUBLIC at %L",
10643                                  arg->sym->name, sym->name, &sym->declared_at)
10644                  == FAILURE)
10645             {
10646               /* Stop this message from recurring.  */
10647               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10648               return FAILURE;
10649             }
10650         }
10651
10652       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10653          PRIVATE to the containing module.  */
10654       for (iface = sym->generic; iface; iface = iface->next)
10655         {
10656           for (arg = iface->sym->formal; arg; arg = arg->next)
10657             {
10658               if (arg->sym
10659                   && arg->sym->ts.type == BT_DERIVED
10660                   && !arg->sym->ts.u.derived->attr.use_assoc
10661                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10662                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10663                                      "'%s' in PUBLIC interface '%s' at %L "
10664                                      "takes dummy arguments of '%s' which is "
10665                                      "PRIVATE", iface->sym->name, sym->name,
10666                                      &iface->sym->declared_at,
10667                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10668                 {
10669                   /* Stop this message from recurring.  */
10670                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10671                   return FAILURE;
10672                 }
10673              }
10674         }
10675
10676       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10677          PRIVATE to the containing module.  */
10678       for (iface = sym->generic; iface; iface = iface->next)
10679         {
10680           for (arg = iface->sym->formal; arg; arg = arg->next)
10681             {
10682               if (arg->sym
10683                   && arg->sym->ts.type == BT_DERIVED
10684                   && !arg->sym->ts.u.derived->attr.use_assoc
10685                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10686                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10687                                      "'%s' in PUBLIC interface '%s' at %L "
10688                                      "takes dummy arguments of '%s' which is "
10689                                      "PRIVATE", iface->sym->name, sym->name,
10690                                      &iface->sym->declared_at,
10691                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10692                 {
10693                   /* Stop this message from recurring.  */
10694                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10695                   return FAILURE;
10696                 }
10697              }
10698         }
10699     }
10700
10701   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
10702       && !sym->attr.proc_pointer)
10703     {
10704       gfc_error ("Function '%s' at %L cannot have an initializer",
10705                  sym->name, &sym->declared_at);
10706       return FAILURE;
10707     }
10708
10709   /* An external symbol may not have an initializer because it is taken to be
10710      a procedure. Exception: Procedure Pointers.  */
10711   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
10712     {
10713       gfc_error ("External object '%s' at %L may not have an initializer",
10714                  sym->name, &sym->declared_at);
10715       return FAILURE;
10716     }
10717
10718   /* An elemental function is required to return a scalar 12.7.1  */
10719   if (sym->attr.elemental && sym->attr.function && sym->as)
10720     {
10721       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
10722                  "result", sym->name, &sym->declared_at);
10723       /* Reset so that the error only occurs once.  */
10724       sym->attr.elemental = 0;
10725       return FAILURE;
10726     }
10727
10728   if (sym->attr.proc == PROC_ST_FUNCTION
10729       && (sym->attr.allocatable || sym->attr.pointer))
10730     {
10731       gfc_error ("Statement function '%s' at %L may not have pointer or "
10732                  "allocatable attribute", sym->name, &sym->declared_at);
10733       return FAILURE;
10734     }
10735
10736   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
10737      char-len-param shall not be array-valued, pointer-valued, recursive
10738      or pure.  ....snip... A character value of * may only be used in the
10739      following ways: (i) Dummy arg of procedure - dummy associates with
10740      actual length; (ii) To declare a named constant; or (iii) External
10741      function - but length must be declared in calling scoping unit.  */
10742   if (sym->attr.function
10743       && sym->ts.type == BT_CHARACTER && !sym->ts.deferred
10744       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
10745     {
10746       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
10747           || (sym->attr.recursive) || (sym->attr.pure))
10748         {
10749           if (sym->as && sym->as->rank)
10750             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10751                        "array-valued", sym->name, &sym->declared_at);
10752
10753           if (sym->attr.pointer)
10754             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10755                        "pointer-valued", sym->name, &sym->declared_at);
10756
10757           if (sym->attr.pure)
10758             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10759                        "pure", sym->name, &sym->declared_at);
10760
10761           if (sym->attr.recursive)
10762             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10763                        "recursive", sym->name, &sym->declared_at);
10764
10765           return FAILURE;
10766         }
10767
10768       /* Appendix B.2 of the standard.  Contained functions give an
10769          error anyway.  Fixed-form is likely to be F77/legacy. Deferred
10770          character length is an F2003 feature.  */
10771       if (!sym->attr.contained
10772             && gfc_current_form != FORM_FIXED
10773             && !sym->ts.deferred)
10774         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
10775                         "CHARACTER(*) function '%s' at %L",
10776                         sym->name, &sym->declared_at);
10777     }
10778
10779   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
10780     {
10781       gfc_formal_arglist *curr_arg;
10782       int has_non_interop_arg = 0;
10783
10784       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10785                              sym->common_block) == FAILURE)
10786         {
10787           /* Clear these to prevent looking at them again if there was an
10788              error.  */
10789           sym->attr.is_bind_c = 0;
10790           sym->attr.is_c_interop = 0;
10791           sym->ts.is_c_interop = 0;
10792         }
10793       else
10794         {
10795           /* So far, no errors have been found.  */
10796           sym->attr.is_c_interop = 1;
10797           sym->ts.is_c_interop = 1;
10798         }
10799       
10800       curr_arg = sym->formal;
10801       while (curr_arg != NULL)
10802         {
10803           /* Skip implicitly typed dummy args here.  */
10804           if (curr_arg->sym->attr.implicit_type == 0)
10805             if (gfc_verify_c_interop_param (curr_arg->sym) == FAILURE)
10806               /* If something is found to fail, record the fact so we
10807                  can mark the symbol for the procedure as not being
10808                  BIND(C) to try and prevent multiple errors being
10809                  reported.  */
10810               has_non_interop_arg = 1;
10811           
10812           curr_arg = curr_arg->next;
10813         }
10814
10815       /* See if any of the arguments were not interoperable and if so, clear
10816          the procedure symbol to prevent duplicate error messages.  */
10817       if (has_non_interop_arg != 0)
10818         {
10819           sym->attr.is_c_interop = 0;
10820           sym->ts.is_c_interop = 0;
10821           sym->attr.is_bind_c = 0;
10822         }
10823     }
10824   
10825   if (!sym->attr.proc_pointer)
10826     {
10827       if (sym->attr.save == SAVE_EXPLICIT)
10828         {
10829           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
10830                      "in '%s' at %L", sym->name, &sym->declared_at);
10831           return FAILURE;
10832         }
10833       if (sym->attr.intent)
10834         {
10835           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
10836                      "in '%s' at %L", sym->name, &sym->declared_at);
10837           return FAILURE;
10838         }
10839       if (sym->attr.subroutine && sym->attr.result)
10840         {
10841           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
10842                      "in '%s' at %L", sym->name, &sym->declared_at);
10843           return FAILURE;
10844         }
10845       if (sym->attr.external && sym->attr.function
10846           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
10847               || sym->attr.contained))
10848         {
10849           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
10850                      "in '%s' at %L", sym->name, &sym->declared_at);
10851           return FAILURE;
10852         }
10853       if (strcmp ("ppr@", sym->name) == 0)
10854         {
10855           gfc_error ("Procedure pointer result '%s' at %L "
10856                      "is missing the pointer attribute",
10857                      sym->ns->proc_name->name, &sym->declared_at);
10858           return FAILURE;
10859         }
10860     }
10861
10862   return SUCCESS;
10863 }
10864
10865
10866 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
10867    been defined and we now know their defined arguments, check that they fulfill
10868    the requirements of the standard for procedures used as finalizers.  */
10869
10870 static gfc_try
10871 gfc_resolve_finalizers (gfc_symbol* derived)
10872 {
10873   gfc_finalizer* list;
10874   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
10875   gfc_try result = SUCCESS;
10876   bool seen_scalar = false;
10877
10878   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
10879     return SUCCESS;
10880
10881   /* Walk over the list of finalizer-procedures, check them, and if any one
10882      does not fit in with the standard's definition, print an error and remove
10883      it from the list.  */
10884   prev_link = &derived->f2k_derived->finalizers;
10885   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
10886     {
10887       gfc_symbol* arg;
10888       gfc_finalizer* i;
10889       int my_rank;
10890
10891       /* Skip this finalizer if we already resolved it.  */
10892       if (list->proc_tree)
10893         {
10894           prev_link = &(list->next);
10895           continue;
10896         }
10897
10898       /* Check this exists and is a SUBROUTINE.  */
10899       if (!list->proc_sym->attr.subroutine)
10900         {
10901           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
10902                      list->proc_sym->name, &list->where);
10903           goto error;
10904         }
10905
10906       /* We should have exactly one argument.  */
10907       if (!list->proc_sym->formal || list->proc_sym->formal->next)
10908         {
10909           gfc_error ("FINAL procedure at %L must have exactly one argument",
10910                      &list->where);
10911           goto error;
10912         }
10913       arg = list->proc_sym->formal->sym;
10914
10915       /* This argument must be of our type.  */
10916       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
10917         {
10918           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
10919                      &arg->declared_at, derived->name);
10920           goto error;
10921         }
10922
10923       /* It must neither be a pointer nor allocatable nor optional.  */
10924       if (arg->attr.pointer)
10925         {
10926           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
10927                      &arg->declared_at);
10928           goto error;
10929         }
10930       if (arg->attr.allocatable)
10931         {
10932           gfc_error ("Argument of FINAL procedure at %L must not be"
10933                      " ALLOCATABLE", &arg->declared_at);
10934           goto error;
10935         }
10936       if (arg->attr.optional)
10937         {
10938           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
10939                      &arg->declared_at);
10940           goto error;
10941         }
10942
10943       /* It must not be INTENT(OUT).  */
10944       if (arg->attr.intent == INTENT_OUT)
10945         {
10946           gfc_error ("Argument of FINAL procedure at %L must not be"
10947                      " INTENT(OUT)", &arg->declared_at);
10948           goto error;
10949         }
10950
10951       /* Warn if the procedure is non-scalar and not assumed shape.  */
10952       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
10953           && arg->as->type != AS_ASSUMED_SHAPE)
10954         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
10955                      " shape argument", &arg->declared_at);
10956
10957       /* Check that it does not match in kind and rank with a FINAL procedure
10958          defined earlier.  To really loop over the *earlier* declarations,
10959          we need to walk the tail of the list as new ones were pushed at the
10960          front.  */
10961       /* TODO: Handle kind parameters once they are implemented.  */
10962       my_rank = (arg->as ? arg->as->rank : 0);
10963       for (i = list->next; i; i = i->next)
10964         {
10965           /* Argument list might be empty; that is an error signalled earlier,
10966              but we nevertheless continued resolving.  */
10967           if (i->proc_sym->formal)
10968             {
10969               gfc_symbol* i_arg = i->proc_sym->formal->sym;
10970               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
10971               if (i_rank == my_rank)
10972                 {
10973                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
10974                              " rank (%d) as '%s'",
10975                              list->proc_sym->name, &list->where, my_rank, 
10976                              i->proc_sym->name);
10977                   goto error;
10978                 }
10979             }
10980         }
10981
10982         /* Is this the/a scalar finalizer procedure?  */
10983         if (!arg->as || arg->as->rank == 0)
10984           seen_scalar = true;
10985
10986         /* Find the symtree for this procedure.  */
10987         gcc_assert (!list->proc_tree);
10988         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
10989
10990         prev_link = &list->next;
10991         continue;
10992
10993         /* Remove wrong nodes immediately from the list so we don't risk any
10994            troubles in the future when they might fail later expectations.  */
10995 error:
10996         result = FAILURE;
10997         i = list;
10998         *prev_link = list->next;
10999         gfc_free_finalizer (i);
11000     }
11001
11002   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
11003      were nodes in the list, must have been for arrays.  It is surely a good
11004      idea to have a scalar version there if there's something to finalize.  */
11005   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
11006     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
11007                  " defined at %L, suggest also scalar one",
11008                  derived->name, &derived->declared_at);
11009
11010   /* TODO:  Remove this error when finalization is finished.  */
11011   gfc_error ("Finalization at %L is not yet implemented",
11012              &derived->declared_at);
11013
11014   return result;
11015 }
11016
11017
11018 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
11019
11020 static gfc_try
11021 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
11022                              const char* generic_name, locus where)
11023 {
11024   gfc_symbol *sym1, *sym2;
11025   const char *pass1, *pass2;
11026
11027   gcc_assert (t1->specific && t2->specific);
11028   gcc_assert (!t1->specific->is_generic);
11029   gcc_assert (!t2->specific->is_generic);
11030   gcc_assert (t1->is_operator == t2->is_operator);
11031
11032   sym1 = t1->specific->u.specific->n.sym;
11033   sym2 = t2->specific->u.specific->n.sym;
11034
11035   if (sym1 == sym2)
11036     return SUCCESS;
11037
11038   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
11039   if (sym1->attr.subroutine != sym2->attr.subroutine
11040       || sym1->attr.function != sym2->attr.function)
11041     {
11042       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
11043                  " GENERIC '%s' at %L",
11044                  sym1->name, sym2->name, generic_name, &where);
11045       return FAILURE;
11046     }
11047
11048   /* Compare the interfaces.  */
11049   if (t1->specific->nopass)
11050     pass1 = NULL;
11051   else if (t1->specific->pass_arg)
11052     pass1 = t1->specific->pass_arg;
11053   else
11054     pass1 = t1->specific->u.specific->n.sym->formal->sym->name;
11055   if (t2->specific->nopass)
11056     pass2 = NULL;
11057   else if (t2->specific->pass_arg)
11058     pass2 = t2->specific->pass_arg;
11059   else
11060     pass2 = t2->specific->u.specific->n.sym->formal->sym->name;  
11061   if (gfc_compare_interfaces (sym1, sym2, sym2->name, !t1->is_operator, 0,
11062                               NULL, 0, pass1, pass2))
11063     {
11064       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
11065                  sym1->name, sym2->name, generic_name, &where);
11066       return FAILURE;
11067     }
11068
11069   return SUCCESS;
11070 }
11071
11072
11073 /* Worker function for resolving a generic procedure binding; this is used to
11074    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
11075
11076    The difference between those cases is finding possible inherited bindings
11077    that are overridden, as one has to look for them in tb_sym_root,
11078    tb_uop_root or tb_op, respectively.  Thus the caller must already find
11079    the super-type and set p->overridden correctly.  */
11080
11081 static gfc_try
11082 resolve_tb_generic_targets (gfc_symbol* super_type,
11083                             gfc_typebound_proc* p, const char* name)
11084 {
11085   gfc_tbp_generic* target;
11086   gfc_symtree* first_target;
11087   gfc_symtree* inherited;
11088
11089   gcc_assert (p && p->is_generic);
11090
11091   /* Try to find the specific bindings for the symtrees in our target-list.  */
11092   gcc_assert (p->u.generic);
11093   for (target = p->u.generic; target; target = target->next)
11094     if (!target->specific)
11095       {
11096         gfc_typebound_proc* overridden_tbp;
11097         gfc_tbp_generic* g;
11098         const char* target_name;
11099
11100         target_name = target->specific_st->name;
11101
11102         /* Defined for this type directly.  */
11103         if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
11104           {
11105             target->specific = target->specific_st->n.tb;
11106             goto specific_found;
11107           }
11108
11109         /* Look for an inherited specific binding.  */
11110         if (super_type)
11111           {
11112             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
11113                                                  true, NULL);
11114
11115             if (inherited)
11116               {
11117                 gcc_assert (inherited->n.tb);
11118                 target->specific = inherited->n.tb;
11119                 goto specific_found;
11120               }
11121           }
11122
11123         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
11124                    " at %L", target_name, name, &p->where);
11125         return FAILURE;
11126
11127         /* Once we've found the specific binding, check it is not ambiguous with
11128            other specifics already found or inherited for the same GENERIC.  */
11129 specific_found:
11130         gcc_assert (target->specific);
11131
11132         /* This must really be a specific binding!  */
11133         if (target->specific->is_generic)
11134           {
11135             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
11136                        " '%s' is GENERIC, too", name, &p->where, target_name);
11137             return FAILURE;
11138           }
11139
11140         /* Check those already resolved on this type directly.  */
11141         for (g = p->u.generic; g; g = g->next)
11142           if (g != target && g->specific
11143               && check_generic_tbp_ambiguity (target, g, name, p->where)
11144                   == FAILURE)
11145             return FAILURE;
11146
11147         /* Check for ambiguity with inherited specific targets.  */
11148         for (overridden_tbp = p->overridden; overridden_tbp;
11149              overridden_tbp = overridden_tbp->overridden)
11150           if (overridden_tbp->is_generic)
11151             {
11152               for (g = overridden_tbp->u.generic; g; g = g->next)
11153                 {
11154                   gcc_assert (g->specific);
11155                   if (check_generic_tbp_ambiguity (target, g,
11156                                                    name, p->where) == FAILURE)
11157                     return FAILURE;
11158                 }
11159             }
11160       }
11161
11162   /* If we attempt to "overwrite" a specific binding, this is an error.  */
11163   if (p->overridden && !p->overridden->is_generic)
11164     {
11165       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
11166                  " the same name", name, &p->where);
11167       return FAILURE;
11168     }
11169
11170   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
11171      all must have the same attributes here.  */
11172   first_target = p->u.generic->specific->u.specific;
11173   gcc_assert (first_target);
11174   p->subroutine = first_target->n.sym->attr.subroutine;
11175   p->function = first_target->n.sym->attr.function;
11176
11177   return SUCCESS;
11178 }
11179
11180
11181 /* Resolve a GENERIC procedure binding for a derived type.  */
11182
11183 static gfc_try
11184 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
11185 {
11186   gfc_symbol* super_type;
11187
11188   /* Find the overridden binding if any.  */
11189   st->n.tb->overridden = NULL;
11190   super_type = gfc_get_derived_super_type (derived);
11191   if (super_type)
11192     {
11193       gfc_symtree* overridden;
11194       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
11195                                             true, NULL);
11196
11197       if (overridden && overridden->n.tb)
11198         st->n.tb->overridden = overridden->n.tb;
11199     }
11200
11201   /* Resolve using worker function.  */
11202   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
11203 }
11204
11205
11206 /* Retrieve the target-procedure of an operator binding and do some checks in
11207    common for intrinsic and user-defined type-bound operators.  */
11208
11209 static gfc_symbol*
11210 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
11211 {
11212   gfc_symbol* target_proc;
11213
11214   gcc_assert (target->specific && !target->specific->is_generic);
11215   target_proc = target->specific->u.specific->n.sym;
11216   gcc_assert (target_proc);
11217
11218   /* All operator bindings must have a passed-object dummy argument.  */
11219   if (target->specific->nopass)
11220     {
11221       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
11222       return NULL;
11223     }
11224
11225   return target_proc;
11226 }
11227
11228
11229 /* Resolve a type-bound intrinsic operator.  */
11230
11231 static gfc_try
11232 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
11233                                 gfc_typebound_proc* p)
11234 {
11235   gfc_symbol* super_type;
11236   gfc_tbp_generic* target;
11237   
11238   /* If there's already an error here, do nothing (but don't fail again).  */
11239   if (p->error)
11240     return SUCCESS;
11241
11242   /* Operators should always be GENERIC bindings.  */
11243   gcc_assert (p->is_generic);
11244
11245   /* Look for an overridden binding.  */
11246   super_type = gfc_get_derived_super_type (derived);
11247   if (super_type && super_type->f2k_derived)
11248     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
11249                                                      op, true, NULL);
11250   else
11251     p->overridden = NULL;
11252
11253   /* Resolve general GENERIC properties using worker function.  */
11254   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
11255     goto error;
11256
11257   /* Check the targets to be procedures of correct interface.  */
11258   for (target = p->u.generic; target; target = target->next)
11259     {
11260       gfc_symbol* target_proc;
11261
11262       target_proc = get_checked_tb_operator_target (target, p->where);
11263       if (!target_proc)
11264         goto error;
11265
11266       if (!gfc_check_operator_interface (target_proc, op, p->where))
11267         goto error;
11268
11269       /* Add target to non-typebound operator list.  */
11270       if (!target->specific->deferred && !derived->attr.use_assoc
11271           && p->access != ACCESS_PRIVATE)
11272         {
11273           gfc_interface *head, *intr;
11274           if (gfc_check_new_interface (derived->ns->op[op], target_proc,
11275                                        p->where) == FAILURE)
11276             return FAILURE;
11277           head = derived->ns->op[op];
11278           intr = gfc_get_interface ();
11279           intr->sym = target_proc;
11280           intr->where = p->where;
11281           intr->next = head;
11282           derived->ns->op[op] = intr;
11283         }
11284     }
11285
11286   return SUCCESS;
11287
11288 error:
11289   p->error = 1;
11290   return FAILURE;
11291 }
11292
11293
11294 /* Resolve a type-bound user operator (tree-walker callback).  */
11295
11296 static gfc_symbol* resolve_bindings_derived;
11297 static gfc_try resolve_bindings_result;
11298
11299 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
11300
11301 static void
11302 resolve_typebound_user_op (gfc_symtree* stree)
11303 {
11304   gfc_symbol* super_type;
11305   gfc_tbp_generic* target;
11306
11307   gcc_assert (stree && stree->n.tb);
11308
11309   if (stree->n.tb->error)
11310     return;
11311
11312   /* Operators should always be GENERIC bindings.  */
11313   gcc_assert (stree->n.tb->is_generic);
11314
11315   /* Find overridden procedure, if any.  */
11316   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11317   if (super_type && super_type->f2k_derived)
11318     {
11319       gfc_symtree* overridden;
11320       overridden = gfc_find_typebound_user_op (super_type, NULL,
11321                                                stree->name, true, NULL);
11322
11323       if (overridden && overridden->n.tb)
11324         stree->n.tb->overridden = overridden->n.tb;
11325     }
11326   else
11327     stree->n.tb->overridden = NULL;
11328
11329   /* Resolve basically using worker function.  */
11330   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
11331         == FAILURE)
11332     goto error;
11333
11334   /* Check the targets to be functions of correct interface.  */
11335   for (target = stree->n.tb->u.generic; target; target = target->next)
11336     {
11337       gfc_symbol* target_proc;
11338
11339       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
11340       if (!target_proc)
11341         goto error;
11342
11343       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
11344         goto error;
11345     }
11346
11347   return;
11348
11349 error:
11350   resolve_bindings_result = FAILURE;
11351   stree->n.tb->error = 1;
11352 }
11353
11354
11355 /* Resolve the type-bound procedures for a derived type.  */
11356
11357 static void
11358 resolve_typebound_procedure (gfc_symtree* stree)
11359 {
11360   gfc_symbol* proc;
11361   locus where;
11362   gfc_symbol* me_arg;
11363   gfc_symbol* super_type;
11364   gfc_component* comp;
11365
11366   gcc_assert (stree);
11367
11368   /* Undefined specific symbol from GENERIC target definition.  */
11369   if (!stree->n.tb)
11370     return;
11371
11372   if (stree->n.tb->error)
11373     return;
11374
11375   /* If this is a GENERIC binding, use that routine.  */
11376   if (stree->n.tb->is_generic)
11377     {
11378       if (resolve_typebound_generic (resolve_bindings_derived, stree)
11379             == FAILURE)
11380         goto error;
11381       return;
11382     }
11383
11384   /* Get the target-procedure to check it.  */
11385   gcc_assert (!stree->n.tb->is_generic);
11386   gcc_assert (stree->n.tb->u.specific);
11387   proc = stree->n.tb->u.specific->n.sym;
11388   where = stree->n.tb->where;
11389   proc->attr.public_used = 1;
11390
11391   /* Default access should already be resolved from the parser.  */
11392   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
11393
11394   /* It should be a module procedure or an external procedure with explicit
11395      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
11396   if ((!proc->attr.subroutine && !proc->attr.function)
11397       || (proc->attr.proc != PROC_MODULE
11398           && proc->attr.if_source != IFSRC_IFBODY)
11399       || (proc->attr.abstract && !stree->n.tb->deferred))
11400     {
11401       gfc_error ("'%s' must be a module procedure or an external procedure with"
11402                  " an explicit interface at %L", proc->name, &where);
11403       goto error;
11404     }
11405   stree->n.tb->subroutine = proc->attr.subroutine;
11406   stree->n.tb->function = proc->attr.function;
11407
11408   /* Find the super-type of the current derived type.  We could do this once and
11409      store in a global if speed is needed, but as long as not I believe this is
11410      more readable and clearer.  */
11411   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11412
11413   /* If PASS, resolve and check arguments if not already resolved / loaded
11414      from a .mod file.  */
11415   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
11416     {
11417       if (stree->n.tb->pass_arg)
11418         {
11419           gfc_formal_arglist* i;
11420
11421           /* If an explicit passing argument name is given, walk the arg-list
11422              and look for it.  */
11423
11424           me_arg = NULL;
11425           stree->n.tb->pass_arg_num = 1;
11426           for (i = proc->formal; i; i = i->next)
11427             {
11428               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
11429                 {
11430                   me_arg = i->sym;
11431                   break;
11432                 }
11433               ++stree->n.tb->pass_arg_num;
11434             }
11435
11436           if (!me_arg)
11437             {
11438               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
11439                          " argument '%s'",
11440                          proc->name, stree->n.tb->pass_arg, &where,
11441                          stree->n.tb->pass_arg);
11442               goto error;
11443             }
11444         }
11445       else
11446         {
11447           /* Otherwise, take the first one; there should in fact be at least
11448              one.  */
11449           stree->n.tb->pass_arg_num = 1;
11450           if (!proc->formal)
11451             {
11452               gfc_error ("Procedure '%s' with PASS at %L must have at"
11453                          " least one argument", proc->name, &where);
11454               goto error;
11455             }
11456           me_arg = proc->formal->sym;
11457         }
11458
11459       /* Now check that the argument-type matches and the passed-object
11460          dummy argument is generally fine.  */
11461
11462       gcc_assert (me_arg);
11463
11464       if (me_arg->ts.type != BT_CLASS)
11465         {
11466           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11467                      " at %L", proc->name, &where);
11468           goto error;
11469         }
11470
11471       if (CLASS_DATA (me_arg)->ts.u.derived
11472           != resolve_bindings_derived)
11473         {
11474           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11475                      " the derived-type '%s'", me_arg->name, proc->name,
11476                      me_arg->name, &where, resolve_bindings_derived->name);
11477           goto error;
11478         }
11479   
11480       gcc_assert (me_arg->ts.type == BT_CLASS);
11481       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
11482         {
11483           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
11484                      " scalar", proc->name, &where);
11485           goto error;
11486         }
11487       if (CLASS_DATA (me_arg)->attr.allocatable)
11488         {
11489           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11490                      " be ALLOCATABLE", proc->name, &where);
11491           goto error;
11492         }
11493       if (CLASS_DATA (me_arg)->attr.class_pointer)
11494         {
11495           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11496                      " be POINTER", proc->name, &where);
11497           goto error;
11498         }
11499     }
11500
11501   /* If we are extending some type, check that we don't override a procedure
11502      flagged NON_OVERRIDABLE.  */
11503   stree->n.tb->overridden = NULL;
11504   if (super_type)
11505     {
11506       gfc_symtree* overridden;
11507       overridden = gfc_find_typebound_proc (super_type, NULL,
11508                                             stree->name, true, NULL);
11509
11510       if (overridden)
11511         {
11512           if (overridden->n.tb)
11513             stree->n.tb->overridden = overridden->n.tb;
11514
11515           if (gfc_check_typebound_override (stree, overridden) == FAILURE)
11516             goto error;
11517         }
11518     }
11519
11520   /* See if there's a name collision with a component directly in this type.  */
11521   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
11522     if (!strcmp (comp->name, stree->name))
11523       {
11524         gfc_error ("Procedure '%s' at %L has the same name as a component of"
11525                    " '%s'",
11526                    stree->name, &where, resolve_bindings_derived->name);
11527         goto error;
11528       }
11529
11530   /* Try to find a name collision with an inherited component.  */
11531   if (super_type && gfc_find_component (super_type, stree->name, true, true))
11532     {
11533       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
11534                  " component of '%s'",
11535                  stree->name, &where, resolve_bindings_derived->name);
11536       goto error;
11537     }
11538
11539   stree->n.tb->error = 0;
11540   return;
11541
11542 error:
11543   resolve_bindings_result = FAILURE;
11544   stree->n.tb->error = 1;
11545 }
11546
11547
11548 static gfc_try
11549 resolve_typebound_procedures (gfc_symbol* derived)
11550 {
11551   int op;
11552   gfc_symbol* super_type;
11553
11554   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
11555     return SUCCESS;
11556   
11557   super_type = gfc_get_derived_super_type (derived);
11558   if (super_type)
11559     resolve_typebound_procedures (super_type);
11560
11561   resolve_bindings_derived = derived;
11562   resolve_bindings_result = SUCCESS;
11563
11564   /* Make sure the vtab has been generated.  */
11565   gfc_find_derived_vtab (derived);
11566
11567   if (derived->f2k_derived->tb_sym_root)
11568     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
11569                           &resolve_typebound_procedure);
11570
11571   if (derived->f2k_derived->tb_uop_root)
11572     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
11573                           &resolve_typebound_user_op);
11574
11575   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
11576     {
11577       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
11578       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
11579                                                p) == FAILURE)
11580         resolve_bindings_result = FAILURE;
11581     }
11582
11583   return resolve_bindings_result;
11584 }
11585
11586
11587 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
11588    to give all identical derived types the same backend_decl.  */
11589 static void
11590 add_dt_to_dt_list (gfc_symbol *derived)
11591 {
11592   gfc_dt_list *dt_list;
11593
11594   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
11595     if (derived == dt_list->derived)
11596       return;
11597
11598   dt_list = gfc_get_dt_list ();
11599   dt_list->next = gfc_derived_types;
11600   dt_list->derived = derived;
11601   gfc_derived_types = dt_list;
11602 }
11603
11604
11605 /* Ensure that a derived-type is really not abstract, meaning that every
11606    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
11607
11608 static gfc_try
11609 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
11610 {
11611   if (!st)
11612     return SUCCESS;
11613
11614   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
11615     return FAILURE;
11616   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
11617     return FAILURE;
11618
11619   if (st->n.tb && st->n.tb->deferred)
11620     {
11621       gfc_symtree* overriding;
11622       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
11623       if (!overriding)
11624         return FAILURE;
11625       gcc_assert (overriding->n.tb);
11626       if (overriding->n.tb->deferred)
11627         {
11628           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
11629                      " '%s' is DEFERRED and not overridden",
11630                      sub->name, &sub->declared_at, st->name);
11631           return FAILURE;
11632         }
11633     }
11634
11635   return SUCCESS;
11636 }
11637
11638 static gfc_try
11639 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
11640 {
11641   /* The algorithm used here is to recursively travel up the ancestry of sub
11642      and for each ancestor-type, check all bindings.  If any of them is
11643      DEFERRED, look it up starting from sub and see if the found (overriding)
11644      binding is not DEFERRED.
11645      This is not the most efficient way to do this, but it should be ok and is
11646      clearer than something sophisticated.  */
11647
11648   gcc_assert (ancestor && !sub->attr.abstract);
11649   
11650   if (!ancestor->attr.abstract)
11651     return SUCCESS;
11652
11653   /* Walk bindings of this ancestor.  */
11654   if (ancestor->f2k_derived)
11655     {
11656       gfc_try t;
11657       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
11658       if (t == FAILURE)
11659         return FAILURE;
11660     }
11661
11662   /* Find next ancestor type and recurse on it.  */
11663   ancestor = gfc_get_derived_super_type (ancestor);
11664   if (ancestor)
11665     return ensure_not_abstract (sub, ancestor);
11666
11667   return SUCCESS;
11668 }
11669
11670
11671 /* Resolve the components of a derived type. This does not have to wait until
11672    resolution stage, but can be done as soon as the dt declaration has been
11673    parsed.  */
11674
11675 static gfc_try
11676 resolve_fl_derived0 (gfc_symbol *sym)
11677 {
11678   gfc_symbol* super_type;
11679   gfc_component *c;
11680
11681   super_type = gfc_get_derived_super_type (sym);
11682
11683   /* F2008, C432. */
11684   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
11685     {
11686       gfc_error ("As extending type '%s' at %L has a coarray component, "
11687                  "parent type '%s' shall also have one", sym->name,
11688                  &sym->declared_at, super_type->name);
11689       return FAILURE;
11690     }
11691
11692   /* Ensure the extended type gets resolved before we do.  */
11693   if (super_type && resolve_fl_derived0 (super_type) == FAILURE)
11694     return FAILURE;
11695
11696   /* An ABSTRACT type must be extensible.  */
11697   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
11698     {
11699       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
11700                  sym->name, &sym->declared_at);
11701       return FAILURE;
11702     }
11703
11704   c = (sym->attr.is_class) ? sym->components->ts.u.derived->components
11705                            : sym->components;
11706
11707   for ( ; c != NULL; c = c->next)
11708     {
11709       /* See PRs 51550, 47545, 48654, 49050, 51075 - and 45170.  */
11710       if (c->ts.type == BT_CHARACTER && c->ts.deferred && !c->attr.function)
11711         {
11712           gfc_error ("Deferred-length character component '%s' at %L is not "
11713                      "yet supported", c->name, &c->loc);
11714           return FAILURE;
11715         }
11716
11717       /* F2008, C442.  */
11718       if ((!sym->attr.is_class || c != sym->components)
11719           && c->attr.codimension
11720           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
11721         {
11722           gfc_error ("Coarray component '%s' at %L must be allocatable with "
11723                      "deferred shape", c->name, &c->loc);
11724           return FAILURE;
11725         }
11726
11727       /* F2008, C443.  */
11728       if (c->attr.codimension && c->ts.type == BT_DERIVED
11729           && c->ts.u.derived->ts.is_iso_c)
11730         {
11731           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11732                      "shall not be a coarray", c->name, &c->loc);
11733           return FAILURE;
11734         }
11735
11736       /* F2008, C444.  */
11737       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
11738           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
11739               || c->attr.allocatable))
11740         {
11741           gfc_error ("Component '%s' at %L with coarray component "
11742                      "shall be a nonpointer, nonallocatable scalar",
11743                      c->name, &c->loc);
11744           return FAILURE;
11745         }
11746
11747       /* F2008, C448.  */
11748       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
11749         {
11750           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
11751                      "is not an array pointer", c->name, &c->loc);
11752           return FAILURE;
11753         }
11754
11755       if (c->attr.proc_pointer && c->ts.interface)
11756         {
11757           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
11758             gfc_error ("Interface '%s', used by procedure pointer component "
11759                        "'%s' at %L, is declared in a later PROCEDURE statement",
11760                        c->ts.interface->name, c->name, &c->loc);
11761
11762           /* Get the attributes from the interface (now resolved).  */
11763           if (c->ts.interface->attr.if_source
11764               || c->ts.interface->attr.intrinsic)
11765             {
11766               gfc_symbol *ifc = c->ts.interface;
11767
11768               if (ifc->formal && !ifc->formal_ns)
11769                 resolve_symbol (ifc);
11770
11771               if (ifc->attr.intrinsic)
11772                 resolve_intrinsic (ifc, &ifc->declared_at);
11773
11774               if (ifc->result)
11775                 {
11776                   c->ts = ifc->result->ts;
11777                   c->attr.allocatable = ifc->result->attr.allocatable;
11778                   c->attr.pointer = ifc->result->attr.pointer;
11779                   c->attr.dimension = ifc->result->attr.dimension;
11780                   c->as = gfc_copy_array_spec (ifc->result->as);
11781                 }
11782               else
11783                 {   
11784                   c->ts = ifc->ts;
11785                   c->attr.allocatable = ifc->attr.allocatable;
11786                   c->attr.pointer = ifc->attr.pointer;
11787                   c->attr.dimension = ifc->attr.dimension;
11788                   c->as = gfc_copy_array_spec (ifc->as);
11789                 }
11790               c->ts.interface = ifc;
11791               c->attr.function = ifc->attr.function;
11792               c->attr.subroutine = ifc->attr.subroutine;
11793               gfc_copy_formal_args_ppc (c, ifc);
11794
11795               c->attr.pure = ifc->attr.pure;
11796               c->attr.elemental = ifc->attr.elemental;
11797               c->attr.recursive = ifc->attr.recursive;
11798               c->attr.always_explicit = ifc->attr.always_explicit;
11799               c->attr.ext_attr |= ifc->attr.ext_attr;
11800               /* Replace symbols in array spec.  */
11801               if (c->as)
11802                 {
11803                   int i;
11804                   for (i = 0; i < c->as->rank; i++)
11805                     {
11806                       gfc_expr_replace_comp (c->as->lower[i], c);
11807                       gfc_expr_replace_comp (c->as->upper[i], c);
11808                     }
11809                 }
11810               /* Copy char length.  */
11811               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11812                 {
11813                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11814                   gfc_expr_replace_comp (cl->length, c);
11815                   if (cl->length && !cl->resolved
11816                         && gfc_resolve_expr (cl->length) == FAILURE)
11817                     return FAILURE;
11818                   c->ts.u.cl = cl;
11819                 }
11820             }
11821           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
11822             {
11823               gfc_error ("Interface '%s' of procedure pointer component "
11824                          "'%s' at %L must be explicit", c->ts.interface->name,
11825                          c->name, &c->loc);
11826               return FAILURE;
11827             }
11828         }
11829       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
11830         {
11831           /* Since PPCs are not implicitly typed, a PPC without an explicit
11832              interface must be a subroutine.  */
11833           gfc_add_subroutine (&c->attr, c->name, &c->loc);
11834         }
11835
11836       /* Procedure pointer components: Check PASS arg.  */
11837       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
11838           && !sym->attr.vtype)
11839         {
11840           gfc_symbol* me_arg;
11841
11842           if (c->tb->pass_arg)
11843             {
11844               gfc_formal_arglist* i;
11845
11846               /* If an explicit passing argument name is given, walk the arg-list
11847                 and look for it.  */
11848
11849               me_arg = NULL;
11850               c->tb->pass_arg_num = 1;
11851               for (i = c->formal; i; i = i->next)
11852                 {
11853                   if (!strcmp (i->sym->name, c->tb->pass_arg))
11854                     {
11855                       me_arg = i->sym;
11856                       break;
11857                     }
11858                   c->tb->pass_arg_num++;
11859                 }
11860
11861               if (!me_arg)
11862                 {
11863                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
11864                              "at %L has no argument '%s'", c->name,
11865                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
11866                   c->tb->error = 1;
11867                   return FAILURE;
11868                 }
11869             }
11870           else
11871             {
11872               /* Otherwise, take the first one; there should in fact be at least
11873                 one.  */
11874               c->tb->pass_arg_num = 1;
11875               if (!c->formal)
11876                 {
11877                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
11878                              "must have at least one argument",
11879                              c->name, &c->loc);
11880                   c->tb->error = 1;
11881                   return FAILURE;
11882                 }
11883               me_arg = c->formal->sym;
11884             }
11885
11886           /* Now check that the argument-type matches.  */
11887           gcc_assert (me_arg);
11888           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
11889               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
11890               || (me_arg->ts.type == BT_CLASS
11891                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
11892             {
11893               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11894                          " the derived type '%s'", me_arg->name, c->name,
11895                          me_arg->name, &c->loc, sym->name);
11896               c->tb->error = 1;
11897               return FAILURE;
11898             }
11899
11900           /* Check for C453.  */
11901           if (me_arg->attr.dimension)
11902             {
11903               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11904                          "must be scalar", me_arg->name, c->name, me_arg->name,
11905                          &c->loc);
11906               c->tb->error = 1;
11907               return FAILURE;
11908             }
11909
11910           if (me_arg->attr.pointer)
11911             {
11912               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11913                          "may not have the POINTER attribute", me_arg->name,
11914                          c->name, me_arg->name, &c->loc);
11915               c->tb->error = 1;
11916               return FAILURE;
11917             }
11918
11919           if (me_arg->attr.allocatable)
11920             {
11921               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11922                          "may not be ALLOCATABLE", me_arg->name, c->name,
11923                          me_arg->name, &c->loc);
11924               c->tb->error = 1;
11925               return FAILURE;
11926             }
11927
11928           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11929             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11930                        " at %L", c->name, &c->loc);
11931
11932         }
11933
11934       /* Check type-spec if this is not the parent-type component.  */
11935       if (((sym->attr.is_class
11936             && (!sym->components->ts.u.derived->attr.extension
11937                 || c != sym->components->ts.u.derived->components))
11938            || (!sym->attr.is_class
11939                && (!sym->attr.extension || c != sym->components)))
11940           && !sym->attr.vtype
11941           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11942         return FAILURE;
11943
11944       /* If this type is an extension, set the accessibility of the parent
11945          component.  */
11946       if (super_type
11947           && ((sym->attr.is_class
11948                && c == sym->components->ts.u.derived->components)
11949               || (!sym->attr.is_class && c == sym->components))
11950           && strcmp (super_type->name, c->name) == 0)
11951         c->attr.access = super_type->attr.access;
11952       
11953       /* If this type is an extension, see if this component has the same name
11954          as an inherited type-bound procedure.  */
11955       if (super_type && !sym->attr.is_class
11956           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11957         {
11958           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11959                      " inherited type-bound procedure",
11960                      c->name, sym->name, &c->loc);
11961           return FAILURE;
11962         }
11963
11964       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer
11965             && !c->ts.deferred)
11966         {
11967          if (c->ts.u.cl->length == NULL
11968              || (resolve_charlen (c->ts.u.cl) == FAILURE)
11969              || !gfc_is_constant_expr (c->ts.u.cl->length))
11970            {
11971              gfc_error ("Character length of component '%s' needs to "
11972                         "be a constant specification expression at %L",
11973                         c->name,
11974                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
11975              return FAILURE;
11976            }
11977         }
11978
11979       if (c->ts.type == BT_CHARACTER && c->ts.deferred
11980           && !c->attr.pointer && !c->attr.allocatable)
11981         {
11982           gfc_error ("Character component '%s' of '%s' at %L with deferred "
11983                      "length must be a POINTER or ALLOCATABLE",
11984                      c->name, sym->name, &c->loc);
11985           return FAILURE;
11986         }
11987
11988       if (c->ts.type == BT_DERIVED
11989           && sym->component_access != ACCESS_PRIVATE
11990           && gfc_check_symbol_access (sym)
11991           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11992           && !c->ts.u.derived->attr.use_assoc
11993           && !gfc_check_symbol_access (c->ts.u.derived)
11994           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11995                              "is a PRIVATE type and cannot be a component of "
11996                              "'%s', which is PUBLIC at %L", c->name,
11997                              sym->name, &sym->declared_at) == FAILURE)
11998         return FAILURE;
11999
12000       if ((sym->attr.sequence || sym->attr.is_bind_c) && c->ts.type == BT_CLASS)
12001         {
12002           gfc_error ("Polymorphic component %s at %L in SEQUENCE or BIND(C) "
12003                      "type %s", c->name, &c->loc, sym->name);
12004           return FAILURE;
12005         }
12006
12007       if (sym->attr.sequence)
12008         {
12009           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
12010             {
12011               gfc_error ("Component %s of SEQUENCE type declared at %L does "
12012                          "not have the SEQUENCE attribute",
12013                          c->ts.u.derived->name, &sym->declared_at);
12014               return FAILURE;
12015             }
12016         }
12017
12018       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.generic)
12019         c->ts.u.derived = gfc_find_dt_in_generic (c->ts.u.derived);
12020       else if (c->ts.type == BT_CLASS && c->attr.class_ok
12021                && CLASS_DATA (c)->ts.u.derived->attr.generic)
12022         CLASS_DATA (c)->ts.u.derived
12023                         = gfc_find_dt_in_generic (CLASS_DATA (c)->ts.u.derived);
12024
12025       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && !sym->attr.vtype
12026           && c->attr.pointer && c->ts.u.derived->components == NULL
12027           && !c->ts.u.derived->attr.zero_comp)
12028         {
12029           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
12030                      "that has not been declared", c->name, sym->name,
12031                      &c->loc);
12032           return FAILURE;
12033         }
12034
12035       if (c->ts.type == BT_CLASS && c->attr.class_ok
12036           && CLASS_DATA (c)->attr.class_pointer
12037           && CLASS_DATA (c)->ts.u.derived->components == NULL
12038           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
12039         {
12040           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
12041                      "that has not been declared", c->name, sym->name,
12042                      &c->loc);
12043           return FAILURE;
12044         }
12045
12046       /* C437.  */
12047       if (c->ts.type == BT_CLASS && c->attr.flavor != FL_PROCEDURE
12048           && (!c->attr.class_ok
12049               || !(CLASS_DATA (c)->attr.class_pointer
12050                    || CLASS_DATA (c)->attr.allocatable)))
12051         {
12052           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
12053                      "or pointer", c->name, &c->loc);
12054           return FAILURE;
12055         }
12056
12057       /* Ensure that all the derived type components are put on the
12058          derived type list; even in formal namespaces, where derived type
12059          pointer components might not have been declared.  */
12060       if (c->ts.type == BT_DERIVED
12061             && c->ts.u.derived
12062             && c->ts.u.derived->components
12063             && c->attr.pointer
12064             && sym != c->ts.u.derived)
12065         add_dt_to_dt_list (c->ts.u.derived);
12066
12067       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
12068                                            || c->attr.proc_pointer
12069                                            || c->attr.allocatable)) == FAILURE)
12070         return FAILURE;
12071     }
12072
12073   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
12074      all DEFERRED bindings are overridden.  */
12075   if (super_type && super_type->attr.abstract && !sym->attr.abstract
12076       && !sym->attr.is_class
12077       && ensure_not_abstract (sym, super_type) == FAILURE)
12078     return FAILURE;
12079
12080   /* Add derived type to the derived type list.  */
12081   add_dt_to_dt_list (sym);
12082
12083   return SUCCESS;
12084 }
12085
12086
12087 /* The following procedure does the full resolution of a derived type,
12088    including resolution of all type-bound procedures (if present). In contrast
12089    to 'resolve_fl_derived0' this can only be done after the module has been
12090    parsed completely.  */
12091
12092 static gfc_try
12093 resolve_fl_derived (gfc_symbol *sym)
12094 {
12095   gfc_symbol *gen_dt = NULL;
12096
12097   if (!sym->attr.is_class)
12098     gfc_find_symbol (sym->name, sym->ns, 0, &gen_dt);
12099   if (gen_dt && gen_dt->generic && gen_dt->generic->next
12100       && (!gen_dt->generic->sym->attr.use_assoc
12101           || gen_dt->generic->sym->module != gen_dt->generic->next->sym->module)
12102       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Generic name '%s' of "
12103                          "function '%s' at %L being the same name as derived "
12104                          "type at %L", sym->name,
12105                          gen_dt->generic->sym == sym
12106                            ? gen_dt->generic->next->sym->name
12107                            : gen_dt->generic->sym->name,
12108                          gen_dt->generic->sym == sym
12109                            ? &gen_dt->generic->next->sym->declared_at
12110                            : &gen_dt->generic->sym->declared_at,
12111                          &sym->declared_at) == FAILURE)
12112     return FAILURE;
12113
12114   if (sym->attr.is_class && sym->ts.u.derived == NULL)
12115     {
12116       /* Fix up incomplete CLASS symbols.  */
12117       gfc_component *data = gfc_find_component (sym, "_data", true, true);
12118       gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true);
12119       if (vptr->ts.u.derived == NULL)
12120         {
12121           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
12122           gcc_assert (vtab);
12123           vptr->ts.u.derived = vtab->ts.u.derived;
12124         }
12125     }
12126   
12127   if (resolve_fl_derived0 (sym) == FAILURE)
12128     return FAILURE;
12129   
12130   /* Resolve the type-bound procedures.  */
12131   if (resolve_typebound_procedures (sym) == FAILURE)
12132     return FAILURE;
12133
12134   /* Resolve the finalizer procedures.  */
12135   if (gfc_resolve_finalizers (sym) == FAILURE)
12136     return FAILURE;
12137   
12138   return SUCCESS;
12139 }
12140
12141
12142 static gfc_try
12143 resolve_fl_namelist (gfc_symbol *sym)
12144 {
12145   gfc_namelist *nl;
12146   gfc_symbol *nlsym;
12147
12148   for (nl = sym->namelist; nl; nl = nl->next)
12149     {
12150       /* Check again, the check in match only works if NAMELIST comes
12151          after the decl.  */
12152       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SIZE)
12153         {
12154           gfc_error ("Assumed size array '%s' in namelist '%s' at %L is not "
12155                      "allowed", nl->sym->name, sym->name, &sym->declared_at);
12156           return FAILURE;
12157         }
12158
12159       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
12160           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: NAMELIST array "
12161                              "object '%s' with assumed shape in namelist "
12162                              "'%s' at %L", nl->sym->name, sym->name,
12163                              &sym->declared_at) == FAILURE)
12164         return FAILURE;
12165
12166       if (is_non_constant_shape_array (nl->sym)
12167           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST array "
12168                              "object '%s' with nonconstant shape in namelist "
12169                              "'%s' at %L", nl->sym->name, sym->name,
12170                              &sym->declared_at) == FAILURE)
12171         return FAILURE;
12172
12173       if (nl->sym->ts.type == BT_CHARACTER
12174           && (nl->sym->ts.u.cl->length == NULL
12175               || !gfc_is_constant_expr (nl->sym->ts.u.cl->length))
12176           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
12177                              "'%s' with nonconstant character length in "
12178                              "namelist '%s' at %L", nl->sym->name, sym->name,
12179                              &sym->declared_at) == FAILURE)
12180         return FAILURE;
12181
12182       /* FIXME: Once UDDTIO is implemented, the following can be
12183          removed.  */
12184       if (nl->sym->ts.type == BT_CLASS)
12185         {
12186           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L is "
12187                      "polymorphic and requires a defined input/output "
12188                      "procedure", nl->sym->name, sym->name, &sym->declared_at);
12189           return FAILURE;
12190         }
12191
12192       if (nl->sym->ts.type == BT_DERIVED
12193           && (nl->sym->ts.u.derived->attr.alloc_comp
12194               || nl->sym->ts.u.derived->attr.pointer_comp))
12195         {
12196           if (gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
12197                               "'%s' in namelist '%s' at %L with ALLOCATABLE "
12198                               "or POINTER components", nl->sym->name,
12199                               sym->name, &sym->declared_at) == FAILURE)
12200             return FAILURE;
12201
12202          /* FIXME: Once UDDTIO is implemented, the following can be
12203             removed.  */
12204           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L has "
12205                      "ALLOCATABLE or POINTER components and thus requires "
12206                      "a defined input/output procedure", nl->sym->name,
12207                      sym->name, &sym->declared_at);
12208           return FAILURE;
12209         }
12210     }
12211
12212   /* Reject PRIVATE objects in a PUBLIC namelist.  */
12213   if (gfc_check_symbol_access (sym))
12214     {
12215       for (nl = sym->namelist; nl; nl = nl->next)
12216         {
12217           if (!nl->sym->attr.use_assoc
12218               && !is_sym_host_assoc (nl->sym, sym->ns)
12219               && !gfc_check_symbol_access (nl->sym))
12220             {
12221               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
12222                          "cannot be member of PUBLIC namelist '%s' at %L",
12223                          nl->sym->name, sym->name, &sym->declared_at);
12224               return FAILURE;
12225             }
12226
12227           /* Types with private components that came here by USE-association.  */
12228           if (nl->sym->ts.type == BT_DERIVED
12229               && derived_inaccessible (nl->sym->ts.u.derived))
12230             {
12231               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
12232                          "components and cannot be member of namelist '%s' at %L",
12233                          nl->sym->name, sym->name, &sym->declared_at);
12234               return FAILURE;
12235             }
12236
12237           /* Types with private components that are defined in the same module.  */
12238           if (nl->sym->ts.type == BT_DERIVED
12239               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
12240               && nl->sym->ts.u.derived->attr.private_comp)
12241             {
12242               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
12243                          "cannot be a member of PUBLIC namelist '%s' at %L",
12244                          nl->sym->name, sym->name, &sym->declared_at);
12245               return FAILURE;
12246             }
12247         }
12248     }
12249
12250
12251   /* 14.1.2 A module or internal procedure represent local entities
12252      of the same type as a namelist member and so are not allowed.  */
12253   for (nl = sym->namelist; nl; nl = nl->next)
12254     {
12255       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
12256         continue;
12257
12258       if (nl->sym->attr.function && nl->sym == nl->sym->result)
12259         if ((nl->sym == sym->ns->proc_name)
12260                ||
12261             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
12262           continue;
12263
12264       nlsym = NULL;
12265       if (nl->sym && nl->sym->name)
12266         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
12267       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
12268         {
12269           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
12270                      "attribute in '%s' at %L", nlsym->name,
12271                      &sym->declared_at);
12272           return FAILURE;
12273         }
12274     }
12275
12276   return SUCCESS;
12277 }
12278
12279
12280 static gfc_try
12281 resolve_fl_parameter (gfc_symbol *sym)
12282 {
12283   /* A parameter array's shape needs to be constant.  */
12284   if (sym->as != NULL 
12285       && (sym->as->type == AS_DEFERRED
12286           || is_non_constant_shape_array (sym)))
12287     {
12288       gfc_error ("Parameter array '%s' at %L cannot be automatic "
12289                  "or of deferred shape", sym->name, &sym->declared_at);
12290       return FAILURE;
12291     }
12292
12293   /* Make sure a parameter that has been implicitly typed still
12294      matches the implicit type, since PARAMETER statements can precede
12295      IMPLICIT statements.  */
12296   if (sym->attr.implicit_type
12297       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
12298                                                              sym->ns)))
12299     {
12300       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
12301                  "later IMPLICIT type", sym->name, &sym->declared_at);
12302       return FAILURE;
12303     }
12304
12305   /* Make sure the types of derived parameters are consistent.  This
12306      type checking is deferred until resolution because the type may
12307      refer to a derived type from the host.  */
12308   if (sym->ts.type == BT_DERIVED
12309       && !gfc_compare_types (&sym->ts, &sym->value->ts))
12310     {
12311       gfc_error ("Incompatible derived type in PARAMETER at %L",
12312                  &sym->value->where);
12313       return FAILURE;
12314     }
12315   return SUCCESS;
12316 }
12317
12318
12319 /* Do anything necessary to resolve a symbol.  Right now, we just
12320    assume that an otherwise unknown symbol is a variable.  This sort
12321    of thing commonly happens for symbols in module.  */
12322
12323 static void
12324 resolve_symbol (gfc_symbol *sym)
12325 {
12326   int check_constant, mp_flag;
12327   gfc_symtree *symtree;
12328   gfc_symtree *this_symtree;
12329   gfc_namespace *ns;
12330   gfc_component *c;
12331   symbol_attribute class_attr;
12332   gfc_array_spec *as;
12333
12334   if (sym->attr.flavor == FL_UNKNOWN
12335       || (sym->attr.flavor == FL_PROCEDURE && !sym->attr.intrinsic
12336           && !sym->attr.generic && !sym->attr.external
12337           && sym->attr.if_source == IFSRC_UNKNOWN))
12338     {
12339
12340     /* If we find that a flavorless symbol is an interface in one of the
12341        parent namespaces, find its symtree in this namespace, free the
12342        symbol and set the symtree to point to the interface symbol.  */
12343       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
12344         {
12345           symtree = gfc_find_symtree (ns->sym_root, sym->name);
12346           if (symtree && (symtree->n.sym->generic ||
12347                           (symtree->n.sym->attr.flavor == FL_PROCEDURE
12348                            && sym->ns->construct_entities)))
12349             {
12350               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
12351                                                sym->name);
12352               gfc_release_symbol (sym);
12353               symtree->n.sym->refs++;
12354               this_symtree->n.sym = symtree->n.sym;
12355               return;
12356             }
12357         }
12358
12359       /* Otherwise give it a flavor according to such attributes as
12360          it has.  */
12361       if (sym->attr.flavor == FL_UNKNOWN && sym->attr.external == 0
12362           && sym->attr.intrinsic == 0)
12363         sym->attr.flavor = FL_VARIABLE;
12364       else if (sym->attr.flavor == FL_UNKNOWN)
12365         {
12366           sym->attr.flavor = FL_PROCEDURE;
12367           if (sym->attr.dimension)
12368             sym->attr.function = 1;
12369         }
12370     }
12371
12372   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
12373     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
12374
12375   if (sym->attr.procedure && sym->ts.interface
12376       && sym->attr.if_source != IFSRC_DECL
12377       && resolve_procedure_interface (sym) == FAILURE)
12378     return;
12379
12380   if (sym->attr.is_protected && !sym->attr.proc_pointer
12381       && (sym->attr.procedure || sym->attr.external))
12382     {
12383       if (sym->attr.external)
12384         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
12385                    "at %L", &sym->declared_at);
12386       else
12387         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
12388                    "at %L", &sym->declared_at);
12389
12390       return;
12391     }
12392
12393   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
12394     return;
12395
12396   /* Symbols that are module procedures with results (functions) have
12397      the types and array specification copied for type checking in
12398      procedures that call them, as well as for saving to a module
12399      file.  These symbols can't stand the scrutiny that their results
12400      can.  */
12401   mp_flag = (sym->result != NULL && sym->result != sym);
12402
12403   /* Make sure that the intrinsic is consistent with its internal 
12404      representation. This needs to be done before assigning a default 
12405      type to avoid spurious warnings.  */
12406   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
12407       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
12408     return;
12409
12410   /* Resolve associate names.  */
12411   if (sym->assoc)
12412     resolve_assoc_var (sym, true);
12413
12414   /* Assign default type to symbols that need one and don't have one.  */
12415   if (sym->ts.type == BT_UNKNOWN)
12416     {
12417       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
12418         {
12419           gfc_set_default_type (sym, 1, NULL);
12420         }
12421
12422       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
12423           && !sym->attr.function && !sym->attr.subroutine
12424           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
12425         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
12426
12427       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12428         {
12429           /* The specific case of an external procedure should emit an error
12430              in the case that there is no implicit type.  */
12431           if (!mp_flag)
12432             gfc_set_default_type (sym, sym->attr.external, NULL);
12433           else
12434             {
12435               /* Result may be in another namespace.  */
12436               resolve_symbol (sym->result);
12437
12438               if (!sym->result->attr.proc_pointer)
12439                 {
12440                   sym->ts = sym->result->ts;
12441                   sym->as = gfc_copy_array_spec (sym->result->as);
12442                   sym->attr.dimension = sym->result->attr.dimension;
12443                   sym->attr.pointer = sym->result->attr.pointer;
12444                   sym->attr.allocatable = sym->result->attr.allocatable;
12445                   sym->attr.contiguous = sym->result->attr.contiguous;
12446                 }
12447             }
12448         }
12449     }
12450   else if (mp_flag && sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12451     gfc_resolve_array_spec (sym->result->as, false);
12452
12453   if (sym->ts.type == BT_CLASS && sym->attr.class_ok)
12454     {
12455       as = CLASS_DATA (sym)->as;
12456       class_attr = CLASS_DATA (sym)->attr;
12457       class_attr.pointer = class_attr.class_pointer;
12458     }
12459   else
12460     {
12461       class_attr = sym->attr;
12462       as = sym->as;
12463     }
12464
12465   /* F2008, C530. */
12466   if (sym->attr.contiguous
12467       && (!class_attr.dimension
12468           || (as->type != AS_ASSUMED_SHAPE && !class_attr.pointer)))
12469     {
12470       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
12471                   "array pointer or an assumed-shape array", sym->name,
12472                   &sym->declared_at);
12473       return;
12474     }
12475
12476   /* Assumed size arrays and assumed shape arrays must be dummy
12477      arguments.  Array-spec's of implied-shape should have been resolved to
12478      AS_EXPLICIT already.  */
12479
12480   if (as)
12481     {
12482       gcc_assert (as->type != AS_IMPLIED_SHAPE);
12483       if (((as->type == AS_ASSUMED_SIZE && !as->cp_was_assumed)
12484            || as->type == AS_ASSUMED_SHAPE)
12485           && sym->attr.dummy == 0)
12486         {
12487           if (as->type == AS_ASSUMED_SIZE)
12488             gfc_error ("Assumed size array at %L must be a dummy argument",
12489                        &sym->declared_at);
12490           else
12491             gfc_error ("Assumed shape array at %L must be a dummy argument",
12492                        &sym->declared_at);
12493           return;
12494         }
12495     }
12496
12497   /* Make sure symbols with known intent or optional are really dummy
12498      variable.  Because of ENTRY statement, this has to be deferred
12499      until resolution time.  */
12500
12501   if (!sym->attr.dummy
12502       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
12503     {
12504       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
12505       return;
12506     }
12507
12508   if (sym->attr.value && !sym->attr.dummy)
12509     {
12510       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
12511                  "it is not a dummy argument", sym->name, &sym->declared_at);
12512       return;
12513     }
12514
12515   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
12516     {
12517       gfc_charlen *cl = sym->ts.u.cl;
12518       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
12519         {
12520           gfc_error ("Character dummy variable '%s' at %L with VALUE "
12521                      "attribute must have constant length",
12522                      sym->name, &sym->declared_at);
12523           return;
12524         }
12525
12526       if (sym->ts.is_c_interop
12527           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
12528         {
12529           gfc_error ("C interoperable character dummy variable '%s' at %L "
12530                      "with VALUE attribute must have length one",
12531                      sym->name, &sym->declared_at);
12532           return;
12533         }
12534     }
12535
12536   if (sym->ts.type == BT_DERIVED && !sym->attr.is_iso_c
12537       && sym->ts.u.derived->attr.generic)
12538     {
12539       sym->ts.u.derived = gfc_find_dt_in_generic (sym->ts.u.derived);
12540       if (!sym->ts.u.derived)
12541         {
12542           gfc_error ("The derived type '%s' at %L is of type '%s', "
12543                      "which has not been defined", sym->name,
12544                      &sym->declared_at, sym->ts.u.derived->name);
12545           sym->ts.type = BT_UNKNOWN;
12546           return;
12547         }
12548     }
12549
12550   if (sym->ts.type == BT_ASSUMED)
12551     { 
12552       /* TS 29113, C407a.  */
12553       if (!sym->attr.dummy)
12554         {
12555           gfc_error ("Assumed type of variable %s at %L is only permitted "
12556                      "for dummy variables", sym->name, &sym->declared_at);
12557           return;
12558         }
12559       if (sym->attr.allocatable || sym->attr.codimension
12560           || sym->attr.pointer || sym->attr.value)
12561         {
12562           gfc_error ("Assumed-type variable %s at %L may not have the "
12563                      "ALLOCATABLE, CODIMENSION, POINTER or VALUE attribute",
12564                      sym->name, &sym->declared_at);
12565           return;
12566         }
12567       if (sym->attr.dimension && sym->as->type == AS_EXPLICIT)
12568         {
12569           gfc_error ("Assumed-type variable %s at %L shall not be an "
12570                      "explicit-shape array", sym->name, &sym->declared_at);
12571           return;
12572         }
12573     }
12574
12575   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
12576      do this for something that was implicitly typed because that is handled
12577      in gfc_set_default_type.  Handle dummy arguments and procedure
12578      definitions separately.  Also, anything that is use associated is not
12579      handled here but instead is handled in the module it is declared in.
12580      Finally, derived type definitions are allowed to be BIND(C) since that
12581      only implies that they're interoperable, and they are checked fully for
12582      interoperability when a variable is declared of that type.  */
12583   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
12584       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
12585       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
12586     {
12587       gfc_try t = SUCCESS;
12588       
12589       /* First, make sure the variable is declared at the
12590          module-level scope (J3/04-007, Section 15.3).  */
12591       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
12592           sym->attr.in_common == 0)
12593         {
12594           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
12595                      "is neither a COMMON block nor declared at the "
12596                      "module level scope", sym->name, &(sym->declared_at));
12597           t = FAILURE;
12598         }
12599       else if (sym->common_head != NULL)
12600         {
12601           t = verify_com_block_vars_c_interop (sym->common_head);
12602         }
12603       else
12604         {
12605           /* If type() declaration, we need to verify that the components
12606              of the given type are all C interoperable, etc.  */
12607           if (sym->ts.type == BT_DERIVED &&
12608               sym->ts.u.derived->attr.is_c_interop != 1)
12609             {
12610               /* Make sure the user marked the derived type as BIND(C).  If
12611                  not, call the verify routine.  This could print an error
12612                  for the derived type more than once if multiple variables
12613                  of that type are declared.  */
12614               if (sym->ts.u.derived->attr.is_bind_c != 1)
12615                 verify_bind_c_derived_type (sym->ts.u.derived);
12616               t = FAILURE;
12617             }
12618           
12619           /* Verify the variable itself as C interoperable if it
12620              is BIND(C).  It is not possible for this to succeed if
12621              the verify_bind_c_derived_type failed, so don't have to handle
12622              any error returned by verify_bind_c_derived_type.  */
12623           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
12624                                  sym->common_block);
12625         }
12626
12627       if (t == FAILURE)
12628         {
12629           /* clear the is_bind_c flag to prevent reporting errors more than
12630              once if something failed.  */
12631           sym->attr.is_bind_c = 0;
12632           return;
12633         }
12634     }
12635
12636   /* If a derived type symbol has reached this point, without its
12637      type being declared, we have an error.  Notice that most
12638      conditions that produce undefined derived types have already
12639      been dealt with.  However, the likes of:
12640      implicit type(t) (t) ..... call foo (t) will get us here if
12641      the type is not declared in the scope of the implicit
12642      statement. Change the type to BT_UNKNOWN, both because it is so
12643      and to prevent an ICE.  */
12644   if (sym->ts.type == BT_DERIVED && !sym->attr.is_iso_c
12645       && sym->ts.u.derived->components == NULL
12646       && !sym->ts.u.derived->attr.zero_comp)
12647     {
12648       gfc_error ("The derived type '%s' at %L is of type '%s', "
12649                  "which has not been defined", sym->name,
12650                   &sym->declared_at, sym->ts.u.derived->name);
12651       sym->ts.type = BT_UNKNOWN;
12652       return;
12653     }
12654
12655   /* Make sure that the derived type has been resolved and that the
12656      derived type is visible in the symbol's namespace, if it is a
12657      module function and is not PRIVATE.  */
12658   if (sym->ts.type == BT_DERIVED
12659         && sym->ts.u.derived->attr.use_assoc
12660         && sym->ns->proc_name
12661         && sym->ns->proc_name->attr.flavor == FL_MODULE
12662         && resolve_fl_derived (sym->ts.u.derived) == FAILURE)
12663     return;
12664
12665   /* Unless the derived-type declaration is use associated, Fortran 95
12666      does not allow public entries of private derived types.
12667      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
12668      161 in 95-006r3.  */
12669   if (sym->ts.type == BT_DERIVED
12670       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
12671       && !sym->ts.u.derived->attr.use_assoc
12672       && gfc_check_symbol_access (sym)
12673       && !gfc_check_symbol_access (sym->ts.u.derived)
12674       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
12675                          "of PRIVATE derived type '%s'",
12676                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
12677                          : "variable", sym->name, &sym->declared_at,
12678                          sym->ts.u.derived->name) == FAILURE)
12679     return;
12680
12681   /* F2008, C1302.  */
12682   if (sym->ts.type == BT_DERIVED
12683       && ((sym->ts.u.derived->from_intmod == INTMOD_ISO_FORTRAN_ENV
12684            && sym->ts.u.derived->intmod_sym_id == ISOFORTRAN_LOCK_TYPE)
12685           || sym->ts.u.derived->attr.lock_comp)
12686       && !sym->attr.codimension && !sym->ts.u.derived->attr.coarray_comp)
12687     {
12688       gfc_error ("Variable %s at %L of type LOCK_TYPE or with subcomponent of "
12689                  "type LOCK_TYPE must be a coarray", sym->name,
12690                  &sym->declared_at);
12691       return;
12692     }
12693
12694   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
12695      default initialization is defined (5.1.2.4.4).  */
12696   if (sym->ts.type == BT_DERIVED
12697       && sym->attr.dummy
12698       && sym->attr.intent == INTENT_OUT
12699       && sym->as
12700       && sym->as->type == AS_ASSUMED_SIZE)
12701     {
12702       for (c = sym->ts.u.derived->components; c; c = c->next)
12703         {
12704           if (c->initializer)
12705             {
12706               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
12707                          "ASSUMED SIZE and so cannot have a default initializer",
12708                          sym->name, &sym->declared_at);
12709               return;
12710             }
12711         }
12712     }
12713
12714   /* F2008, C542.  */
12715   if (sym->ts.type == BT_DERIVED && sym->attr.dummy
12716       && sym->attr.intent == INTENT_OUT && sym->attr.lock_comp)
12717     {
12718       gfc_error ("Dummy argument '%s' at %L of LOCK_TYPE shall not be "
12719                  "INTENT(OUT)", sym->name, &sym->declared_at);
12720       return;
12721     }
12722
12723   /* F2008, C525.  */
12724   if ((((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12725          || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12726              && CLASS_DATA (sym)->attr.coarray_comp))
12727        || class_attr.codimension)
12728       && (sym->attr.result || sym->result == sym))
12729     {
12730       gfc_error ("Function result '%s' at %L shall not be a coarray or have "
12731                  "a coarray component", sym->name, &sym->declared_at);
12732       return;
12733     }
12734
12735   /* F2008, C524.  */
12736   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
12737       && sym->ts.u.derived->ts.is_iso_c)
12738     {
12739       gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12740                  "shall not be a coarray", sym->name, &sym->declared_at);
12741       return;
12742     }
12743
12744   /* F2008, C525.  */
12745   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12746         || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12747             && CLASS_DATA (sym)->attr.coarray_comp))
12748       && (class_attr.codimension || class_attr.pointer || class_attr.dimension
12749           || class_attr.allocatable))
12750     {
12751       gfc_error ("Variable '%s' at %L with coarray component "
12752                  "shall be a nonpointer, nonallocatable scalar",
12753                  sym->name, &sym->declared_at);
12754       return;
12755     }
12756
12757   /* F2008, C526.  The function-result case was handled above.  */
12758   if (class_attr.codimension
12759       && !(class_attr.allocatable || sym->attr.dummy || sym->attr.save
12760            || sym->attr.select_type_temporary
12761            || sym->ns->save_all
12762            || sym->ns->proc_name->attr.flavor == FL_MODULE
12763            || sym->ns->proc_name->attr.is_main_program
12764            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
12765     {
12766       gfc_error ("Variable '%s' at %L is a coarray and is not ALLOCATABLE, SAVE "
12767                  "nor a dummy argument", sym->name, &sym->declared_at);
12768       return;
12769     }
12770   /* F2008, C528.  */
12771   else if (class_attr.codimension && !sym->attr.select_type_temporary
12772            && !class_attr.allocatable && as && as->cotype == AS_DEFERRED)
12773     {
12774       gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
12775                  "deferred shape", sym->name, &sym->declared_at);
12776       return;
12777     }
12778   else if (class_attr.codimension && class_attr.allocatable && as
12779            && (as->cotype != AS_DEFERRED || as->type != AS_DEFERRED))
12780     {
12781       gfc_error ("Allocatable coarray variable '%s' at %L must have "
12782                  "deferred shape", sym->name, &sym->declared_at);
12783       return;
12784     }
12785
12786   /* F2008, C541.  */
12787   if ((((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12788         || (sym->ts.type == BT_CLASS && sym->attr.class_ok
12789             && CLASS_DATA (sym)->attr.coarray_comp))
12790        || (class_attr.codimension && class_attr.allocatable))
12791       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
12792     {
12793       gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
12794                  "allocatable coarray or have coarray components",
12795                  sym->name, &sym->declared_at);
12796       return;
12797     }
12798
12799   if (class_attr.codimension && sym->attr.dummy
12800       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
12801     {
12802       gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
12803                  "procedure '%s'", sym->name, &sym->declared_at,
12804                  sym->ns->proc_name->name);
12805       return;
12806     }
12807
12808   switch (sym->attr.flavor)
12809     {
12810     case FL_VARIABLE:
12811       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
12812         return;
12813       break;
12814
12815     case FL_PROCEDURE:
12816       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
12817         return;
12818       break;
12819
12820     case FL_NAMELIST:
12821       if (resolve_fl_namelist (sym) == FAILURE)
12822         return;
12823       break;
12824
12825     case FL_PARAMETER:
12826       if (resolve_fl_parameter (sym) == FAILURE)
12827         return;
12828       break;
12829
12830     default:
12831       break;
12832     }
12833
12834   /* Resolve array specifier. Check as well some constraints
12835      on COMMON blocks.  */
12836
12837   check_constant = sym->attr.in_common && !sym->attr.pointer;
12838
12839   /* Set the formal_arg_flag so that check_conflict will not throw
12840      an error for host associated variables in the specification
12841      expression for an array_valued function.  */
12842   if (sym->attr.function && sym->as)
12843     formal_arg_flag = 1;
12844
12845   gfc_resolve_array_spec (sym->as, check_constant);
12846
12847   formal_arg_flag = 0;
12848
12849   /* Resolve formal namespaces.  */
12850   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
12851       && !sym->attr.contained && !sym->attr.intrinsic)
12852     gfc_resolve (sym->formal_ns);
12853
12854   /* Make sure the formal namespace is present.  */
12855   if (sym->formal && !sym->formal_ns)
12856     {
12857       gfc_formal_arglist *formal = sym->formal;
12858       while (formal && !formal->sym)
12859         formal = formal->next;
12860
12861       if (formal)
12862         {
12863           sym->formal_ns = formal->sym->ns;
12864           sym->formal_ns->refs++;
12865         }
12866     }
12867
12868   /* Check threadprivate restrictions.  */
12869   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
12870       && (!sym->attr.in_common
12871           && sym->module == NULL
12872           && (sym->ns->proc_name == NULL
12873               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
12874     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
12875
12876   /* If we have come this far we can apply default-initializers, as
12877      described in 14.7.5, to those variables that have not already
12878      been assigned one.  */
12879   if (sym->ts.type == BT_DERIVED
12880       && sym->ns == gfc_current_ns
12881       && !sym->value
12882       && !sym->attr.allocatable
12883       && !sym->attr.alloc_comp)
12884     {
12885       symbol_attribute *a = &sym->attr;
12886
12887       if ((!a->save && !a->dummy && !a->pointer
12888            && !a->in_common && !a->use_assoc
12889            && (a->referenced || a->result)
12890            && !(a->function && sym != sym->result))
12891           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
12892         apply_default_init (sym);
12893     }
12894
12895   if (sym->ts.type == BT_CLASS && sym->ns == gfc_current_ns
12896       && sym->attr.dummy && sym->attr.intent == INTENT_OUT
12897       && !CLASS_DATA (sym)->attr.class_pointer
12898       && !CLASS_DATA (sym)->attr.allocatable)
12899     apply_default_init (sym);
12900
12901   /* If this symbol has a type-spec, check it.  */
12902   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
12903       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
12904     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
12905           == FAILURE)
12906       return;
12907 }
12908
12909
12910 /************* Resolve DATA statements *************/
12911
12912 static struct
12913 {
12914   gfc_data_value *vnode;
12915   mpz_t left;
12916 }
12917 values;
12918
12919
12920 /* Advance the values structure to point to the next value in the data list.  */
12921
12922 static gfc_try
12923 next_data_value (void)
12924 {
12925   while (mpz_cmp_ui (values.left, 0) == 0)
12926     {
12927
12928       if (values.vnode->next == NULL)
12929         return FAILURE;
12930
12931       values.vnode = values.vnode->next;
12932       mpz_set (values.left, values.vnode->repeat);
12933     }
12934
12935   return SUCCESS;
12936 }
12937
12938
12939 static gfc_try
12940 check_data_variable (gfc_data_variable *var, locus *where)
12941 {
12942   gfc_expr *e;
12943   mpz_t size;
12944   mpz_t offset;
12945   gfc_try t;
12946   ar_type mark = AR_UNKNOWN;
12947   int i;
12948   mpz_t section_index[GFC_MAX_DIMENSIONS];
12949   gfc_ref *ref;
12950   gfc_array_ref *ar;
12951   gfc_symbol *sym;
12952   int has_pointer;
12953
12954   if (gfc_resolve_expr (var->expr) == FAILURE)
12955     return FAILURE;
12956
12957   ar = NULL;
12958   mpz_init_set_si (offset, 0);
12959   e = var->expr;
12960
12961   if (e->expr_type != EXPR_VARIABLE)
12962     gfc_internal_error ("check_data_variable(): Bad expression");
12963
12964   sym = e->symtree->n.sym;
12965
12966   if (sym->ns->is_block_data && !sym->attr.in_common)
12967     {
12968       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
12969                  sym->name, &sym->declared_at);
12970     }
12971
12972   if (e->ref == NULL && sym->as)
12973     {
12974       gfc_error ("DATA array '%s' at %L must be specified in a previous"
12975                  " declaration", sym->name, where);
12976       return FAILURE;
12977     }
12978
12979   has_pointer = sym->attr.pointer;
12980
12981   if (gfc_is_coindexed (e))
12982     {
12983       gfc_error ("DATA element '%s' at %L cannot have a coindex", sym->name,
12984                  where);
12985       return FAILURE;
12986     }
12987
12988   for (ref = e->ref; ref; ref = ref->next)
12989     {
12990       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
12991         has_pointer = 1;
12992
12993       if (has_pointer
12994             && ref->type == REF_ARRAY
12995             && ref->u.ar.type != AR_FULL)
12996           {
12997             gfc_error ("DATA element '%s' at %L is a pointer and so must "
12998                         "be a full array", sym->name, where);
12999             return FAILURE;
13000           }
13001     }
13002
13003   if (e->rank == 0 || has_pointer)
13004     {
13005       mpz_init_set_ui (size, 1);
13006       ref = NULL;
13007     }
13008   else
13009     {
13010       ref = e->ref;
13011
13012       /* Find the array section reference.  */
13013       for (ref = e->ref; ref; ref = ref->next)
13014         {
13015           if (ref->type != REF_ARRAY)
13016             continue;
13017           if (ref->u.ar.type == AR_ELEMENT)
13018             continue;
13019           break;
13020         }
13021       gcc_assert (ref);
13022
13023       /* Set marks according to the reference pattern.  */
13024       switch (ref->u.ar.type)
13025         {
13026         case AR_FULL:
13027           mark = AR_FULL;
13028           break;
13029
13030         case AR_SECTION:
13031           ar = &ref->u.ar;
13032           /* Get the start position of array section.  */
13033           gfc_get_section_index (ar, section_index, &offset);
13034           mark = AR_SECTION;
13035           break;
13036
13037         default:
13038           gcc_unreachable ();
13039         }
13040
13041       if (gfc_array_size (e, &size) == FAILURE)
13042         {
13043           gfc_error ("Nonconstant array section at %L in DATA statement",
13044                      &e->where);
13045           mpz_clear (offset);
13046           return FAILURE;
13047         }
13048     }
13049
13050   t = SUCCESS;
13051
13052   while (mpz_cmp_ui (size, 0) > 0)
13053     {
13054       if (next_data_value () == FAILURE)
13055         {
13056           gfc_error ("DATA statement at %L has more variables than values",
13057                      where);
13058           t = FAILURE;
13059           break;
13060         }
13061
13062       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
13063       if (t == FAILURE)
13064         break;
13065
13066       /* If we have more than one element left in the repeat count,
13067          and we have more than one element left in the target variable,
13068          then create a range assignment.  */
13069       /* FIXME: Only done for full arrays for now, since array sections
13070          seem tricky.  */
13071       if (mark == AR_FULL && ref && ref->next == NULL
13072           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
13073         {
13074           mpz_t range;
13075
13076           if (mpz_cmp (size, values.left) >= 0)
13077             {
13078               mpz_init_set (range, values.left);
13079               mpz_sub (size, size, values.left);
13080               mpz_set_ui (values.left, 0);
13081             }
13082           else
13083             {
13084               mpz_init_set (range, size);
13085               mpz_sub (values.left, values.left, size);
13086               mpz_set_ui (size, 0);
13087             }
13088
13089           t = gfc_assign_data_value (var->expr, values.vnode->expr,
13090                                      offset, &range);
13091
13092           mpz_add (offset, offset, range);
13093           mpz_clear (range);
13094
13095           if (t == FAILURE)
13096             break;
13097         }
13098
13099       /* Assign initial value to symbol.  */
13100       else
13101         {
13102           mpz_sub_ui (values.left, values.left, 1);
13103           mpz_sub_ui (size, size, 1);
13104
13105           t = gfc_assign_data_value (var->expr, values.vnode->expr,
13106                                      offset, NULL);
13107           if (t == FAILURE)
13108             break;
13109
13110           if (mark == AR_FULL)
13111             mpz_add_ui (offset, offset, 1);
13112
13113           /* Modify the array section indexes and recalculate the offset
13114              for next element.  */
13115           else if (mark == AR_SECTION)
13116             gfc_advance_section (section_index, ar, &offset);
13117         }
13118     }
13119
13120   if (mark == AR_SECTION)
13121     {
13122       for (i = 0; i < ar->dimen; i++)
13123         mpz_clear (section_index[i]);
13124     }
13125
13126   mpz_clear (size);
13127   mpz_clear (offset);
13128
13129   return t;
13130 }
13131
13132
13133 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
13134
13135 /* Iterate over a list of elements in a DATA statement.  */
13136
13137 static gfc_try
13138 traverse_data_list (gfc_data_variable *var, locus *where)
13139 {
13140   mpz_t trip;
13141   iterator_stack frame;
13142   gfc_expr *e, *start, *end, *step;
13143   gfc_try retval = SUCCESS;
13144
13145   mpz_init (frame.value);
13146   mpz_init (trip);
13147
13148   start = gfc_copy_expr (var->iter.start);
13149   end = gfc_copy_expr (var->iter.end);
13150   step = gfc_copy_expr (var->iter.step);
13151
13152   if (gfc_simplify_expr (start, 1) == FAILURE
13153       || start->expr_type != EXPR_CONSTANT)
13154     {
13155       gfc_error ("start of implied-do loop at %L could not be "
13156                  "simplified to a constant value", &start->where);
13157       retval = FAILURE;
13158       goto cleanup;
13159     }
13160   if (gfc_simplify_expr (end, 1) == FAILURE
13161       || end->expr_type != EXPR_CONSTANT)
13162     {
13163       gfc_error ("end of implied-do loop at %L could not be "
13164                  "simplified to a constant value", &start->where);
13165       retval = FAILURE;
13166       goto cleanup;
13167     }
13168   if (gfc_simplify_expr (step, 1) == FAILURE
13169       || step->expr_type != EXPR_CONSTANT)
13170     {
13171       gfc_error ("step of implied-do loop at %L could not be "
13172                  "simplified to a constant value", &start->where);
13173       retval = FAILURE;
13174       goto cleanup;
13175     }
13176
13177   mpz_set (trip, end->value.integer);
13178   mpz_sub (trip, trip, start->value.integer);
13179   mpz_add (trip, trip, step->value.integer);
13180
13181   mpz_div (trip, trip, step->value.integer);
13182
13183   mpz_set (frame.value, start->value.integer);
13184
13185   frame.prev = iter_stack;
13186   frame.variable = var->iter.var->symtree;
13187   iter_stack = &frame;
13188
13189   while (mpz_cmp_ui (trip, 0) > 0)
13190     {
13191       if (traverse_data_var (var->list, where) == FAILURE)
13192         {
13193           retval = FAILURE;
13194           goto cleanup;
13195         }
13196
13197       e = gfc_copy_expr (var->expr);
13198       if (gfc_simplify_expr (e, 1) == FAILURE)
13199         {
13200           gfc_free_expr (e);
13201           retval = FAILURE;
13202           goto cleanup;
13203         }
13204
13205       mpz_add (frame.value, frame.value, step->value.integer);
13206
13207       mpz_sub_ui (trip, trip, 1);
13208     }
13209
13210 cleanup:
13211   mpz_clear (frame.value);
13212   mpz_clear (trip);
13213
13214   gfc_free_expr (start);
13215   gfc_free_expr (end);
13216   gfc_free_expr (step);
13217
13218   iter_stack = frame.prev;
13219   return retval;
13220 }
13221
13222
13223 /* Type resolve variables in the variable list of a DATA statement.  */
13224
13225 static gfc_try
13226 traverse_data_var (gfc_data_variable *var, locus *where)
13227 {
13228   gfc_try t;
13229
13230   for (; var; var = var->next)
13231     {
13232       if (var->expr == NULL)
13233         t = traverse_data_list (var, where);
13234       else
13235         t = check_data_variable (var, where);
13236
13237       if (t == FAILURE)
13238         return FAILURE;
13239     }
13240
13241   return SUCCESS;
13242 }
13243
13244
13245 /* Resolve the expressions and iterators associated with a data statement.
13246    This is separate from the assignment checking because data lists should
13247    only be resolved once.  */
13248
13249 static gfc_try
13250 resolve_data_variables (gfc_data_variable *d)
13251 {
13252   for (; d; d = d->next)
13253     {
13254       if (d->list == NULL)
13255         {
13256           if (gfc_resolve_expr (d->expr) == FAILURE)
13257             return FAILURE;
13258         }
13259       else
13260         {
13261           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
13262             return FAILURE;
13263
13264           if (resolve_data_variables (d->list) == FAILURE)
13265             return FAILURE;
13266         }
13267     }
13268
13269   return SUCCESS;
13270 }
13271
13272
13273 /* Resolve a single DATA statement.  We implement this by storing a pointer to
13274    the value list into static variables, and then recursively traversing the
13275    variables list, expanding iterators and such.  */
13276
13277 static void
13278 resolve_data (gfc_data *d)
13279 {
13280
13281   if (resolve_data_variables (d->var) == FAILURE)
13282     return;
13283
13284   values.vnode = d->value;
13285   if (d->value == NULL)
13286     mpz_set_ui (values.left, 0);
13287   else
13288     mpz_set (values.left, d->value->repeat);
13289
13290   if (traverse_data_var (d->var, &d->where) == FAILURE)
13291     return;
13292
13293   /* At this point, we better not have any values left.  */
13294
13295   if (next_data_value () == SUCCESS)
13296     gfc_error ("DATA statement at %L has more values than variables",
13297                &d->where);
13298 }
13299
13300
13301 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
13302    accessed by host or use association, is a dummy argument to a pure function,
13303    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
13304    is storage associated with any such variable, shall not be used in the
13305    following contexts: (clients of this function).  */
13306
13307 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
13308    procedure.  Returns zero if assignment is OK, nonzero if there is a
13309    problem.  */
13310 int
13311 gfc_impure_variable (gfc_symbol *sym)
13312 {
13313   gfc_symbol *proc;
13314   gfc_namespace *ns;
13315
13316   if (sym->attr.use_assoc || sym->attr.in_common)
13317     return 1;
13318
13319   /* Check if the symbol's ns is inside the pure procedure.  */
13320   for (ns = gfc_current_ns; ns; ns = ns->parent)
13321     {
13322       if (ns == sym->ns)
13323         break;
13324       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
13325         return 1;
13326     }
13327
13328   proc = sym->ns->proc_name;
13329   if (sym->attr.dummy && gfc_pure (proc)
13330         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
13331                 ||
13332              proc->attr.function))
13333     return 1;
13334
13335   /* TODO: Sort out what can be storage associated, if anything, and include
13336      it here.  In principle equivalences should be scanned but it does not
13337      seem to be possible to storage associate an impure variable this way.  */
13338   return 0;
13339 }
13340
13341
13342 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
13343    current namespace is inside a pure procedure.  */
13344
13345 int
13346 gfc_pure (gfc_symbol *sym)
13347 {
13348   symbol_attribute attr;
13349   gfc_namespace *ns;
13350
13351   if (sym == NULL)
13352     {
13353       /* Check if the current namespace or one of its parents
13354         belongs to a pure procedure.  */
13355       for (ns = gfc_current_ns; ns; ns = ns->parent)
13356         {
13357           sym = ns->proc_name;
13358           if (sym == NULL)
13359             return 0;
13360           attr = sym->attr;
13361           if (attr.flavor == FL_PROCEDURE && attr.pure)
13362             return 1;
13363         }
13364       return 0;
13365     }
13366
13367   attr = sym->attr;
13368
13369   return attr.flavor == FL_PROCEDURE && attr.pure;
13370 }
13371
13372
13373 /* Test whether a symbol is implicitly pure or not.  For a NULL pointer,
13374    checks if the current namespace is implicitly pure.  Note that this
13375    function returns false for a PURE procedure.  */
13376
13377 int
13378 gfc_implicit_pure (gfc_symbol *sym)
13379 {
13380   gfc_namespace *ns;
13381
13382   if (sym == NULL)
13383     {
13384       /* Check if the current procedure is implicit_pure.  Walk up
13385          the procedure list until we find a procedure.  */
13386       for (ns = gfc_current_ns; ns; ns = ns->parent)
13387         {
13388           sym = ns->proc_name;
13389           if (sym == NULL)
13390             return 0;
13391           
13392           if (sym->attr.flavor == FL_PROCEDURE)
13393             break;
13394         }
13395     }
13396   
13397   return sym->attr.flavor == FL_PROCEDURE && sym->attr.implicit_pure
13398     && !sym->attr.pure;
13399 }
13400
13401
13402 /* Test whether the current procedure is elemental or not.  */
13403
13404 int
13405 gfc_elemental (gfc_symbol *sym)
13406 {
13407   symbol_attribute attr;
13408
13409   if (sym == NULL)
13410     sym = gfc_current_ns->proc_name;
13411   if (sym == NULL)
13412     return 0;
13413   attr = sym->attr;
13414
13415   return attr.flavor == FL_PROCEDURE && attr.elemental;
13416 }
13417
13418
13419 /* Warn about unused labels.  */
13420
13421 static void
13422 warn_unused_fortran_label (gfc_st_label *label)
13423 {
13424   if (label == NULL)
13425     return;
13426
13427   warn_unused_fortran_label (label->left);
13428
13429   if (label->defined == ST_LABEL_UNKNOWN)
13430     return;
13431
13432   switch (label->referenced)
13433     {
13434     case ST_LABEL_UNKNOWN:
13435       gfc_warning ("Label %d at %L defined but not used", label->value,
13436                    &label->where);
13437       break;
13438
13439     case ST_LABEL_BAD_TARGET:
13440       gfc_warning ("Label %d at %L defined but cannot be used",
13441                    label->value, &label->where);
13442       break;
13443
13444     default:
13445       break;
13446     }
13447
13448   warn_unused_fortran_label (label->right);
13449 }
13450
13451
13452 /* Returns the sequence type of a symbol or sequence.  */
13453
13454 static seq_type
13455 sequence_type (gfc_typespec ts)
13456 {
13457   seq_type result;
13458   gfc_component *c;
13459
13460   switch (ts.type)
13461   {
13462     case BT_DERIVED:
13463
13464       if (ts.u.derived->components == NULL)
13465         return SEQ_NONDEFAULT;
13466
13467       result = sequence_type (ts.u.derived->components->ts);
13468       for (c = ts.u.derived->components->next; c; c = c->next)
13469         if (sequence_type (c->ts) != result)
13470           return SEQ_MIXED;
13471
13472       return result;
13473
13474     case BT_CHARACTER:
13475       if (ts.kind != gfc_default_character_kind)
13476           return SEQ_NONDEFAULT;
13477
13478       return SEQ_CHARACTER;
13479
13480     case BT_INTEGER:
13481       if (ts.kind != gfc_default_integer_kind)
13482           return SEQ_NONDEFAULT;
13483
13484       return SEQ_NUMERIC;
13485
13486     case BT_REAL:
13487       if (!(ts.kind == gfc_default_real_kind
13488             || ts.kind == gfc_default_double_kind))
13489           return SEQ_NONDEFAULT;
13490
13491       return SEQ_NUMERIC;
13492
13493     case BT_COMPLEX:
13494       if (ts.kind != gfc_default_complex_kind)
13495           return SEQ_NONDEFAULT;
13496
13497       return SEQ_NUMERIC;
13498
13499     case BT_LOGICAL:
13500       if (ts.kind != gfc_default_logical_kind)
13501           return SEQ_NONDEFAULT;
13502
13503       return SEQ_NUMERIC;
13504
13505     default:
13506       return SEQ_NONDEFAULT;
13507   }
13508 }
13509
13510
13511 /* Resolve derived type EQUIVALENCE object.  */
13512
13513 static gfc_try
13514 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
13515 {
13516   gfc_component *c = derived->components;
13517
13518   if (!derived)
13519     return SUCCESS;
13520
13521   /* Shall not be an object of nonsequence derived type.  */
13522   if (!derived->attr.sequence)
13523     {
13524       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
13525                  "attribute to be an EQUIVALENCE object", sym->name,
13526                  &e->where);
13527       return FAILURE;
13528     }
13529
13530   /* Shall not have allocatable components.  */
13531   if (derived->attr.alloc_comp)
13532     {
13533       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
13534                  "components to be an EQUIVALENCE object",sym->name,
13535                  &e->where);
13536       return FAILURE;
13537     }
13538
13539   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
13540     {
13541       gfc_error ("Derived type variable '%s' at %L with default "
13542                  "initialization cannot be in EQUIVALENCE with a variable "
13543                  "in COMMON", sym->name, &e->where);
13544       return FAILURE;
13545     }
13546
13547   for (; c ; c = c->next)
13548     {
13549       if (c->ts.type == BT_DERIVED
13550           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
13551         return FAILURE;
13552
13553       /* Shall not be an object of sequence derived type containing a pointer
13554          in the structure.  */
13555       if (c->attr.pointer)
13556         {
13557           gfc_error ("Derived type variable '%s' at %L with pointer "
13558                      "component(s) cannot be an EQUIVALENCE object",
13559                      sym->name, &e->where);
13560           return FAILURE;
13561         }
13562     }
13563   return SUCCESS;
13564 }
13565
13566
13567 /* Resolve equivalence object. 
13568    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
13569    an allocatable array, an object of nonsequence derived type, an object of
13570    sequence derived type containing a pointer at any level of component
13571    selection, an automatic object, a function name, an entry name, a result
13572    name, a named constant, a structure component, or a subobject of any of
13573    the preceding objects.  A substring shall not have length zero.  A
13574    derived type shall not have components with default initialization nor
13575    shall two objects of an equivalence group be initialized.
13576    Either all or none of the objects shall have an protected attribute.
13577    The simple constraints are done in symbol.c(check_conflict) and the rest
13578    are implemented here.  */
13579
13580 static void
13581 resolve_equivalence (gfc_equiv *eq)
13582 {
13583   gfc_symbol *sym;
13584   gfc_symbol *first_sym;
13585   gfc_expr *e;
13586   gfc_ref *r;
13587   locus *last_where = NULL;
13588   seq_type eq_type, last_eq_type;
13589   gfc_typespec *last_ts;
13590   int object, cnt_protected;
13591   const char *msg;
13592
13593   last_ts = &eq->expr->symtree->n.sym->ts;
13594
13595   first_sym = eq->expr->symtree->n.sym;
13596
13597   cnt_protected = 0;
13598
13599   for (object = 1; eq; eq = eq->eq, object++)
13600     {
13601       e = eq->expr;
13602
13603       e->ts = e->symtree->n.sym->ts;
13604       /* match_varspec might not know yet if it is seeing
13605          array reference or substring reference, as it doesn't
13606          know the types.  */
13607       if (e->ref && e->ref->type == REF_ARRAY)
13608         {
13609           gfc_ref *ref = e->ref;
13610           sym = e->symtree->n.sym;
13611
13612           if (sym->attr.dimension)
13613             {
13614               ref->u.ar.as = sym->as;
13615               ref = ref->next;
13616             }
13617
13618           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
13619           if (e->ts.type == BT_CHARACTER
13620               && ref
13621               && ref->type == REF_ARRAY
13622               && ref->u.ar.dimen == 1
13623               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
13624               && ref->u.ar.stride[0] == NULL)
13625             {
13626               gfc_expr *start = ref->u.ar.start[0];
13627               gfc_expr *end = ref->u.ar.end[0];
13628               void *mem = NULL;
13629
13630               /* Optimize away the (:) reference.  */
13631               if (start == NULL && end == NULL)
13632                 {
13633                   if (e->ref == ref)
13634                     e->ref = ref->next;
13635                   else
13636                     e->ref->next = ref->next;
13637                   mem = ref;
13638                 }
13639               else
13640                 {
13641                   ref->type = REF_SUBSTRING;
13642                   if (start == NULL)
13643                     start = gfc_get_int_expr (gfc_default_integer_kind,
13644                                               NULL, 1);
13645                   ref->u.ss.start = start;
13646                   if (end == NULL && e->ts.u.cl)
13647                     end = gfc_copy_expr (e->ts.u.cl->length);
13648                   ref->u.ss.end = end;
13649                   ref->u.ss.length = e->ts.u.cl;
13650                   e->ts.u.cl = NULL;
13651                 }
13652               ref = ref->next;
13653               free (mem);
13654             }
13655
13656           /* Any further ref is an error.  */
13657           if (ref)
13658             {
13659               gcc_assert (ref->type == REF_ARRAY);
13660               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
13661                          &ref->u.ar.where);
13662               continue;
13663             }
13664         }
13665
13666       if (gfc_resolve_expr (e) == FAILURE)
13667         continue;
13668
13669       sym = e->symtree->n.sym;
13670
13671       if (sym->attr.is_protected)
13672         cnt_protected++;
13673       if (cnt_protected > 0 && cnt_protected != object)
13674         {
13675               gfc_error ("Either all or none of the objects in the "
13676                          "EQUIVALENCE set at %L shall have the "
13677                          "PROTECTED attribute",
13678                          &e->where);
13679               break;
13680         }
13681
13682       /* Shall not equivalence common block variables in a PURE procedure.  */
13683       if (sym->ns->proc_name
13684           && sym->ns->proc_name->attr.pure
13685           && sym->attr.in_common)
13686         {
13687           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
13688                      "object in the pure procedure '%s'",
13689                      sym->name, &e->where, sym->ns->proc_name->name);
13690           break;
13691         }
13692
13693       /* Shall not be a named constant.  */
13694       if (e->expr_type == EXPR_CONSTANT)
13695         {
13696           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
13697                      "object", sym->name, &e->where);
13698           continue;
13699         }
13700
13701       if (e->ts.type == BT_DERIVED
13702           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
13703         continue;
13704
13705       /* Check that the types correspond correctly:
13706          Note 5.28:
13707          A numeric sequence structure may be equivalenced to another sequence
13708          structure, an object of default integer type, default real type, double
13709          precision real type, default logical type such that components of the
13710          structure ultimately only become associated to objects of the same
13711          kind. A character sequence structure may be equivalenced to an object
13712          of default character kind or another character sequence structure.
13713          Other objects may be equivalenced only to objects of the same type and
13714          kind parameters.  */
13715
13716       /* Identical types are unconditionally OK.  */
13717       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
13718         goto identical_types;
13719
13720       last_eq_type = sequence_type (*last_ts);
13721       eq_type = sequence_type (sym->ts);
13722
13723       /* Since the pair of objects is not of the same type, mixed or
13724          non-default sequences can be rejected.  */
13725
13726       msg = "Sequence %s with mixed components in EQUIVALENCE "
13727             "statement at %L with different type objects";
13728       if ((object ==2
13729            && last_eq_type == SEQ_MIXED
13730            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
13731               == FAILURE)
13732           || (eq_type == SEQ_MIXED
13733               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13734                                  &e->where) == FAILURE))
13735         continue;
13736
13737       msg = "Non-default type object or sequence %s in EQUIVALENCE "
13738             "statement at %L with objects of different type";
13739       if ((object ==2
13740            && last_eq_type == SEQ_NONDEFAULT
13741            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
13742                               last_where) == FAILURE)
13743           || (eq_type == SEQ_NONDEFAULT
13744               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13745                                  &e->where) == FAILURE))
13746         continue;
13747
13748       msg ="Non-CHARACTER object '%s' in default CHARACTER "
13749            "EQUIVALENCE statement at %L";
13750       if (last_eq_type == SEQ_CHARACTER
13751           && eq_type != SEQ_CHARACTER
13752           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13753                              &e->where) == FAILURE)
13754                 continue;
13755
13756       msg ="Non-NUMERIC object '%s' in default NUMERIC "
13757            "EQUIVALENCE statement at %L";
13758       if (last_eq_type == SEQ_NUMERIC
13759           && eq_type != SEQ_NUMERIC
13760           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13761                              &e->where) == FAILURE)
13762                 continue;
13763
13764   identical_types:
13765       last_ts =&sym->ts;
13766       last_where = &e->where;
13767
13768       if (!e->ref)
13769         continue;
13770
13771       /* Shall not be an automatic array.  */
13772       if (e->ref->type == REF_ARRAY
13773           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
13774         {
13775           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
13776                      "an EQUIVALENCE object", sym->name, &e->where);
13777           continue;
13778         }
13779
13780       r = e->ref;
13781       while (r)
13782         {
13783           /* Shall not be a structure component.  */
13784           if (r->type == REF_COMPONENT)
13785             {
13786               gfc_error ("Structure component '%s' at %L cannot be an "
13787                          "EQUIVALENCE object",
13788                          r->u.c.component->name, &e->where);
13789               break;
13790             }
13791
13792           /* A substring shall not have length zero.  */
13793           if (r->type == REF_SUBSTRING)
13794             {
13795               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
13796                 {
13797                   gfc_error ("Substring at %L has length zero",
13798                              &r->u.ss.start->where);
13799                   break;
13800                 }
13801             }
13802           r = r->next;
13803         }
13804     }
13805 }
13806
13807
13808 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
13809
13810 static void
13811 resolve_fntype (gfc_namespace *ns)
13812 {
13813   gfc_entry_list *el;
13814   gfc_symbol *sym;
13815
13816   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
13817     return;
13818
13819   /* If there are any entries, ns->proc_name is the entry master
13820      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
13821   if (ns->entries)
13822     sym = ns->entries->sym;
13823   else
13824     sym = ns->proc_name;
13825   if (sym->result == sym
13826       && sym->ts.type == BT_UNKNOWN
13827       && gfc_set_default_type (sym, 0, NULL) == FAILURE
13828       && !sym->attr.untyped)
13829     {
13830       gfc_error ("Function '%s' at %L has no IMPLICIT type",
13831                  sym->name, &sym->declared_at);
13832       sym->attr.untyped = 1;
13833     }
13834
13835   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
13836       && !sym->attr.contained
13837       && !gfc_check_symbol_access (sym->ts.u.derived)
13838       && gfc_check_symbol_access (sym))
13839     {
13840       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
13841                       "%L of PRIVATE type '%s'", sym->name,
13842                       &sym->declared_at, sym->ts.u.derived->name);
13843     }
13844
13845     if (ns->entries)
13846     for (el = ns->entries->next; el; el = el->next)
13847       {
13848         if (el->sym->result == el->sym
13849             && el->sym->ts.type == BT_UNKNOWN
13850             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
13851             && !el->sym->attr.untyped)
13852           {
13853             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
13854                        el->sym->name, &el->sym->declared_at);
13855             el->sym->attr.untyped = 1;
13856           }
13857       }
13858 }
13859
13860
13861 /* 12.3.2.1.1 Defined operators.  */
13862
13863 static gfc_try
13864 check_uop_procedure (gfc_symbol *sym, locus where)
13865 {
13866   gfc_formal_arglist *formal;
13867
13868   if (!sym->attr.function)
13869     {
13870       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
13871                  sym->name, &where);
13872       return FAILURE;
13873     }
13874
13875   if (sym->ts.type == BT_CHARACTER
13876       && !(sym->ts.u.cl && sym->ts.u.cl->length)
13877       && !(sym->result && sym->result->ts.u.cl
13878            && sym->result->ts.u.cl->length))
13879     {
13880       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
13881                  "character length", sym->name, &where);
13882       return FAILURE;
13883     }
13884
13885   formal = sym->formal;
13886   if (!formal || !formal->sym)
13887     {
13888       gfc_error ("User operator procedure '%s' at %L must have at least "
13889                  "one argument", sym->name, &where);
13890       return FAILURE;
13891     }
13892
13893   if (formal->sym->attr.intent != INTENT_IN)
13894     {
13895       gfc_error ("First argument of operator interface at %L must be "
13896                  "INTENT(IN)", &where);
13897       return FAILURE;
13898     }
13899
13900   if (formal->sym->attr.optional)
13901     {
13902       gfc_error ("First argument of operator interface at %L cannot be "
13903                  "optional", &where);
13904       return FAILURE;
13905     }
13906
13907   formal = formal->next;
13908   if (!formal || !formal->sym)
13909     return SUCCESS;
13910
13911   if (formal->sym->attr.intent != INTENT_IN)
13912     {
13913       gfc_error ("Second argument of operator interface at %L must be "
13914                  "INTENT(IN)", &where);
13915       return FAILURE;
13916     }
13917
13918   if (formal->sym->attr.optional)
13919     {
13920       gfc_error ("Second argument of operator interface at %L cannot be "
13921                  "optional", &where);
13922       return FAILURE;
13923     }
13924
13925   if (formal->next)
13926     {
13927       gfc_error ("Operator interface at %L must have, at most, two "
13928                  "arguments", &where);
13929       return FAILURE;
13930     }
13931
13932   return SUCCESS;
13933 }
13934
13935 static void
13936 gfc_resolve_uops (gfc_symtree *symtree)
13937 {
13938   gfc_interface *itr;
13939
13940   if (symtree == NULL)
13941     return;
13942
13943   gfc_resolve_uops (symtree->left);
13944   gfc_resolve_uops (symtree->right);
13945
13946   for (itr = symtree->n.uop->op; itr; itr = itr->next)
13947     check_uop_procedure (itr->sym, itr->sym->declared_at);
13948 }
13949
13950
13951 /* Examine all of the expressions associated with a program unit,
13952    assign types to all intermediate expressions, make sure that all
13953    assignments are to compatible types and figure out which names
13954    refer to which functions or subroutines.  It doesn't check code
13955    block, which is handled by resolve_code.  */
13956
13957 static void
13958 resolve_types (gfc_namespace *ns)
13959 {
13960   gfc_namespace *n;
13961   gfc_charlen *cl;
13962   gfc_data *d;
13963   gfc_equiv *eq;
13964   gfc_namespace* old_ns = gfc_current_ns;
13965
13966   /* Check that all IMPLICIT types are ok.  */
13967   if (!ns->seen_implicit_none)
13968     {
13969       unsigned letter;
13970       for (letter = 0; letter != GFC_LETTERS; ++letter)
13971         if (ns->set_flag[letter]
13972             && resolve_typespec_used (&ns->default_type[letter],
13973                                       &ns->implicit_loc[letter],
13974                                       NULL) == FAILURE)
13975           return;
13976     }
13977
13978   gfc_current_ns = ns;
13979
13980   resolve_entries (ns);
13981
13982   resolve_common_vars (ns->blank_common.head, false);
13983   resolve_common_blocks (ns->common_root);
13984
13985   resolve_contained_functions (ns);
13986
13987   if (ns->proc_name && ns->proc_name->attr.flavor == FL_PROCEDURE
13988       && ns->proc_name->attr.if_source == IFSRC_IFBODY)
13989     resolve_formal_arglist (ns->proc_name);
13990
13991   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
13992
13993   for (cl = ns->cl_list; cl; cl = cl->next)
13994     resolve_charlen (cl);
13995
13996   gfc_traverse_ns (ns, resolve_symbol);
13997
13998   resolve_fntype (ns);
13999
14000   for (n = ns->contained; n; n = n->sibling)
14001     {
14002       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
14003         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
14004                    "also be PURE", n->proc_name->name,
14005                    &n->proc_name->declared_at);
14006
14007       resolve_types (n);
14008     }
14009
14010   forall_flag = 0;
14011   do_concurrent_flag = 0;
14012   gfc_check_interfaces (ns);
14013
14014   gfc_traverse_ns (ns, resolve_values);
14015
14016   if (ns->save_all)
14017     gfc_save_all (ns);
14018
14019   iter_stack = NULL;
14020   for (d = ns->data; d; d = d->next)
14021     resolve_data (d);
14022
14023   iter_stack = NULL;
14024   gfc_traverse_ns (ns, gfc_formalize_init_value);
14025
14026   gfc_traverse_ns (ns, gfc_verify_binding_labels);
14027
14028   if (ns->common_root != NULL)
14029     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
14030
14031   for (eq = ns->equiv; eq; eq = eq->next)
14032     resolve_equivalence (eq);
14033
14034   /* Warn about unused labels.  */
14035   if (warn_unused_label)
14036     warn_unused_fortran_label (ns->st_labels);
14037
14038   gfc_resolve_uops (ns->uop_root);
14039
14040   gfc_current_ns = old_ns;
14041 }
14042
14043
14044 /* Call resolve_code recursively.  */
14045
14046 static void
14047 resolve_codes (gfc_namespace *ns)
14048 {
14049   gfc_namespace *n;
14050   bitmap_obstack old_obstack;
14051
14052   if (ns->resolved == 1)
14053     return;
14054
14055   for (n = ns->contained; n; n = n->sibling)
14056     resolve_codes (n);
14057
14058   gfc_current_ns = ns;
14059
14060   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
14061   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
14062     cs_base = NULL;
14063
14064   /* Set to an out of range value.  */
14065   current_entry_id = -1;
14066
14067   old_obstack = labels_obstack;
14068   bitmap_obstack_initialize (&labels_obstack);
14069
14070   resolve_code (ns->code, ns);
14071
14072   bitmap_obstack_release (&labels_obstack);
14073   labels_obstack = old_obstack;
14074 }
14075
14076
14077 /* This function is called after a complete program unit has been compiled.
14078    Its purpose is to examine all of the expressions associated with a program
14079    unit, assign types to all intermediate expressions, make sure that all
14080    assignments are to compatible types and figure out which names refer to
14081    which functions or subroutines.  */
14082
14083 void
14084 gfc_resolve (gfc_namespace *ns)
14085 {
14086   gfc_namespace *old_ns;
14087   code_stack *old_cs_base;
14088
14089   if (ns->resolved)
14090     return;
14091
14092   ns->resolved = -1;
14093   old_ns = gfc_current_ns;
14094   old_cs_base = cs_base;
14095
14096   resolve_types (ns);
14097   resolve_codes (ns);
14098
14099   gfc_current_ns = old_ns;
14100   cs_base = old_cs_base;
14101   ns->resolved = 1;
14102
14103   gfc_run_passes (ns);
14104 }