OSDN Git Service

2011-01-09 Thomas Koenig <tkoenig@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009,
3    2010, 2011
4    Free Software Foundation, Inc.
5    Contributed by Andy Vaught
6
7 This file is part of GCC.
8
9 GCC is free software; you can redistribute it and/or modify it under
10 the terms of the GNU General Public License as published by the Free
11 Software Foundation; either version 3, or (at your option) any later
12 version.
13
14 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15 WARRANTY; without even the implied warranty of MERCHANTABILITY or
16 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
17 for more details.
18
19 You should have received a copy of the GNU General Public License
20 along with GCC; see the file COPYING3.  If not see
21 <http://www.gnu.org/licenses/>.  */
22
23 #include "config.h"
24 #include "system.h"
25 #include "flags.h"
26 #include "gfortran.h"
27 #include "obstack.h"
28 #include "bitmap.h"
29 #include "arith.h"  /* For gfc_compare_expr().  */
30 #include "dependency.h"
31 #include "data.h"
32 #include "target-memory.h" /* for gfc_simplify_transfer */
33 #include "constructor.h"
34
35 /* Types used in equivalence statements.  */
36
37 typedef enum seq_type
38 {
39   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
40 }
41 seq_type;
42
43 /* Stack to keep track of the nesting of blocks as we move through the
44    code.  See resolve_branch() and resolve_code().  */
45
46 typedef struct code_stack
47 {
48   struct gfc_code *head, *current;
49   struct code_stack *prev;
50
51   /* This bitmap keeps track of the targets valid for a branch from
52      inside this block except for END {IF|SELECT}s of enclosing
53      blocks.  */
54   bitmap reachable_labels;
55 }
56 code_stack;
57
58 static code_stack *cs_base = NULL;
59
60
61 /* Nonzero if we're inside a FORALL block.  */
62
63 static int forall_flag;
64
65 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
66
67 static int omp_workshare_flag;
68
69 /* Nonzero if we are processing a formal arglist. The corresponding function
70    resets the flag each time that it is read.  */
71 static int formal_arg_flag = 0;
72
73 /* True if we are resolving a specification expression.  */
74 static int specification_expr = 0;
75
76 /* The id of the last entry seen.  */
77 static int current_entry_id;
78
79 /* We use bitmaps to determine if a branch target is valid.  */
80 static bitmap_obstack labels_obstack;
81
82 /* True when simplifying a EXPR_VARIABLE argument to an inquiry function.  */
83 static bool inquiry_argument = false;
84
85 int
86 gfc_is_formal_arg (void)
87 {
88   return formal_arg_flag;
89 }
90
91 /* Is the symbol host associated?  */
92 static bool
93 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
94 {
95   for (ns = ns->parent; ns; ns = ns->parent)
96     {      
97       if (sym->ns == ns)
98         return true;
99     }
100
101   return false;
102 }
103
104 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
105    an ABSTRACT derived-type.  If where is not NULL, an error message with that
106    locus is printed, optionally using name.  */
107
108 static gfc_try
109 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
110 {
111   if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
112     {
113       if (where)
114         {
115           if (name)
116             gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
117                        name, where, ts->u.derived->name);
118           else
119             gfc_error ("ABSTRACT type '%s' used at %L",
120                        ts->u.derived->name, where);
121         }
122
123       return FAILURE;
124     }
125
126   return SUCCESS;
127 }
128
129
130 static void resolve_symbol (gfc_symbol *sym);
131 static gfc_try resolve_intrinsic (gfc_symbol *sym, locus *loc);
132
133
134 /* Resolve the interface for a PROCEDURE declaration or procedure pointer.  */
135
136 static gfc_try
137 resolve_procedure_interface (gfc_symbol *sym)
138 {
139   if (sym->ts.interface == sym)
140     {
141       gfc_error ("PROCEDURE '%s' at %L may not be used as its own interface",
142                  sym->name, &sym->declared_at);
143       return FAILURE;
144     }
145   if (sym->ts.interface->attr.procedure)
146     {
147       gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared "
148                  "in a later PROCEDURE statement", sym->ts.interface->name,
149                  sym->name, &sym->declared_at);
150       return FAILURE;
151     }
152
153   /* Get the attributes from the interface (now resolved).  */
154   if (sym->ts.interface->attr.if_source || sym->ts.interface->attr.intrinsic)
155     {
156       gfc_symbol *ifc = sym->ts.interface;
157       resolve_symbol (ifc);
158
159       if (ifc->attr.intrinsic)
160         resolve_intrinsic (ifc, &ifc->declared_at);
161
162       if (ifc->result)
163         sym->ts = ifc->result->ts;
164       else   
165         sym->ts = ifc->ts;
166       sym->ts.interface = ifc;
167       sym->attr.function = ifc->attr.function;
168       sym->attr.subroutine = ifc->attr.subroutine;
169       gfc_copy_formal_args (sym, ifc);
170
171       sym->attr.allocatable = ifc->attr.allocatable;
172       sym->attr.pointer = ifc->attr.pointer;
173       sym->attr.pure = ifc->attr.pure;
174       sym->attr.elemental = ifc->attr.elemental;
175       sym->attr.dimension = ifc->attr.dimension;
176       sym->attr.contiguous = ifc->attr.contiguous;
177       sym->attr.recursive = ifc->attr.recursive;
178       sym->attr.always_explicit = ifc->attr.always_explicit;
179       sym->attr.ext_attr |= ifc->attr.ext_attr;
180       sym->attr.is_bind_c = ifc->attr.is_bind_c;
181       /* Copy array spec.  */
182       sym->as = gfc_copy_array_spec (ifc->as);
183       if (sym->as)
184         {
185           int i;
186           for (i = 0; i < sym->as->rank; i++)
187             {
188               gfc_expr_replace_symbols (sym->as->lower[i], sym);
189               gfc_expr_replace_symbols (sym->as->upper[i], sym);
190             }
191         }
192       /* Copy char length.  */
193       if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
194         {
195           sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
196           gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
197           if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
198               && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
199             return FAILURE;
200         }
201     }
202   else if (sym->ts.interface->name[0] != '\0')
203     {
204       gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
205                  sym->ts.interface->name, sym->name, &sym->declared_at);
206       return FAILURE;
207     }
208
209   return SUCCESS;
210 }
211
212
213 /* Resolve types of formal argument lists.  These have to be done early so that
214    the formal argument lists of module procedures can be copied to the
215    containing module before the individual procedures are resolved
216    individually.  We also resolve argument lists of procedures in interface
217    blocks because they are self-contained scoping units.
218
219    Since a dummy argument cannot be a non-dummy procedure, the only
220    resort left for untyped names are the IMPLICIT types.  */
221
222 static void
223 resolve_formal_arglist (gfc_symbol *proc)
224 {
225   gfc_formal_arglist *f;
226   gfc_symbol *sym;
227   int i;
228
229   if (proc->result != NULL)
230     sym = proc->result;
231   else
232     sym = proc;
233
234   if (gfc_elemental (proc)
235       || sym->attr.pointer || sym->attr.allocatable
236       || (sym->as && sym->as->rank > 0))
237     {
238       proc->attr.always_explicit = 1;
239       sym->attr.always_explicit = 1;
240     }
241
242   formal_arg_flag = 1;
243
244   for (f = proc->formal; f; f = f->next)
245     {
246       sym = f->sym;
247
248       if (sym == NULL)
249         {
250           /* Alternate return placeholder.  */
251           if (gfc_elemental (proc))
252             gfc_error ("Alternate return specifier in elemental subroutine "
253                        "'%s' at %L is not allowed", proc->name,
254                        &proc->declared_at);
255           if (proc->attr.function)
256             gfc_error ("Alternate return specifier in function "
257                        "'%s' at %L is not allowed", proc->name,
258                        &proc->declared_at);
259           continue;
260         }
261       else if (sym->attr.procedure && sym->ts.interface
262                && sym->attr.if_source != IFSRC_DECL)
263         resolve_procedure_interface (sym);
264
265       if (sym->attr.if_source != IFSRC_UNKNOWN)
266         resolve_formal_arglist (sym);
267
268       if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
269         {
270           if (gfc_pure (proc) && !gfc_pure (sym))
271             {
272               gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
273                          "also be PURE", sym->name, &sym->declared_at);
274               continue;
275             }
276
277           if (proc->attr.implicit_pure && !gfc_pure(sym))
278             proc->attr.implicit_pure = 0;
279
280           if (gfc_elemental (proc))
281             {
282               gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
283                          "procedure", &sym->declared_at);
284               continue;
285             }
286
287           if (sym->attr.function
288                 && sym->ts.type == BT_UNKNOWN
289                 && sym->attr.intrinsic)
290             {
291               gfc_intrinsic_sym *isym;
292               isym = gfc_find_function (sym->name);
293               if (isym == NULL || !isym->specific)
294                 {
295                   gfc_error ("Unable to find a specific INTRINSIC procedure "
296                              "for the reference '%s' at %L", sym->name,
297                              &sym->declared_at);
298                 }
299               sym->ts = isym->ts;
300             }
301
302           continue;
303         }
304
305       if (sym->ts.type == BT_UNKNOWN && !proc->attr.intrinsic
306           && (!sym->attr.function || sym->result == sym))
307         gfc_set_default_type (sym, 1, sym->ns);
308
309       gfc_resolve_array_spec (sym->as, 0);
310
311       /* We can't tell if an array with dimension (:) is assumed or deferred
312          shape until we know if it has the pointer or allocatable attributes.
313       */
314       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
315           && !(sym->attr.pointer || sym->attr.allocatable))
316         {
317           sym->as->type = AS_ASSUMED_SHAPE;
318           for (i = 0; i < sym->as->rank; i++)
319             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
320                                                   NULL, 1);
321         }
322
323       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
324           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
325           || sym->attr.optional)
326         {
327           proc->attr.always_explicit = 1;
328           if (proc->result)
329             proc->result->attr.always_explicit = 1;
330         }
331
332       /* If the flavor is unknown at this point, it has to be a variable.
333          A procedure specification would have already set the type.  */
334
335       if (sym->attr.flavor == FL_UNKNOWN)
336         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
337
338       if (gfc_pure (proc) && !sym->attr.pointer
339           && sym->attr.flavor != FL_PROCEDURE)
340         {
341           if (proc->attr.function && sym->attr.intent != INTENT_IN)
342             gfc_error ("Argument '%s' of pure function '%s' at %L must be "
343                        "INTENT(IN)", sym->name, proc->name,
344                        &sym->declared_at);
345
346           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
347             gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
348                        "have its INTENT specified", sym->name, proc->name,
349                        &sym->declared_at);
350         }
351
352       if (proc->attr.implicit_pure && !sym->attr.pointer
353           && sym->attr.flavor != FL_PROCEDURE)
354         {
355           if (proc->attr.function && sym->attr.intent != INTENT_IN)
356             proc->attr.implicit_pure = 0;
357
358           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
359             proc->attr.implicit_pure = 0;
360         }
361
362       if (gfc_elemental (proc))
363         {
364           /* F2008, C1289.  */
365           if (sym->attr.codimension)
366             {
367               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
368                          "procedure", sym->name, &sym->declared_at);
369               continue;
370             }
371
372           if (sym->as != NULL)
373             {
374               gfc_error ("Argument '%s' of elemental procedure at %L must "
375                          "be scalar", sym->name, &sym->declared_at);
376               continue;
377             }
378
379           if (sym->attr.allocatable)
380             {
381               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
382                          "have the ALLOCATABLE attribute", sym->name,
383                          &sym->declared_at);
384               continue;
385             }
386
387           if (sym->attr.pointer)
388             {
389               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
390                          "have the POINTER attribute", sym->name,
391                          &sym->declared_at);
392               continue;
393             }
394
395           if (sym->attr.flavor == FL_PROCEDURE)
396             {
397               gfc_error ("Dummy procedure '%s' not allowed in elemental "
398                          "procedure '%s' at %L", sym->name, proc->name,
399                          &sym->declared_at);
400               continue;
401             }
402
403           if (sym->attr.intent == INTENT_UNKNOWN)
404             {
405               gfc_error ("Argument '%s' of elemental procedure '%s' at %L must "
406                          "have its INTENT specified", sym->name, proc->name,
407                          &sym->declared_at);
408               continue;
409             }
410         }
411
412       /* Each dummy shall be specified to be scalar.  */
413       if (proc->attr.proc == PROC_ST_FUNCTION)
414         {
415           if (sym->as != NULL)
416             {
417               gfc_error ("Argument '%s' of statement function at %L must "
418                          "be scalar", sym->name, &sym->declared_at);
419               continue;
420             }
421
422           if (sym->ts.type == BT_CHARACTER)
423             {
424               gfc_charlen *cl = sym->ts.u.cl;
425               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
426                 {
427                   gfc_error ("Character-valued argument '%s' of statement "
428                              "function at %L must have constant length",
429                              sym->name, &sym->declared_at);
430                   continue;
431                 }
432             }
433         }
434     }
435   formal_arg_flag = 0;
436 }
437
438
439 /* Work function called when searching for symbols that have argument lists
440    associated with them.  */
441
442 static void
443 find_arglists (gfc_symbol *sym)
444 {
445   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
446     return;
447
448   resolve_formal_arglist (sym);
449 }
450
451
452 /* Given a namespace, resolve all formal argument lists within the namespace.
453  */
454
455 static void
456 resolve_formal_arglists (gfc_namespace *ns)
457 {
458   if (ns == NULL)
459     return;
460
461   gfc_traverse_ns (ns, find_arglists);
462 }
463
464
465 static void
466 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
467 {
468   gfc_try t;
469
470   /* If this namespace is not a function or an entry master function,
471      ignore it.  */
472   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
473       || sym->attr.entry_master)
474     return;
475
476   /* Try to find out of what the return type is.  */
477   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
478     {
479       t = gfc_set_default_type (sym->result, 0, ns);
480
481       if (t == FAILURE && !sym->result->attr.untyped)
482         {
483           if (sym->result == sym)
484             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
485                        sym->name, &sym->declared_at);
486           else if (!sym->result->attr.proc_pointer)
487             gfc_error ("Result '%s' of contained function '%s' at %L has "
488                        "no IMPLICIT type", sym->result->name, sym->name,
489                        &sym->result->declared_at);
490           sym->result->attr.untyped = 1;
491         }
492     }
493
494   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
495      type, lists the only ways a character length value of * can be used:
496      dummy arguments of procedures, named constants, and function results
497      in external functions.  Internal function results and results of module
498      procedures are not on this list, ergo, not permitted.  */
499
500   if (sym->result->ts.type == BT_CHARACTER)
501     {
502       gfc_charlen *cl = sym->result->ts.u.cl;
503       if (!cl || !cl->length)
504         {
505           /* See if this is a module-procedure and adapt error message
506              accordingly.  */
507           bool module_proc;
508           gcc_assert (ns->parent && ns->parent->proc_name);
509           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
510
511           gfc_error ("Character-valued %s '%s' at %L must not be"
512                      " assumed length",
513                      module_proc ? _("module procedure")
514                                  : _("internal function"),
515                      sym->name, &sym->declared_at);
516         }
517     }
518 }
519
520
521 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
522    introduce duplicates.  */
523
524 static void
525 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
526 {
527   gfc_formal_arglist *f, *new_arglist;
528   gfc_symbol *new_sym;
529
530   for (; new_args != NULL; new_args = new_args->next)
531     {
532       new_sym = new_args->sym;
533       /* See if this arg is already in the formal argument list.  */
534       for (f = proc->formal; f; f = f->next)
535         {
536           if (new_sym == f->sym)
537             break;
538         }
539
540       if (f)
541         continue;
542
543       /* Add a new argument.  Argument order is not important.  */
544       new_arglist = gfc_get_formal_arglist ();
545       new_arglist->sym = new_sym;
546       new_arglist->next = proc->formal;
547       proc->formal  = new_arglist;
548     }
549 }
550
551
552 /* Flag the arguments that are not present in all entries.  */
553
554 static void
555 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
556 {
557   gfc_formal_arglist *f, *head;
558   head = new_args;
559
560   for (f = proc->formal; f; f = f->next)
561     {
562       if (f->sym == NULL)
563         continue;
564
565       for (new_args = head; new_args; new_args = new_args->next)
566         {
567           if (new_args->sym == f->sym)
568             break;
569         }
570
571       if (new_args)
572         continue;
573
574       f->sym->attr.not_always_present = 1;
575     }
576 }
577
578
579 /* Resolve alternate entry points.  If a symbol has multiple entry points we
580    create a new master symbol for the main routine, and turn the existing
581    symbol into an entry point.  */
582
583 static void
584 resolve_entries (gfc_namespace *ns)
585 {
586   gfc_namespace *old_ns;
587   gfc_code *c;
588   gfc_symbol *proc;
589   gfc_entry_list *el;
590   char name[GFC_MAX_SYMBOL_LEN + 1];
591   static int master_count = 0;
592
593   if (ns->proc_name == NULL)
594     return;
595
596   /* No need to do anything if this procedure doesn't have alternate entry
597      points.  */
598   if (!ns->entries)
599     return;
600
601   /* We may already have resolved alternate entry points.  */
602   if (ns->proc_name->attr.entry_master)
603     return;
604
605   /* If this isn't a procedure something has gone horribly wrong.  */
606   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
607
608   /* Remember the current namespace.  */
609   old_ns = gfc_current_ns;
610
611   gfc_current_ns = ns;
612
613   /* Add the main entry point to the list of entry points.  */
614   el = gfc_get_entry_list ();
615   el->sym = ns->proc_name;
616   el->id = 0;
617   el->next = ns->entries;
618   ns->entries = el;
619   ns->proc_name->attr.entry = 1;
620
621   /* If it is a module function, it needs to be in the right namespace
622      so that gfc_get_fake_result_decl can gather up the results. The
623      need for this arose in get_proc_name, where these beasts were
624      left in their own namespace, to keep prior references linked to
625      the entry declaration.*/
626   if (ns->proc_name->attr.function
627       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
628     el->sym->ns = ns;
629
630   /* Do the same for entries where the master is not a module
631      procedure.  These are retained in the module namespace because
632      of the module procedure declaration.  */
633   for (el = el->next; el; el = el->next)
634     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
635           && el->sym->attr.mod_proc)
636       el->sym->ns = ns;
637   el = ns->entries;
638
639   /* Add an entry statement for it.  */
640   c = gfc_get_code ();
641   c->op = EXEC_ENTRY;
642   c->ext.entry = el;
643   c->next = ns->code;
644   ns->code = c;
645
646   /* Create a new symbol for the master function.  */
647   /* Give the internal function a unique name (within this file).
648      Also include the function name so the user has some hope of figuring
649      out what is going on.  */
650   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
651             master_count++, ns->proc_name->name);
652   gfc_get_ha_symbol (name, &proc);
653   gcc_assert (proc != NULL);
654
655   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
656   if (ns->proc_name->attr.subroutine)
657     gfc_add_subroutine (&proc->attr, proc->name, NULL);
658   else
659     {
660       gfc_symbol *sym;
661       gfc_typespec *ts, *fts;
662       gfc_array_spec *as, *fas;
663       gfc_add_function (&proc->attr, proc->name, NULL);
664       proc->result = proc;
665       fas = ns->entries->sym->as;
666       fas = fas ? fas : ns->entries->sym->result->as;
667       fts = &ns->entries->sym->result->ts;
668       if (fts->type == BT_UNKNOWN)
669         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
670       for (el = ns->entries->next; el; el = el->next)
671         {
672           ts = &el->sym->result->ts;
673           as = el->sym->as;
674           as = as ? as : el->sym->result->as;
675           if (ts->type == BT_UNKNOWN)
676             ts = gfc_get_default_type (el->sym->result->name, NULL);
677
678           if (! gfc_compare_types (ts, fts)
679               || (el->sym->result->attr.dimension
680                   != ns->entries->sym->result->attr.dimension)
681               || (el->sym->result->attr.pointer
682                   != ns->entries->sym->result->attr.pointer))
683             break;
684           else if (as && fas && ns->entries->sym->result != el->sym->result
685                       && gfc_compare_array_spec (as, fas) == 0)
686             gfc_error ("Function %s at %L has entries with mismatched "
687                        "array specifications", ns->entries->sym->name,
688                        &ns->entries->sym->declared_at);
689           /* The characteristics need to match and thus both need to have
690              the same string length, i.e. both len=*, or both len=4.
691              Having both len=<variable> is also possible, but difficult to
692              check at compile time.  */
693           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
694                    && (((ts->u.cl->length && !fts->u.cl->length)
695                         ||(!ts->u.cl->length && fts->u.cl->length))
696                        || (ts->u.cl->length
697                            && ts->u.cl->length->expr_type
698                               != fts->u.cl->length->expr_type)
699                        || (ts->u.cl->length
700                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
701                            && mpz_cmp (ts->u.cl->length->value.integer,
702                                        fts->u.cl->length->value.integer) != 0)))
703             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
704                             "entries returning variables of different "
705                             "string lengths", ns->entries->sym->name,
706                             &ns->entries->sym->declared_at);
707         }
708
709       if (el == NULL)
710         {
711           sym = ns->entries->sym->result;
712           /* All result types the same.  */
713           proc->ts = *fts;
714           if (sym->attr.dimension)
715             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
716           if (sym->attr.pointer)
717             gfc_add_pointer (&proc->attr, NULL);
718         }
719       else
720         {
721           /* Otherwise the result will be passed through a union by
722              reference.  */
723           proc->attr.mixed_entry_master = 1;
724           for (el = ns->entries; el; el = el->next)
725             {
726               sym = el->sym->result;
727               if (sym->attr.dimension)
728                 {
729                   if (el == ns->entries)
730                     gfc_error ("FUNCTION result %s can't be an array in "
731                                "FUNCTION %s at %L", sym->name,
732                                ns->entries->sym->name, &sym->declared_at);
733                   else
734                     gfc_error ("ENTRY result %s can't be an array in "
735                                "FUNCTION %s at %L", sym->name,
736                                ns->entries->sym->name, &sym->declared_at);
737                 }
738               else if (sym->attr.pointer)
739                 {
740                   if (el == ns->entries)
741                     gfc_error ("FUNCTION result %s can't be a POINTER in "
742                                "FUNCTION %s at %L", sym->name,
743                                ns->entries->sym->name, &sym->declared_at);
744                   else
745                     gfc_error ("ENTRY result %s can't be a POINTER in "
746                                "FUNCTION %s at %L", sym->name,
747                                ns->entries->sym->name, &sym->declared_at);
748                 }
749               else
750                 {
751                   ts = &sym->ts;
752                   if (ts->type == BT_UNKNOWN)
753                     ts = gfc_get_default_type (sym->name, NULL);
754                   switch (ts->type)
755                     {
756                     case BT_INTEGER:
757                       if (ts->kind == gfc_default_integer_kind)
758                         sym = NULL;
759                       break;
760                     case BT_REAL:
761                       if (ts->kind == gfc_default_real_kind
762                           || ts->kind == gfc_default_double_kind)
763                         sym = NULL;
764                       break;
765                     case BT_COMPLEX:
766                       if (ts->kind == gfc_default_complex_kind)
767                         sym = NULL;
768                       break;
769                     case BT_LOGICAL:
770                       if (ts->kind == gfc_default_logical_kind)
771                         sym = NULL;
772                       break;
773                     case BT_UNKNOWN:
774                       /* We will issue error elsewhere.  */
775                       sym = NULL;
776                       break;
777                     default:
778                       break;
779                     }
780                   if (sym)
781                     {
782                       if (el == ns->entries)
783                         gfc_error ("FUNCTION result %s can't be of type %s "
784                                    "in FUNCTION %s at %L", sym->name,
785                                    gfc_typename (ts), ns->entries->sym->name,
786                                    &sym->declared_at);
787                       else
788                         gfc_error ("ENTRY result %s can't be of type %s "
789                                    "in FUNCTION %s at %L", sym->name,
790                                    gfc_typename (ts), ns->entries->sym->name,
791                                    &sym->declared_at);
792                     }
793                 }
794             }
795         }
796     }
797   proc->attr.access = ACCESS_PRIVATE;
798   proc->attr.entry_master = 1;
799
800   /* Merge all the entry point arguments.  */
801   for (el = ns->entries; el; el = el->next)
802     merge_argument_lists (proc, el->sym->formal);
803
804   /* Check the master formal arguments for any that are not
805      present in all entry points.  */
806   for (el = ns->entries; el; el = el->next)
807     check_argument_lists (proc, el->sym->formal);
808
809   /* Use the master function for the function body.  */
810   ns->proc_name = proc;
811
812   /* Finalize the new symbols.  */
813   gfc_commit_symbols ();
814
815   /* Restore the original namespace.  */
816   gfc_current_ns = old_ns;
817 }
818
819
820 /* Resolve common variables.  */
821 static void
822 resolve_common_vars (gfc_symbol *sym, bool named_common)
823 {
824   gfc_symbol *csym = sym;
825
826   for (; csym; csym = csym->common_next)
827     {
828       if (csym->value || csym->attr.data)
829         {
830           if (!csym->ns->is_block_data)
831             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
832                             "but only in BLOCK DATA initialization is "
833                             "allowed", csym->name, &csym->declared_at);
834           else if (!named_common)
835             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
836                             "in a blank COMMON but initialization is only "
837                             "allowed in named common blocks", csym->name,
838                             &csym->declared_at);
839         }
840
841       if (csym->ts.type != BT_DERIVED)
842         continue;
843
844       if (!(csym->ts.u.derived->attr.sequence
845             || csym->ts.u.derived->attr.is_bind_c))
846         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
847                        "has neither the SEQUENCE nor the BIND(C) "
848                        "attribute", csym->name, &csym->declared_at);
849       if (csym->ts.u.derived->attr.alloc_comp)
850         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
851                        "has an ultimate component that is "
852                        "allocatable", csym->name, &csym->declared_at);
853       if (gfc_has_default_initializer (csym->ts.u.derived))
854         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
855                        "may not have default initializer", csym->name,
856                        &csym->declared_at);
857
858       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
859         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
860     }
861 }
862
863 /* Resolve common blocks.  */
864 static void
865 resolve_common_blocks (gfc_symtree *common_root)
866 {
867   gfc_symbol *sym;
868
869   if (common_root == NULL)
870     return;
871
872   if (common_root->left)
873     resolve_common_blocks (common_root->left);
874   if (common_root->right)
875     resolve_common_blocks (common_root->right);
876
877   resolve_common_vars (common_root->n.common->head, true);
878
879   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
880   if (sym == NULL)
881     return;
882
883   if (sym->attr.flavor == FL_PARAMETER)
884     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
885                sym->name, &common_root->n.common->where, &sym->declared_at);
886
887   if (sym->attr.intrinsic)
888     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
889                sym->name, &common_root->n.common->where);
890   else if (sym->attr.result
891            || gfc_is_function_return_value (sym, gfc_current_ns))
892     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
893                     "that is also a function result", sym->name,
894                     &common_root->n.common->where);
895   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
896            && sym->attr.proc != PROC_ST_FUNCTION)
897     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
898                     "that is also a global procedure", sym->name,
899                     &common_root->n.common->where);
900 }
901
902
903 /* Resolve contained function types.  Because contained functions can call one
904    another, they have to be worked out before any of the contained procedures
905    can be resolved.
906
907    The good news is that if a function doesn't already have a type, the only
908    way it can get one is through an IMPLICIT type or a RESULT variable, because
909    by definition contained functions are contained namespace they're contained
910    in, not in a sibling or parent namespace.  */
911
912 static void
913 resolve_contained_functions (gfc_namespace *ns)
914 {
915   gfc_namespace *child;
916   gfc_entry_list *el;
917
918   resolve_formal_arglists (ns);
919
920   for (child = ns->contained; child; child = child->sibling)
921     {
922       /* Resolve alternate entry points first.  */
923       resolve_entries (child);
924
925       /* Then check function return types.  */
926       resolve_contained_fntype (child->proc_name, child);
927       for (el = child->entries; el; el = el->next)
928         resolve_contained_fntype (el->sym, child);
929     }
930 }
931
932
933 /* Resolve all of the elements of a structure constructor and make sure that
934    the types are correct. The 'init' flag indicates that the given
935    constructor is an initializer.  */
936
937 static gfc_try
938 resolve_structure_cons (gfc_expr *expr, int init)
939 {
940   gfc_constructor *cons;
941   gfc_component *comp;
942   gfc_try t;
943   symbol_attribute a;
944
945   t = SUCCESS;
946
947   if (expr->ts.type == BT_DERIVED)
948     resolve_symbol (expr->ts.u.derived);
949
950   cons = gfc_constructor_first (expr->value.constructor);
951   /* A constructor may have references if it is the result of substituting a
952      parameter variable.  In this case we just pull out the component we
953      want.  */
954   if (expr->ref)
955     comp = expr->ref->u.c.sym->components;
956   else
957     comp = expr->ts.u.derived->components;
958
959   /* See if the user is trying to invoke a structure constructor for one of
960      the iso_c_binding derived types.  */
961   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
962       && expr->ts.u.derived->ts.is_iso_c && cons
963       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
964     {
965       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
966                  expr->ts.u.derived->name, &(expr->where));
967       return FAILURE;
968     }
969
970   /* Return if structure constructor is c_null_(fun)prt.  */
971   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
972       && expr->ts.u.derived->ts.is_iso_c && cons
973       && cons->expr && cons->expr->expr_type == EXPR_NULL)
974     return SUCCESS;
975
976   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
977     {
978       int rank;
979
980       if (!cons->expr)
981         continue;
982
983       if (gfc_resolve_expr (cons->expr) == FAILURE)
984         {
985           t = FAILURE;
986           continue;
987         }
988
989       rank = comp->as ? comp->as->rank : 0;
990       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
991           && (comp->attr.allocatable || cons->expr->rank))
992         {
993           gfc_error ("The rank of the element in the derived type "
994                      "constructor at %L does not match that of the "
995                      "component (%d/%d)", &cons->expr->where,
996                      cons->expr->rank, rank);
997           t = FAILURE;
998         }
999
1000       /* If we don't have the right type, try to convert it.  */
1001
1002       if (!comp->attr.proc_pointer &&
1003           !gfc_compare_types (&cons->expr->ts, &comp->ts))
1004         {
1005           t = FAILURE;
1006           if (strcmp (comp->name, "_extends") == 0)
1007             {
1008               /* Can afford to be brutal with the _extends initializer.
1009                  The derived type can get lost because it is PRIVATE
1010                  but it is not usage constrained by the standard.  */
1011               cons->expr->ts = comp->ts;
1012               t = SUCCESS;
1013             }
1014           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
1015             gfc_error ("The element in the derived type constructor at %L, "
1016                        "for pointer component '%s', is %s but should be %s",
1017                        &cons->expr->where, comp->name,
1018                        gfc_basic_typename (cons->expr->ts.type),
1019                        gfc_basic_typename (comp->ts.type));
1020           else
1021             t = gfc_convert_type (cons->expr, &comp->ts, 1);
1022         }
1023
1024       /* For strings, the length of the constructor should be the same as
1025          the one of the structure, ensure this if the lengths are known at
1026          compile time and when we are dealing with PARAMETER or structure
1027          constructors.  */
1028       if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1029           && comp->ts.u.cl->length
1030           && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1031           && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1032           && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1033           && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1034                       comp->ts.u.cl->length->value.integer) != 0)
1035         {
1036           if (cons->expr->expr_type == EXPR_VARIABLE
1037               && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1038             {
1039               /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1040                  to make use of the gfc_resolve_character_array_constructor
1041                  machinery.  The expression is later simplified away to
1042                  an array of string literals.  */
1043               gfc_expr *para = cons->expr;
1044               cons->expr = gfc_get_expr ();
1045               cons->expr->ts = para->ts;
1046               cons->expr->where = para->where;
1047               cons->expr->expr_type = EXPR_ARRAY;
1048               cons->expr->rank = para->rank;
1049               cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1050               gfc_constructor_append_expr (&cons->expr->value.constructor,
1051                                            para, &cons->expr->where);
1052             }
1053           if (cons->expr->expr_type == EXPR_ARRAY)
1054             {
1055               gfc_constructor *p;
1056               p = gfc_constructor_first (cons->expr->value.constructor);
1057               if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1058                 {
1059                   gfc_charlen *cl, *cl2;
1060
1061                   cl2 = NULL;
1062                   for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1063                     {
1064                       if (cl == cons->expr->ts.u.cl)
1065                         break;
1066                       cl2 = cl;
1067                     }
1068
1069                   gcc_assert (cl);
1070
1071                   if (cl2)
1072                     cl2->next = cl->next;
1073
1074                   gfc_free_expr (cl->length);
1075                   gfc_free (cl);
1076                 }
1077
1078               cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1079               cons->expr->ts.u.cl->length_from_typespec = true;
1080               cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1081               gfc_resolve_character_array_constructor (cons->expr);
1082             }
1083         }
1084
1085       if (cons->expr->expr_type == EXPR_NULL
1086           && !(comp->attr.pointer || comp->attr.allocatable
1087                || comp->attr.proc_pointer
1088                || (comp->ts.type == BT_CLASS
1089                    && (CLASS_DATA (comp)->attr.class_pointer
1090                        || CLASS_DATA (comp)->attr.allocatable))))
1091         {
1092           t = FAILURE;
1093           gfc_error ("The NULL in the derived type constructor at %L is "
1094                      "being applied to component '%s', which is neither "
1095                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
1096                      comp->name);
1097         }
1098
1099       if (!comp->attr.pointer || comp->attr.proc_pointer
1100           || cons->expr->expr_type == EXPR_NULL)
1101         continue;
1102
1103       a = gfc_expr_attr (cons->expr);
1104
1105       if (!a.pointer && !a.target)
1106         {
1107           t = FAILURE;
1108           gfc_error ("The element in the derived type constructor at %L, "
1109                      "for pointer component '%s' should be a POINTER or "
1110                      "a TARGET", &cons->expr->where, comp->name);
1111         }
1112
1113       if (init)
1114         {
1115           /* F08:C461. Additional checks for pointer initialization.  */
1116           if (a.allocatable)
1117             {
1118               t = FAILURE;
1119               gfc_error ("Pointer initialization target at %L "
1120                          "must not be ALLOCATABLE ", &cons->expr->where);
1121             }
1122           if (!a.save)
1123             {
1124               t = FAILURE;
1125               gfc_error ("Pointer initialization target at %L "
1126                          "must have the SAVE attribute", &cons->expr->where);
1127             }
1128         }
1129
1130       /* F2003, C1272 (3).  */
1131       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
1132           && (gfc_impure_variable (cons->expr->symtree->n.sym)
1133               || gfc_is_coindexed (cons->expr)))
1134         {
1135           t = FAILURE;
1136           gfc_error ("Invalid expression in the derived type constructor for "
1137                      "pointer component '%s' at %L in PURE procedure",
1138                      comp->name, &cons->expr->where);
1139         }
1140
1141       if (gfc_implicit_pure (NULL)
1142             && cons->expr->expr_type == EXPR_VARIABLE
1143             && (gfc_impure_variable (cons->expr->symtree->n.sym)
1144                 || gfc_is_coindexed (cons->expr)))
1145         gfc_current_ns->proc_name->attr.implicit_pure = 0;
1146
1147     }
1148
1149   return t;
1150 }
1151
1152
1153 /****************** Expression name resolution ******************/
1154
1155 /* Returns 0 if a symbol was not declared with a type or
1156    attribute declaration statement, nonzero otherwise.  */
1157
1158 static int
1159 was_declared (gfc_symbol *sym)
1160 {
1161   symbol_attribute a;
1162
1163   a = sym->attr;
1164
1165   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1166     return 1;
1167
1168   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1169       || a.optional || a.pointer || a.save || a.target || a.volatile_
1170       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1171       || a.asynchronous || a.codimension)
1172     return 1;
1173
1174   return 0;
1175 }
1176
1177
1178 /* Determine if a symbol is generic or not.  */
1179
1180 static int
1181 generic_sym (gfc_symbol *sym)
1182 {
1183   gfc_symbol *s;
1184
1185   if (sym->attr.generic ||
1186       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1187     return 1;
1188
1189   if (was_declared (sym) || sym->ns->parent == NULL)
1190     return 0;
1191
1192   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1193   
1194   if (s != NULL)
1195     {
1196       if (s == sym)
1197         return 0;
1198       else
1199         return generic_sym (s);
1200     }
1201
1202   return 0;
1203 }
1204
1205
1206 /* Determine if a symbol is specific or not.  */
1207
1208 static int
1209 specific_sym (gfc_symbol *sym)
1210 {
1211   gfc_symbol *s;
1212
1213   if (sym->attr.if_source == IFSRC_IFBODY
1214       || sym->attr.proc == PROC_MODULE
1215       || sym->attr.proc == PROC_INTERNAL
1216       || sym->attr.proc == PROC_ST_FUNCTION
1217       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1218       || sym->attr.external)
1219     return 1;
1220
1221   if (was_declared (sym) || sym->ns->parent == NULL)
1222     return 0;
1223
1224   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1225
1226   return (s == NULL) ? 0 : specific_sym (s);
1227 }
1228
1229
1230 /* Figure out if the procedure is specific, generic or unknown.  */
1231
1232 typedef enum
1233 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1234 proc_type;
1235
1236 static proc_type
1237 procedure_kind (gfc_symbol *sym)
1238 {
1239   if (generic_sym (sym))
1240     return PTYPE_GENERIC;
1241
1242   if (specific_sym (sym))
1243     return PTYPE_SPECIFIC;
1244
1245   return PTYPE_UNKNOWN;
1246 }
1247
1248 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1249    is nonzero when matching actual arguments.  */
1250
1251 static int need_full_assumed_size = 0;
1252
1253 static bool
1254 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1255 {
1256   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1257       return false;
1258
1259   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1260      What should it be?  */
1261   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1262           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1263                && (e->ref->u.ar.type == AR_FULL))
1264     {
1265       gfc_error ("The upper bound in the last dimension must "
1266                  "appear in the reference to the assumed size "
1267                  "array '%s' at %L", sym->name, &e->where);
1268       return true;
1269     }
1270   return false;
1271 }
1272
1273
1274 /* Look for bad assumed size array references in argument expressions
1275   of elemental and array valued intrinsic procedures.  Since this is
1276   called from procedure resolution functions, it only recurses at
1277   operators.  */
1278
1279 static bool
1280 resolve_assumed_size_actual (gfc_expr *e)
1281 {
1282   if (e == NULL)
1283    return false;
1284
1285   switch (e->expr_type)
1286     {
1287     case EXPR_VARIABLE:
1288       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1289         return true;
1290       break;
1291
1292     case EXPR_OP:
1293       if (resolve_assumed_size_actual (e->value.op.op1)
1294           || resolve_assumed_size_actual (e->value.op.op2))
1295         return true;
1296       break;
1297
1298     default:
1299       break;
1300     }
1301   return false;
1302 }
1303
1304
1305 /* Check a generic procedure, passed as an actual argument, to see if
1306    there is a matching specific name.  If none, it is an error, and if
1307    more than one, the reference is ambiguous.  */
1308 static int
1309 count_specific_procs (gfc_expr *e)
1310 {
1311   int n;
1312   gfc_interface *p;
1313   gfc_symbol *sym;
1314         
1315   n = 0;
1316   sym = e->symtree->n.sym;
1317
1318   for (p = sym->generic; p; p = p->next)
1319     if (strcmp (sym->name, p->sym->name) == 0)
1320       {
1321         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1322                                        sym->name);
1323         n++;
1324       }
1325
1326   if (n > 1)
1327     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1328                &e->where);
1329
1330   if (n == 0)
1331     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1332                "argument at %L", sym->name, &e->where);
1333
1334   return n;
1335 }
1336
1337
1338 /* See if a call to sym could possibly be a not allowed RECURSION because of
1339    a missing RECURIVE declaration.  This means that either sym is the current
1340    context itself, or sym is the parent of a contained procedure calling its
1341    non-RECURSIVE containing procedure.
1342    This also works if sym is an ENTRY.  */
1343
1344 static bool
1345 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1346 {
1347   gfc_symbol* proc_sym;
1348   gfc_symbol* context_proc;
1349   gfc_namespace* real_context;
1350
1351   if (sym->attr.flavor == FL_PROGRAM)
1352     return false;
1353
1354   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1355
1356   /* If we've got an ENTRY, find real procedure.  */
1357   if (sym->attr.entry && sym->ns->entries)
1358     proc_sym = sym->ns->entries->sym;
1359   else
1360     proc_sym = sym;
1361
1362   /* If sym is RECURSIVE, all is well of course.  */
1363   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1364     return false;
1365
1366   /* Find the context procedure's "real" symbol if it has entries.
1367      We look for a procedure symbol, so recurse on the parents if we don't
1368      find one (like in case of a BLOCK construct).  */
1369   for (real_context = context; ; real_context = real_context->parent)
1370     {
1371       /* We should find something, eventually!  */
1372       gcc_assert (real_context);
1373
1374       context_proc = (real_context->entries ? real_context->entries->sym
1375                                             : real_context->proc_name);
1376
1377       /* In some special cases, there may not be a proc_name, like for this
1378          invalid code:
1379          real(bad_kind()) function foo () ...
1380          when checking the call to bad_kind ().
1381          In these cases, we simply return here and assume that the
1382          call is ok.  */
1383       if (!context_proc)
1384         return false;
1385
1386       if (context_proc->attr.flavor != FL_LABEL)
1387         break;
1388     }
1389
1390   /* A call from sym's body to itself is recursion, of course.  */
1391   if (context_proc == proc_sym)
1392     return true;
1393
1394   /* The same is true if context is a contained procedure and sym the
1395      containing one.  */
1396   if (context_proc->attr.contained)
1397     {
1398       gfc_symbol* parent_proc;
1399
1400       gcc_assert (context->parent);
1401       parent_proc = (context->parent->entries ? context->parent->entries->sym
1402                                               : context->parent->proc_name);
1403
1404       if (parent_proc == proc_sym)
1405         return true;
1406     }
1407
1408   return false;
1409 }
1410
1411
1412 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1413    its typespec and formal argument list.  */
1414
1415 static gfc_try
1416 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1417 {
1418   gfc_intrinsic_sym* isym = NULL;
1419   const char* symstd;
1420
1421   if (sym->formal)
1422     return SUCCESS;
1423
1424   /* We already know this one is an intrinsic, so we don't call
1425      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1426      gfc_find_subroutine directly to check whether it is a function or
1427      subroutine.  */
1428
1429   if (sym->intmod_sym_id)
1430     isym = gfc_intrinsic_function_by_id ((gfc_isym_id) sym->intmod_sym_id);
1431   else
1432     isym = gfc_find_function (sym->name);
1433
1434   if (isym)
1435     {
1436       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1437           && !sym->attr.implicit_type)
1438         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1439                       " ignored", sym->name, &sym->declared_at);
1440
1441       if (!sym->attr.function &&
1442           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1443         return FAILURE;
1444
1445       sym->ts = isym->ts;
1446     }
1447   else if ((isym = gfc_find_subroutine (sym->name)))
1448     {
1449       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1450         {
1451           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1452                       " specifier", sym->name, &sym->declared_at);
1453           return FAILURE;
1454         }
1455
1456       if (!sym->attr.subroutine &&
1457           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1458         return FAILURE;
1459     }
1460   else
1461     {
1462       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1463                  &sym->declared_at);
1464       return FAILURE;
1465     }
1466
1467   gfc_copy_formal_args_intr (sym, isym);
1468
1469   /* Check it is actually available in the standard settings.  */
1470   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1471       == FAILURE)
1472     {
1473       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1474                  " available in the current standard settings but %s.  Use"
1475                  " an appropriate -std=* option or enable -fall-intrinsics"
1476                  " in order to use it.",
1477                  sym->name, &sym->declared_at, symstd);
1478       return FAILURE;
1479     }
1480
1481   return SUCCESS;
1482 }
1483
1484
1485 /* Resolve a procedure expression, like passing it to a called procedure or as
1486    RHS for a procedure pointer assignment.  */
1487
1488 static gfc_try
1489 resolve_procedure_expression (gfc_expr* expr)
1490 {
1491   gfc_symbol* sym;
1492
1493   if (expr->expr_type != EXPR_VARIABLE)
1494     return SUCCESS;
1495   gcc_assert (expr->symtree);
1496
1497   sym = expr->symtree->n.sym;
1498
1499   if (sym->attr.intrinsic)
1500     resolve_intrinsic (sym, &expr->where);
1501
1502   if (sym->attr.flavor != FL_PROCEDURE
1503       || (sym->attr.function && sym->result == sym))
1504     return SUCCESS;
1505
1506   /* A non-RECURSIVE procedure that is used as procedure expression within its
1507      own body is in danger of being called recursively.  */
1508   if (is_illegal_recursion (sym, gfc_current_ns))
1509     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1510                  " itself recursively.  Declare it RECURSIVE or use"
1511                  " -frecursive", sym->name, &expr->where);
1512   
1513   return SUCCESS;
1514 }
1515
1516
1517 /* Resolve an actual argument list.  Most of the time, this is just
1518    resolving the expressions in the list.
1519    The exception is that we sometimes have to decide whether arguments
1520    that look like procedure arguments are really simple variable
1521    references.  */
1522
1523 static gfc_try
1524 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1525                         bool no_formal_args)
1526 {
1527   gfc_symbol *sym;
1528   gfc_symtree *parent_st;
1529   gfc_expr *e;
1530   int save_need_full_assumed_size;
1531   gfc_component *comp;
1532
1533   for (; arg; arg = arg->next)
1534     {
1535       e = arg->expr;
1536       if (e == NULL)
1537         {
1538           /* Check the label is a valid branching target.  */
1539           if (arg->label)
1540             {
1541               if (arg->label->defined == ST_LABEL_UNKNOWN)
1542                 {
1543                   gfc_error ("Label %d referenced at %L is never defined",
1544                              arg->label->value, &arg->label->where);
1545                   return FAILURE;
1546                 }
1547             }
1548           continue;
1549         }
1550
1551       if (gfc_is_proc_ptr_comp (e, &comp))
1552         {
1553           e->ts = comp->ts;
1554           if (e->expr_type == EXPR_PPC)
1555             {
1556               if (comp->as != NULL)
1557                 e->rank = comp->as->rank;
1558               e->expr_type = EXPR_FUNCTION;
1559             }
1560           if (gfc_resolve_expr (e) == FAILURE)                          
1561             return FAILURE; 
1562           goto argument_list;
1563         }
1564
1565       if (e->expr_type == EXPR_VARIABLE
1566             && e->symtree->n.sym->attr.generic
1567             && no_formal_args
1568             && count_specific_procs (e) != 1)
1569         return FAILURE;
1570
1571       if (e->ts.type != BT_PROCEDURE)
1572         {
1573           save_need_full_assumed_size = need_full_assumed_size;
1574           if (e->expr_type != EXPR_VARIABLE)
1575             need_full_assumed_size = 0;
1576           if (gfc_resolve_expr (e) != SUCCESS)
1577             return FAILURE;
1578           need_full_assumed_size = save_need_full_assumed_size;
1579           goto argument_list;
1580         }
1581
1582       /* See if the expression node should really be a variable reference.  */
1583
1584       sym = e->symtree->n.sym;
1585
1586       if (sym->attr.flavor == FL_PROCEDURE
1587           || sym->attr.intrinsic
1588           || sym->attr.external)
1589         {
1590           int actual_ok;
1591
1592           /* If a procedure is not already determined to be something else
1593              check if it is intrinsic.  */
1594           if (!sym->attr.intrinsic
1595               && !(sym->attr.external || sym->attr.use_assoc
1596                    || sym->attr.if_source == IFSRC_IFBODY)
1597               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1598             sym->attr.intrinsic = 1;
1599
1600           if (sym->attr.proc == PROC_ST_FUNCTION)
1601             {
1602               gfc_error ("Statement function '%s' at %L is not allowed as an "
1603                          "actual argument", sym->name, &e->where);
1604             }
1605
1606           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1607                                                sym->attr.subroutine);
1608           if (sym->attr.intrinsic && actual_ok == 0)
1609             {
1610               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1611                          "actual argument", sym->name, &e->where);
1612             }
1613
1614           if (sym->attr.contained && !sym->attr.use_assoc
1615               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1616             {
1617               if (gfc_notify_std (GFC_STD_F2008,
1618                                   "Fortran 2008: Internal procedure '%s' is"
1619                                   " used as actual argument at %L",
1620                                   sym->name, &e->where) == FAILURE)
1621                 return FAILURE;
1622             }
1623
1624           if (sym->attr.elemental && !sym->attr.intrinsic)
1625             {
1626               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1627                          "allowed as an actual argument at %L", sym->name,
1628                          &e->where);
1629             }
1630
1631           /* Check if a generic interface has a specific procedure
1632             with the same name before emitting an error.  */
1633           if (sym->attr.generic && count_specific_procs (e) != 1)
1634             return FAILURE;
1635           
1636           /* Just in case a specific was found for the expression.  */
1637           sym = e->symtree->n.sym;
1638
1639           /* If the symbol is the function that names the current (or
1640              parent) scope, then we really have a variable reference.  */
1641
1642           if (gfc_is_function_return_value (sym, sym->ns))
1643             goto got_variable;
1644
1645           /* If all else fails, see if we have a specific intrinsic.  */
1646           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1647             {
1648               gfc_intrinsic_sym *isym;
1649
1650               isym = gfc_find_function (sym->name);
1651               if (isym == NULL || !isym->specific)
1652                 {
1653                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1654                              "for the reference '%s' at %L", sym->name,
1655                              &e->where);
1656                   return FAILURE;
1657                 }
1658               sym->ts = isym->ts;
1659               sym->attr.intrinsic = 1;
1660               sym->attr.function = 1;
1661             }
1662
1663           if (gfc_resolve_expr (e) == FAILURE)
1664             return FAILURE;
1665           goto argument_list;
1666         }
1667
1668       /* See if the name is a module procedure in a parent unit.  */
1669
1670       if (was_declared (sym) || sym->ns->parent == NULL)
1671         goto got_variable;
1672
1673       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1674         {
1675           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1676           return FAILURE;
1677         }
1678
1679       if (parent_st == NULL)
1680         goto got_variable;
1681
1682       sym = parent_st->n.sym;
1683       e->symtree = parent_st;           /* Point to the right thing.  */
1684
1685       if (sym->attr.flavor == FL_PROCEDURE
1686           || sym->attr.intrinsic
1687           || sym->attr.external)
1688         {
1689           if (gfc_resolve_expr (e) == FAILURE)
1690             return FAILURE;
1691           goto argument_list;
1692         }
1693
1694     got_variable:
1695       e->expr_type = EXPR_VARIABLE;
1696       e->ts = sym->ts;
1697       if (sym->as != NULL)
1698         {
1699           e->rank = sym->as->rank;
1700           e->ref = gfc_get_ref ();
1701           e->ref->type = REF_ARRAY;
1702           e->ref->u.ar.type = AR_FULL;
1703           e->ref->u.ar.as = sym->as;
1704         }
1705
1706       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1707          primary.c (match_actual_arg). If above code determines that it
1708          is a  variable instead, it needs to be resolved as it was not
1709          done at the beginning of this function.  */
1710       save_need_full_assumed_size = need_full_assumed_size;
1711       if (e->expr_type != EXPR_VARIABLE)
1712         need_full_assumed_size = 0;
1713       if (gfc_resolve_expr (e) != SUCCESS)
1714         return FAILURE;
1715       need_full_assumed_size = save_need_full_assumed_size;
1716
1717     argument_list:
1718       /* Check argument list functions %VAL, %LOC and %REF.  There is
1719          nothing to do for %REF.  */
1720       if (arg->name && arg->name[0] == '%')
1721         {
1722           if (strncmp ("%VAL", arg->name, 4) == 0)
1723             {
1724               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1725                 {
1726                   gfc_error ("By-value argument at %L is not of numeric "
1727                              "type", &e->where);
1728                   return FAILURE;
1729                 }
1730
1731               if (e->rank)
1732                 {
1733                   gfc_error ("By-value argument at %L cannot be an array or "
1734                              "an array section", &e->where);
1735                 return FAILURE;
1736                 }
1737
1738               /* Intrinsics are still PROC_UNKNOWN here.  However,
1739                  since same file external procedures are not resolvable
1740                  in gfortran, it is a good deal easier to leave them to
1741                  intrinsic.c.  */
1742               if (ptype != PROC_UNKNOWN
1743                   && ptype != PROC_DUMMY
1744                   && ptype != PROC_EXTERNAL
1745                   && ptype != PROC_MODULE)
1746                 {
1747                   gfc_error ("By-value argument at %L is not allowed "
1748                              "in this context", &e->where);
1749                   return FAILURE;
1750                 }
1751             }
1752
1753           /* Statement functions have already been excluded above.  */
1754           else if (strncmp ("%LOC", arg->name, 4) == 0
1755                    && e->ts.type == BT_PROCEDURE)
1756             {
1757               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1758                 {
1759                   gfc_error ("Passing internal procedure at %L by location "
1760                              "not allowed", &e->where);
1761                   return FAILURE;
1762                 }
1763             }
1764         }
1765
1766       /* Fortran 2008, C1237.  */
1767       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1768           && gfc_has_ultimate_pointer (e))
1769         {
1770           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1771                      "component", &e->where);
1772           return FAILURE;
1773         }
1774     }
1775
1776   return SUCCESS;
1777 }
1778
1779
1780 /* Do the checks of the actual argument list that are specific to elemental
1781    procedures.  If called with c == NULL, we have a function, otherwise if
1782    expr == NULL, we have a subroutine.  */
1783
1784 static gfc_try
1785 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1786 {
1787   gfc_actual_arglist *arg0;
1788   gfc_actual_arglist *arg;
1789   gfc_symbol *esym = NULL;
1790   gfc_intrinsic_sym *isym = NULL;
1791   gfc_expr *e = NULL;
1792   gfc_intrinsic_arg *iformal = NULL;
1793   gfc_formal_arglist *eformal = NULL;
1794   bool formal_optional = false;
1795   bool set_by_optional = false;
1796   int i;
1797   int rank = 0;
1798
1799   /* Is this an elemental procedure?  */
1800   if (expr && expr->value.function.actual != NULL)
1801     {
1802       if (expr->value.function.esym != NULL
1803           && expr->value.function.esym->attr.elemental)
1804         {
1805           arg0 = expr->value.function.actual;
1806           esym = expr->value.function.esym;
1807         }
1808       else if (expr->value.function.isym != NULL
1809                && expr->value.function.isym->elemental)
1810         {
1811           arg0 = expr->value.function.actual;
1812           isym = expr->value.function.isym;
1813         }
1814       else
1815         return SUCCESS;
1816     }
1817   else if (c && c->ext.actual != NULL)
1818     {
1819       arg0 = c->ext.actual;
1820       
1821       if (c->resolved_sym)
1822         esym = c->resolved_sym;
1823       else
1824         esym = c->symtree->n.sym;
1825       gcc_assert (esym);
1826
1827       if (!esym->attr.elemental)
1828         return SUCCESS;
1829     }
1830   else
1831     return SUCCESS;
1832
1833   /* The rank of an elemental is the rank of its array argument(s).  */
1834   for (arg = arg0; arg; arg = arg->next)
1835     {
1836       if (arg->expr != NULL && arg->expr->rank > 0)
1837         {
1838           rank = arg->expr->rank;
1839           if (arg->expr->expr_type == EXPR_VARIABLE
1840               && arg->expr->symtree->n.sym->attr.optional)
1841             set_by_optional = true;
1842
1843           /* Function specific; set the result rank and shape.  */
1844           if (expr)
1845             {
1846               expr->rank = rank;
1847               if (!expr->shape && arg->expr->shape)
1848                 {
1849                   expr->shape = gfc_get_shape (rank);
1850                   for (i = 0; i < rank; i++)
1851                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1852                 }
1853             }
1854           break;
1855         }
1856     }
1857
1858   /* If it is an array, it shall not be supplied as an actual argument
1859      to an elemental procedure unless an array of the same rank is supplied
1860      as an actual argument corresponding to a nonoptional dummy argument of
1861      that elemental procedure(12.4.1.5).  */
1862   formal_optional = false;
1863   if (isym)
1864     iformal = isym->formal;
1865   else
1866     eformal = esym->formal;
1867
1868   for (arg = arg0; arg; arg = arg->next)
1869     {
1870       if (eformal)
1871         {
1872           if (eformal->sym && eformal->sym->attr.optional)
1873             formal_optional = true;
1874           eformal = eformal->next;
1875         }
1876       else if (isym && iformal)
1877         {
1878           if (iformal->optional)
1879             formal_optional = true;
1880           iformal = iformal->next;
1881         }
1882       else if (isym)
1883         formal_optional = true;
1884
1885       if (pedantic && arg->expr != NULL
1886           && arg->expr->expr_type == EXPR_VARIABLE
1887           && arg->expr->symtree->n.sym->attr.optional
1888           && formal_optional
1889           && arg->expr->rank
1890           && (set_by_optional || arg->expr->rank != rank)
1891           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1892         {
1893           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1894                        "MISSING, it cannot be the actual argument of an "
1895                        "ELEMENTAL procedure unless there is a non-optional "
1896                        "argument with the same rank (12.4.1.5)",
1897                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1898           return FAILURE;
1899         }
1900     }
1901
1902   for (arg = arg0; arg; arg = arg->next)
1903     {
1904       if (arg->expr == NULL || arg->expr->rank == 0)
1905         continue;
1906
1907       /* Being elemental, the last upper bound of an assumed size array
1908          argument must be present.  */
1909       if (resolve_assumed_size_actual (arg->expr))
1910         return FAILURE;
1911
1912       /* Elemental procedure's array actual arguments must conform.  */
1913       if (e != NULL)
1914         {
1915           if (gfc_check_conformance (arg->expr, e,
1916                                      "elemental procedure") == FAILURE)
1917             return FAILURE;
1918         }
1919       else
1920         e = arg->expr;
1921     }
1922
1923   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1924      is an array, the intent inout/out variable needs to be also an array.  */
1925   if (rank > 0 && esym && expr == NULL)
1926     for (eformal = esym->formal, arg = arg0; arg && eformal;
1927          arg = arg->next, eformal = eformal->next)
1928       if ((eformal->sym->attr.intent == INTENT_OUT
1929            || eformal->sym->attr.intent == INTENT_INOUT)
1930           && arg->expr && arg->expr->rank == 0)
1931         {
1932           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1933                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1934                      "actual argument is an array", &arg->expr->where,
1935                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1936                      : "INOUT", eformal->sym->name, esym->name);
1937           return FAILURE;
1938         }
1939   return SUCCESS;
1940 }
1941
1942
1943 /* This function does the checking of references to global procedures
1944    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1945    77 and 95 standards.  It checks for a gsymbol for the name, making
1946    one if it does not already exist.  If it already exists, then the
1947    reference being resolved must correspond to the type of gsymbol.
1948    Otherwise, the new symbol is equipped with the attributes of the
1949    reference.  The corresponding code that is called in creating
1950    global entities is parse.c.
1951
1952    In addition, for all but -std=legacy, the gsymbols are used to
1953    check the interfaces of external procedures from the same file.
1954    The namespace of the gsymbol is resolved and then, once this is
1955    done the interface is checked.  */
1956
1957
1958 static bool
1959 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1960 {
1961   if (!gsym_ns->proc_name->attr.recursive)
1962     return true;
1963
1964   if (sym->ns == gsym_ns)
1965     return false;
1966
1967   if (sym->ns->parent && sym->ns->parent == gsym_ns)
1968     return false;
1969
1970   return true;
1971 }
1972
1973 static bool
1974 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
1975 {
1976   if (gsym_ns->entries)
1977     {
1978       gfc_entry_list *entry = gsym_ns->entries;
1979
1980       for (; entry; entry = entry->next)
1981         {
1982           if (strcmp (sym->name, entry->sym->name) == 0)
1983             {
1984               if (strcmp (gsym_ns->proc_name->name,
1985                           sym->ns->proc_name->name) == 0)
1986                 return false;
1987
1988               if (sym->ns->parent
1989                   && strcmp (gsym_ns->proc_name->name,
1990                              sym->ns->parent->proc_name->name) == 0)
1991                 return false;
1992             }
1993         }
1994     }
1995   return true;
1996 }
1997
1998 static void
1999 resolve_global_procedure (gfc_symbol *sym, locus *where,
2000                           gfc_actual_arglist **actual, int sub)
2001 {
2002   gfc_gsymbol * gsym;
2003   gfc_namespace *ns;
2004   enum gfc_symbol_type type;
2005
2006   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
2007
2008   gsym = gfc_get_gsymbol (sym->name);
2009
2010   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
2011     gfc_global_used (gsym, where);
2012
2013   if (gfc_option.flag_whole_file
2014         && (sym->attr.if_source == IFSRC_UNKNOWN
2015             || sym->attr.if_source == IFSRC_IFBODY)
2016         && gsym->type != GSYM_UNKNOWN
2017         && gsym->ns
2018         && gsym->ns->resolved != -1
2019         && gsym->ns->proc_name
2020         && not_in_recursive (sym, gsym->ns)
2021         && not_entry_self_reference (sym, gsym->ns))
2022     {
2023       gfc_symbol *def_sym;
2024
2025       /* Resolve the gsymbol namespace if needed.  */
2026       if (!gsym->ns->resolved)
2027         {
2028           gfc_dt_list *old_dt_list;
2029
2030           /* Stash away derived types so that the backend_decls do not
2031              get mixed up.  */
2032           old_dt_list = gfc_derived_types;
2033           gfc_derived_types = NULL;
2034
2035           gfc_resolve (gsym->ns);
2036
2037           /* Store the new derived types with the global namespace.  */
2038           if (gfc_derived_types)
2039             gsym->ns->derived_types = gfc_derived_types;
2040
2041           /* Restore the derived types of this namespace.  */
2042           gfc_derived_types = old_dt_list;
2043         }
2044
2045       /* Make sure that translation for the gsymbol occurs before
2046          the procedure currently being resolved.  */
2047       ns = gfc_global_ns_list;
2048       for (; ns && ns != gsym->ns; ns = ns->sibling)
2049         {
2050           if (ns->sibling == gsym->ns)
2051             {
2052               ns->sibling = gsym->ns->sibling;
2053               gsym->ns->sibling = gfc_global_ns_list;
2054               gfc_global_ns_list = gsym->ns;
2055               break;
2056             }
2057         }
2058
2059       def_sym = gsym->ns->proc_name;
2060       if (def_sym->attr.entry_master)
2061         {
2062           gfc_entry_list *entry;
2063           for (entry = gsym->ns->entries; entry; entry = entry->next)
2064             if (strcmp (entry->sym->name, sym->name) == 0)
2065               {
2066                 def_sym = entry->sym;
2067                 break;
2068               }
2069         }
2070
2071       /* Differences in constant character lengths.  */
2072       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
2073         {
2074           long int l1 = 0, l2 = 0;
2075           gfc_charlen *cl1 = sym->ts.u.cl;
2076           gfc_charlen *cl2 = def_sym->ts.u.cl;
2077
2078           if (cl1 != NULL
2079               && cl1->length != NULL
2080               && cl1->length->expr_type == EXPR_CONSTANT)
2081             l1 = mpz_get_si (cl1->length->value.integer);
2082
2083           if (cl2 != NULL
2084               && cl2->length != NULL
2085               && cl2->length->expr_type == EXPR_CONSTANT)
2086             l2 = mpz_get_si (cl2->length->value.integer);
2087
2088           if (l1 && l2 && l1 != l2)
2089             gfc_error ("Character length mismatch in return type of "
2090                        "function '%s' at %L (%ld/%ld)", sym->name,
2091                        &sym->declared_at, l1, l2);
2092         }
2093
2094      /* Type mismatch of function return type and expected type.  */
2095      if (sym->attr.function
2096          && !gfc_compare_types (&sym->ts, &def_sym->ts))
2097         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
2098                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2099                    gfc_typename (&def_sym->ts));
2100
2101       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
2102         {
2103           gfc_formal_arglist *arg = def_sym->formal;
2104           for ( ; arg; arg = arg->next)
2105             if (!arg->sym)
2106               continue;
2107             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
2108             else if (arg->sym->attr.allocatable
2109                      || arg->sym->attr.asynchronous
2110                      || arg->sym->attr.optional
2111                      || arg->sym->attr.pointer
2112                      || arg->sym->attr.target
2113                      || arg->sym->attr.value
2114                      || arg->sym->attr.volatile_)
2115               {
2116                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
2117                            "has an attribute that requires an explicit "
2118                            "interface for this procedure", arg->sym->name,
2119                            sym->name, &sym->declared_at);
2120                 break;
2121               }
2122             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
2123             else if (arg->sym && arg->sym->as
2124                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
2125               {
2126                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
2127                            "argument '%s' must have an explicit interface",
2128                            sym->name, &sym->declared_at, arg->sym->name);
2129                 break;
2130               }
2131             /* F2008, 12.4.2.2 (2c)  */
2132             else if (arg->sym->attr.codimension)
2133               {
2134                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
2135                            "'%s' must have an explicit interface",
2136                            sym->name, &sym->declared_at, arg->sym->name);
2137                 break;
2138               }
2139             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
2140             else if (false) /* TODO: is a parametrized derived type  */
2141               {
2142                 gfc_error ("Procedure '%s' at %L with parametrized derived "
2143                            "type argument '%s' must have an explicit "
2144                            "interface", sym->name, &sym->declared_at,
2145                            arg->sym->name);
2146                 break;
2147               }
2148             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
2149             else if (arg->sym->ts.type == BT_CLASS)
2150               {
2151                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
2152                            "argument '%s' must have an explicit interface",
2153                            sym->name, &sym->declared_at, arg->sym->name);
2154                 break;
2155               }
2156         }
2157
2158       if (def_sym->attr.function)
2159         {
2160           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
2161           if (def_sym->as && def_sym->as->rank
2162               && (!sym->as || sym->as->rank != def_sym->as->rank))
2163             gfc_error ("The reference to function '%s' at %L either needs an "
2164                        "explicit INTERFACE or the rank is incorrect", sym->name,
2165                        where);
2166
2167           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
2168           if ((def_sym->result->attr.pointer
2169                || def_sym->result->attr.allocatable)
2170                && (sym->attr.if_source != IFSRC_IFBODY
2171                    || def_sym->result->attr.pointer
2172                         != sym->result->attr.pointer
2173                    || def_sym->result->attr.allocatable
2174                         != sym->result->attr.allocatable))
2175             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
2176                        "result must have an explicit interface", sym->name,
2177                        where);
2178
2179           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
2180           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
2181               && def_sym->ts.u.cl->length != NULL)
2182             {
2183               gfc_charlen *cl = sym->ts.u.cl;
2184
2185               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
2186                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
2187                 {
2188                   gfc_error ("Nonconstant character-length function '%s' at %L "
2189                              "must have an explicit interface", sym->name,
2190                              &sym->declared_at);
2191                 }
2192             }
2193         }
2194
2195       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2196       if (def_sym->attr.elemental && !sym->attr.elemental)
2197         {
2198           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2199                      "interface", sym->name, &sym->declared_at);
2200         }
2201
2202       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2203       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2204         {
2205           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2206                      "an explicit interface", sym->name, &sym->declared_at);
2207         }
2208
2209       if (gfc_option.flag_whole_file == 1
2210           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2211               && !(gfc_option.warn_std & GFC_STD_GNU)))
2212         gfc_errors_to_warnings (1);
2213
2214       if (sym->attr.if_source != IFSRC_IFBODY)  
2215         gfc_procedure_use (def_sym, actual, where);
2216
2217       gfc_errors_to_warnings (0);
2218     }
2219
2220   if (gsym->type == GSYM_UNKNOWN)
2221     {
2222       gsym->type = type;
2223       gsym->where = *where;
2224     }
2225
2226   gsym->used = 1;
2227 }
2228
2229
2230 /************* Function resolution *************/
2231
2232 /* Resolve a function call known to be generic.
2233    Section 14.1.2.4.1.  */
2234
2235 static match
2236 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2237 {
2238   gfc_symbol *s;
2239
2240   if (sym->attr.generic)
2241     {
2242       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2243       if (s != NULL)
2244         {
2245           expr->value.function.name = s->name;
2246           expr->value.function.esym = s;
2247
2248           if (s->ts.type != BT_UNKNOWN)
2249             expr->ts = s->ts;
2250           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2251             expr->ts = s->result->ts;
2252
2253           if (s->as != NULL)
2254             expr->rank = s->as->rank;
2255           else if (s->result != NULL && s->result->as != NULL)
2256             expr->rank = s->result->as->rank;
2257
2258           gfc_set_sym_referenced (expr->value.function.esym);
2259
2260           return MATCH_YES;
2261         }
2262
2263       /* TODO: Need to search for elemental references in generic
2264          interface.  */
2265     }
2266
2267   if (sym->attr.intrinsic)
2268     return gfc_intrinsic_func_interface (expr, 0);
2269
2270   return MATCH_NO;
2271 }
2272
2273
2274 static gfc_try
2275 resolve_generic_f (gfc_expr *expr)
2276 {
2277   gfc_symbol *sym;
2278   match m;
2279
2280   sym = expr->symtree->n.sym;
2281
2282   for (;;)
2283     {
2284       m = resolve_generic_f0 (expr, sym);
2285       if (m == MATCH_YES)
2286         return SUCCESS;
2287       else if (m == MATCH_ERROR)
2288         return FAILURE;
2289
2290 generic:
2291       if (sym->ns->parent == NULL)
2292         break;
2293       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2294
2295       if (sym == NULL)
2296         break;
2297       if (!generic_sym (sym))
2298         goto generic;
2299     }
2300
2301   /* Last ditch attempt.  See if the reference is to an intrinsic
2302      that possesses a matching interface.  14.1.2.4  */
2303   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
2304     {
2305       gfc_error ("There is no specific function for the generic '%s' at %L",
2306                  expr->symtree->n.sym->name, &expr->where);
2307       return FAILURE;
2308     }
2309
2310   m = gfc_intrinsic_func_interface (expr, 0);
2311   if (m == MATCH_YES)
2312     return SUCCESS;
2313   if (m == MATCH_NO)
2314     gfc_error ("Generic function '%s' at %L is not consistent with a "
2315                "specific intrinsic interface", expr->symtree->n.sym->name,
2316                &expr->where);
2317
2318   return FAILURE;
2319 }
2320
2321
2322 /* Resolve a function call known to be specific.  */
2323
2324 static match
2325 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2326 {
2327   match m;
2328
2329   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2330     {
2331       if (sym->attr.dummy)
2332         {
2333           sym->attr.proc = PROC_DUMMY;
2334           goto found;
2335         }
2336
2337       sym->attr.proc = PROC_EXTERNAL;
2338       goto found;
2339     }
2340
2341   if (sym->attr.proc == PROC_MODULE
2342       || sym->attr.proc == PROC_ST_FUNCTION
2343       || sym->attr.proc == PROC_INTERNAL)
2344     goto found;
2345
2346   if (sym->attr.intrinsic)
2347     {
2348       m = gfc_intrinsic_func_interface (expr, 1);
2349       if (m == MATCH_YES)
2350         return MATCH_YES;
2351       if (m == MATCH_NO)
2352         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2353                    "with an intrinsic", sym->name, &expr->where);
2354
2355       return MATCH_ERROR;
2356     }
2357
2358   return MATCH_NO;
2359
2360 found:
2361   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2362
2363   if (sym->result)
2364     expr->ts = sym->result->ts;
2365   else
2366     expr->ts = sym->ts;
2367   expr->value.function.name = sym->name;
2368   expr->value.function.esym = sym;
2369   if (sym->as != NULL)
2370     expr->rank = sym->as->rank;
2371
2372   return MATCH_YES;
2373 }
2374
2375
2376 static gfc_try
2377 resolve_specific_f (gfc_expr *expr)
2378 {
2379   gfc_symbol *sym;
2380   match m;
2381
2382   sym = expr->symtree->n.sym;
2383
2384   for (;;)
2385     {
2386       m = resolve_specific_f0 (sym, expr);
2387       if (m == MATCH_YES)
2388         return SUCCESS;
2389       if (m == MATCH_ERROR)
2390         return FAILURE;
2391
2392       if (sym->ns->parent == NULL)
2393         break;
2394
2395       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2396
2397       if (sym == NULL)
2398         break;
2399     }
2400
2401   gfc_error ("Unable to resolve the specific function '%s' at %L",
2402              expr->symtree->n.sym->name, &expr->where);
2403
2404   return SUCCESS;
2405 }
2406
2407
2408 /* Resolve a procedure call not known to be generic nor specific.  */
2409
2410 static gfc_try
2411 resolve_unknown_f (gfc_expr *expr)
2412 {
2413   gfc_symbol *sym;
2414   gfc_typespec *ts;
2415
2416   sym = expr->symtree->n.sym;
2417
2418   if (sym->attr.dummy)
2419     {
2420       sym->attr.proc = PROC_DUMMY;
2421       expr->value.function.name = sym->name;
2422       goto set_type;
2423     }
2424
2425   /* See if we have an intrinsic function reference.  */
2426
2427   if (gfc_is_intrinsic (sym, 0, expr->where))
2428     {
2429       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2430         return SUCCESS;
2431       return FAILURE;
2432     }
2433
2434   /* The reference is to an external name.  */
2435
2436   sym->attr.proc = PROC_EXTERNAL;
2437   expr->value.function.name = sym->name;
2438   expr->value.function.esym = expr->symtree->n.sym;
2439
2440   if (sym->as != NULL)
2441     expr->rank = sym->as->rank;
2442
2443   /* Type of the expression is either the type of the symbol or the
2444      default type of the symbol.  */
2445
2446 set_type:
2447   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2448
2449   if (sym->ts.type != BT_UNKNOWN)
2450     expr->ts = sym->ts;
2451   else
2452     {
2453       ts = gfc_get_default_type (sym->name, sym->ns);
2454
2455       if (ts->type == BT_UNKNOWN)
2456         {
2457           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2458                      sym->name, &expr->where);
2459           return FAILURE;
2460         }
2461       else
2462         expr->ts = *ts;
2463     }
2464
2465   return SUCCESS;
2466 }
2467
2468
2469 /* Return true, if the symbol is an external procedure.  */
2470 static bool
2471 is_external_proc (gfc_symbol *sym)
2472 {
2473   if (!sym->attr.dummy && !sym->attr.contained
2474         && !(sym->attr.intrinsic
2475               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2476         && sym->attr.proc != PROC_ST_FUNCTION
2477         && !sym->attr.proc_pointer
2478         && !sym->attr.use_assoc
2479         && sym->name)
2480     return true;
2481
2482   return false;
2483 }
2484
2485
2486 /* Figure out if a function reference is pure or not.  Also set the name
2487    of the function for a potential error message.  Return nonzero if the
2488    function is PURE, zero if not.  */
2489 static int
2490 pure_stmt_function (gfc_expr *, gfc_symbol *);
2491
2492 static int
2493 pure_function (gfc_expr *e, const char **name)
2494 {
2495   int pure;
2496
2497   *name = NULL;
2498
2499   if (e->symtree != NULL
2500         && e->symtree->n.sym != NULL
2501         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2502     return pure_stmt_function (e, e->symtree->n.sym);
2503
2504   if (e->value.function.esym)
2505     {
2506       pure = gfc_pure (e->value.function.esym);
2507       *name = e->value.function.esym->name;
2508     }
2509   else if (e->value.function.isym)
2510     {
2511       pure = e->value.function.isym->pure
2512              || e->value.function.isym->elemental;
2513       *name = e->value.function.isym->name;
2514     }
2515   else
2516     {
2517       /* Implicit functions are not pure.  */
2518       pure = 0;
2519       *name = e->value.function.name;
2520     }
2521
2522   return pure;
2523 }
2524
2525
2526 static bool
2527 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2528                  int *f ATTRIBUTE_UNUSED)
2529 {
2530   const char *name;
2531
2532   /* Don't bother recursing into other statement functions
2533      since they will be checked individually for purity.  */
2534   if (e->expr_type != EXPR_FUNCTION
2535         || !e->symtree
2536         || e->symtree->n.sym == sym
2537         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2538     return false;
2539
2540   return pure_function (e, &name) ? false : true;
2541 }
2542
2543
2544 static int
2545 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2546 {
2547   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2548 }
2549
2550
2551 static gfc_try
2552 is_scalar_expr_ptr (gfc_expr *expr)
2553 {
2554   gfc_try retval = SUCCESS;
2555   gfc_ref *ref;
2556   int start;
2557   int end;
2558
2559   /* See if we have a gfc_ref, which means we have a substring, array
2560      reference, or a component.  */
2561   if (expr->ref != NULL)
2562     {
2563       ref = expr->ref;
2564       while (ref->next != NULL)
2565         ref = ref->next;
2566
2567       switch (ref->type)
2568         {
2569         case REF_SUBSTRING:
2570           if (ref->u.ss.start == NULL || ref->u.ss.end == NULL
2571               || gfc_dep_compare_expr (ref->u.ss.start, ref->u.ss.end) != 0)
2572             retval = FAILURE;
2573           break;
2574
2575         case REF_ARRAY:
2576           if (ref->u.ar.type == AR_ELEMENT)
2577             retval = SUCCESS;
2578           else if (ref->u.ar.type == AR_FULL)
2579             {
2580               /* The user can give a full array if the array is of size 1.  */
2581               if (ref->u.ar.as != NULL
2582                   && ref->u.ar.as->rank == 1
2583                   && ref->u.ar.as->type == AS_EXPLICIT
2584                   && ref->u.ar.as->lower[0] != NULL
2585                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2586                   && ref->u.ar.as->upper[0] != NULL
2587                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2588                 {
2589                   /* If we have a character string, we need to check if
2590                      its length is one.  */
2591                   if (expr->ts.type == BT_CHARACTER)
2592                     {
2593                       if (expr->ts.u.cl == NULL
2594                           || expr->ts.u.cl->length == NULL
2595                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2596                           != 0)
2597                         retval = FAILURE;
2598                     }
2599                   else
2600                     {
2601                       /* We have constant lower and upper bounds.  If the
2602                          difference between is 1, it can be considered a
2603                          scalar.  
2604                          FIXME: Use gfc_dep_compare_expr instead.  */
2605                       start = (int) mpz_get_si
2606                                 (ref->u.ar.as->lower[0]->value.integer);
2607                       end = (int) mpz_get_si
2608                                 (ref->u.ar.as->upper[0]->value.integer);
2609                       if (end - start + 1 != 1)
2610                         retval = FAILURE;
2611                    }
2612                 }
2613               else
2614                 retval = FAILURE;
2615             }
2616           else
2617             retval = FAILURE;
2618           break;
2619         default:
2620           retval = SUCCESS;
2621           break;
2622         }
2623     }
2624   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2625     {
2626       /* Character string.  Make sure it's of length 1.  */
2627       if (expr->ts.u.cl == NULL
2628           || expr->ts.u.cl->length == NULL
2629           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2630         retval = FAILURE;
2631     }
2632   else if (expr->rank != 0)
2633     retval = FAILURE;
2634
2635   return retval;
2636 }
2637
2638
2639 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2640    and, in the case of c_associated, set the binding label based on
2641    the arguments.  */
2642
2643 static gfc_try
2644 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2645                           gfc_symbol **new_sym)
2646 {
2647   char name[GFC_MAX_SYMBOL_LEN + 1];
2648   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2649   int optional_arg = 0;
2650   gfc_try retval = SUCCESS;
2651   gfc_symbol *args_sym;
2652   gfc_typespec *arg_ts;
2653   symbol_attribute arg_attr;
2654
2655   if (args->expr->expr_type == EXPR_CONSTANT
2656       || args->expr->expr_type == EXPR_OP
2657       || args->expr->expr_type == EXPR_NULL)
2658     {
2659       gfc_error ("Argument to '%s' at %L is not a variable",
2660                  sym->name, &(args->expr->where));
2661       return FAILURE;
2662     }
2663
2664   args_sym = args->expr->symtree->n.sym;
2665
2666   /* The typespec for the actual arg should be that stored in the expr
2667      and not necessarily that of the expr symbol (args_sym), because
2668      the actual expression could be a part-ref of the expr symbol.  */
2669   arg_ts = &(args->expr->ts);
2670   arg_attr = gfc_expr_attr (args->expr);
2671     
2672   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2673     {
2674       /* If the user gave two args then they are providing something for
2675          the optional arg (the second cptr).  Therefore, set the name and
2676          binding label to the c_associated for two cptrs.  Otherwise,
2677          set c_associated to expect one cptr.  */
2678       if (args->next)
2679         {
2680           /* two args.  */
2681           sprintf (name, "%s_2", sym->name);
2682           sprintf (binding_label, "%s_2", sym->binding_label);
2683           optional_arg = 1;
2684         }
2685       else
2686         {
2687           /* one arg.  */
2688           sprintf (name, "%s_1", sym->name);
2689           sprintf (binding_label, "%s_1", sym->binding_label);
2690           optional_arg = 0;
2691         }
2692
2693       /* Get a new symbol for the version of c_associated that
2694          will get called.  */
2695       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2696     }
2697   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2698            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2699     {
2700       sprintf (name, "%s", sym->name);
2701       sprintf (binding_label, "%s", sym->binding_label);
2702
2703       /* Error check the call.  */
2704       if (args->next != NULL)
2705         {
2706           gfc_error_now ("More actual than formal arguments in '%s' "
2707                          "call at %L", name, &(args->expr->where));
2708           retval = FAILURE;
2709         }
2710       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2711         {
2712           /* Make sure we have either the target or pointer attribute.  */
2713           if (!arg_attr.target && !arg_attr.pointer)
2714             {
2715               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2716                              "a TARGET or an associated pointer",
2717                              args_sym->name,
2718                              sym->name, &(args->expr->where));
2719               retval = FAILURE;
2720             }
2721
2722           /* See if we have interoperable type and type param.  */
2723           if (verify_c_interop (arg_ts) == SUCCESS
2724               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2725             {
2726               if (args_sym->attr.target == 1)
2727                 {
2728                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2729                      has the target attribute and is interoperable.  */
2730                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2731                      allocatable variable that has the TARGET attribute and
2732                      is not an array of zero size.  */
2733                   if (args_sym->attr.allocatable == 1)
2734                     {
2735                       if (args_sym->attr.dimension != 0 
2736                           && (args_sym->as && args_sym->as->rank == 0))
2737                         {
2738                           gfc_error_now ("Allocatable variable '%s' used as a "
2739                                          "parameter to '%s' at %L must not be "
2740                                          "an array of zero size",
2741                                          args_sym->name, sym->name,
2742                                          &(args->expr->where));
2743                           retval = FAILURE;
2744                         }
2745                     }
2746                   else
2747                     {
2748                       /* A non-allocatable target variable with C
2749                          interoperable type and type parameters must be
2750                          interoperable.  */
2751                       if (args_sym && args_sym->attr.dimension)
2752                         {
2753                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2754                             {
2755                               gfc_error ("Assumed-shape array '%s' at %L "
2756                                          "cannot be an argument to the "
2757                                          "procedure '%s' because "
2758                                          "it is not C interoperable",
2759                                          args_sym->name,
2760                                          &(args->expr->where), sym->name);
2761                               retval = FAILURE;
2762                             }
2763                           else if (args_sym->as->type == AS_DEFERRED)
2764                             {
2765                               gfc_error ("Deferred-shape array '%s' at %L "
2766                                          "cannot be an argument to the "
2767                                          "procedure '%s' because "
2768                                          "it is not C interoperable",
2769                                          args_sym->name,
2770                                          &(args->expr->where), sym->name);
2771                               retval = FAILURE;
2772                             }
2773                         }
2774                               
2775                       /* Make sure it's not a character string.  Arrays of
2776                          any type should be ok if the variable is of a C
2777                          interoperable type.  */
2778                       if (arg_ts->type == BT_CHARACTER)
2779                         if (arg_ts->u.cl != NULL
2780                             && (arg_ts->u.cl->length == NULL
2781                                 || arg_ts->u.cl->length->expr_type
2782                                    != EXPR_CONSTANT
2783                                 || mpz_cmp_si
2784                                     (arg_ts->u.cl->length->value.integer, 1)
2785                                    != 0)
2786                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2787                           {
2788                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2789                                            "at %L must have a length of 1",
2790                                            args_sym->name, sym->name,
2791                                            &(args->expr->where));
2792                             retval = FAILURE;
2793                           }
2794                     }
2795                 }
2796               else if (arg_attr.pointer
2797                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2798                 {
2799                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2800                      scalar pointer.  */
2801                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2802                                  "associated scalar POINTER", args_sym->name,
2803                                  sym->name, &(args->expr->where));
2804                   retval = FAILURE;
2805                 }
2806             }
2807           else
2808             {
2809               /* The parameter is not required to be C interoperable.  If it
2810                  is not C interoperable, it must be a nonpolymorphic scalar
2811                  with no length type parameters.  It still must have either
2812                  the pointer or target attribute, and it can be
2813                  allocatable (but must be allocated when c_loc is called).  */
2814               if (args->expr->rank != 0 
2815                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2816                 {
2817                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2818                                  "scalar", args_sym->name, sym->name,
2819                                  &(args->expr->where));
2820                   retval = FAILURE;
2821                 }
2822               else if (arg_ts->type == BT_CHARACTER 
2823                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2824                 {
2825                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2826                                  "%L must have a length of 1",
2827                                  args_sym->name, sym->name,
2828                                  &(args->expr->where));
2829                   retval = FAILURE;
2830                 }
2831               else if (arg_ts->type == BT_CLASS)
2832                 {
2833                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
2834                                  "polymorphic", args_sym->name, sym->name,
2835                                  &(args->expr->where));
2836                   retval = FAILURE;
2837                 }
2838             }
2839         }
2840       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2841         {
2842           if (args_sym->attr.flavor != FL_PROCEDURE)
2843             {
2844               /* TODO: Update this error message to allow for procedure
2845                  pointers once they are implemented.  */
2846               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2847                              "procedure",
2848                              args_sym->name, sym->name,
2849                              &(args->expr->where));
2850               retval = FAILURE;
2851             }
2852           else if (args_sym->attr.is_bind_c != 1)
2853             {
2854               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2855                              "BIND(C)",
2856                              args_sym->name, sym->name,
2857                              &(args->expr->where));
2858               retval = FAILURE;
2859             }
2860         }
2861       
2862       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2863       *new_sym = sym;
2864     }
2865   else
2866     {
2867       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2868                           "iso_c_binding function: '%s'!\n", sym->name);
2869     }
2870
2871   return retval;
2872 }
2873
2874
2875 /* Resolve a function call, which means resolving the arguments, then figuring
2876    out which entity the name refers to.  */
2877
2878 static gfc_try
2879 resolve_function (gfc_expr *expr)
2880 {
2881   gfc_actual_arglist *arg;
2882   gfc_symbol *sym;
2883   const char *name;
2884   gfc_try t;
2885   int temp;
2886   procedure_type p = PROC_INTRINSIC;
2887   bool no_formal_args;
2888
2889   sym = NULL;
2890   if (expr->symtree)
2891     sym = expr->symtree->n.sym;
2892
2893   /* If this is a procedure pointer component, it has already been resolved.  */
2894   if (gfc_is_proc_ptr_comp (expr, NULL))
2895     return SUCCESS;
2896   
2897   if (sym && sym->attr.intrinsic
2898       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2899     return FAILURE;
2900
2901   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2902     {
2903       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2904       return FAILURE;
2905     }
2906
2907   /* If this ia a deferred TBP with an abstract interface (which may
2908      of course be referenced), expr->value.function.esym will be set.  */
2909   if (sym && sym->attr.abstract && !expr->value.function.esym)
2910     {
2911       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2912                  sym->name, &expr->where);
2913       return FAILURE;
2914     }
2915
2916   /* Switch off assumed size checking and do this again for certain kinds
2917      of procedure, once the procedure itself is resolved.  */
2918   need_full_assumed_size++;
2919
2920   if (expr->symtree && expr->symtree->n.sym)
2921     p = expr->symtree->n.sym->attr.proc;
2922
2923   if (expr->value.function.isym && expr->value.function.isym->inquiry)
2924     inquiry_argument = true;
2925   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2926
2927   if (resolve_actual_arglist (expr->value.function.actual,
2928                               p, no_formal_args) == FAILURE)
2929     {
2930       inquiry_argument = false;
2931       return FAILURE;
2932     }
2933
2934   inquiry_argument = false;
2935  
2936   /* Need to setup the call to the correct c_associated, depending on
2937      the number of cptrs to user gives to compare.  */
2938   if (sym && sym->attr.is_iso_c == 1)
2939     {
2940       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
2941           == FAILURE)
2942         return FAILURE;
2943       
2944       /* Get the symtree for the new symbol (resolved func).
2945          the old one will be freed later, when it's no longer used.  */
2946       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
2947     }
2948   
2949   /* Resume assumed_size checking.  */
2950   need_full_assumed_size--;
2951
2952   /* If the procedure is external, check for usage.  */
2953   if (sym && is_external_proc (sym))
2954     resolve_global_procedure (sym, &expr->where,
2955                               &expr->value.function.actual, 0);
2956
2957   if (sym && sym->ts.type == BT_CHARACTER
2958       && sym->ts.u.cl
2959       && sym->ts.u.cl->length == NULL
2960       && !sym->attr.dummy
2961       && expr->value.function.esym == NULL
2962       && !sym->attr.contained)
2963     {
2964       /* Internal procedures are taken care of in resolve_contained_fntype.  */
2965       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
2966                  "be used at %L since it is not a dummy argument",
2967                  sym->name, &expr->where);
2968       return FAILURE;
2969     }
2970
2971   /* See if function is already resolved.  */
2972
2973   if (expr->value.function.name != NULL)
2974     {
2975       if (expr->ts.type == BT_UNKNOWN)
2976         expr->ts = sym->ts;
2977       t = SUCCESS;
2978     }
2979   else
2980     {
2981       /* Apply the rules of section 14.1.2.  */
2982
2983       switch (procedure_kind (sym))
2984         {
2985         case PTYPE_GENERIC:
2986           t = resolve_generic_f (expr);
2987           break;
2988
2989         case PTYPE_SPECIFIC:
2990           t = resolve_specific_f (expr);
2991           break;
2992
2993         case PTYPE_UNKNOWN:
2994           t = resolve_unknown_f (expr);
2995           break;
2996
2997         default:
2998           gfc_internal_error ("resolve_function(): bad function type");
2999         }
3000     }
3001
3002   /* If the expression is still a function (it might have simplified),
3003      then we check to see if we are calling an elemental function.  */
3004
3005   if (expr->expr_type != EXPR_FUNCTION)
3006     return t;
3007
3008   temp = need_full_assumed_size;
3009   need_full_assumed_size = 0;
3010
3011   if (resolve_elemental_actual (expr, NULL) == FAILURE)
3012     return FAILURE;
3013
3014   if (omp_workshare_flag
3015       && expr->value.function.esym
3016       && ! gfc_elemental (expr->value.function.esym))
3017     {
3018       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
3019                  "in WORKSHARE construct", expr->value.function.esym->name,
3020                  &expr->where);
3021       t = FAILURE;
3022     }
3023
3024 #define GENERIC_ID expr->value.function.isym->id
3025   else if (expr->value.function.actual != NULL
3026            && expr->value.function.isym != NULL
3027            && GENERIC_ID != GFC_ISYM_LBOUND
3028            && GENERIC_ID != GFC_ISYM_LEN
3029            && GENERIC_ID != GFC_ISYM_LOC
3030            && GENERIC_ID != GFC_ISYM_PRESENT)
3031     {
3032       /* Array intrinsics must also have the last upper bound of an
3033          assumed size array argument.  UBOUND and SIZE have to be
3034          excluded from the check if the second argument is anything
3035          than a constant.  */
3036
3037       for (arg = expr->value.function.actual; arg; arg = arg->next)
3038         {
3039           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3040               && arg->next != NULL && arg->next->expr)
3041             {
3042               if (arg->next->expr->expr_type != EXPR_CONSTANT)
3043                 break;
3044
3045               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
3046                 break;
3047
3048               if ((int)mpz_get_si (arg->next->expr->value.integer)
3049                         < arg->expr->rank)
3050                 break;
3051             }
3052
3053           if (arg->expr != NULL
3054               && arg->expr->rank > 0
3055               && resolve_assumed_size_actual (arg->expr))
3056             return FAILURE;
3057         }
3058     }
3059 #undef GENERIC_ID
3060
3061   need_full_assumed_size = temp;
3062   name = NULL;
3063
3064   if (!pure_function (expr, &name) && name)
3065     {
3066       if (forall_flag)
3067         {
3068           gfc_error ("reference to non-PURE function '%s' at %L inside a "
3069                      "FORALL %s", name, &expr->where,
3070                      forall_flag == 2 ? "mask" : "block");
3071           t = FAILURE;
3072         }
3073       else if (gfc_pure (NULL))
3074         {
3075           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
3076                      "procedure within a PURE procedure", name, &expr->where);
3077           t = FAILURE;
3078         }
3079     }
3080
3081   if (!pure_function (expr, &name) && name && gfc_implicit_pure (NULL))
3082     gfc_current_ns->proc_name->attr.implicit_pure = 0;
3083
3084   /* Functions without the RECURSIVE attribution are not allowed to
3085    * call themselves.  */
3086   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3087     {
3088       gfc_symbol *esym;
3089       esym = expr->value.function.esym;
3090
3091       if (is_illegal_recursion (esym, gfc_current_ns))
3092       {
3093         if (esym->attr.entry && esym->ns->entries)
3094           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3095                      " function '%s' is not RECURSIVE",
3096                      esym->name, &expr->where, esym->ns->entries->sym->name);
3097         else
3098           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
3099                      " is not RECURSIVE", esym->name, &expr->where);
3100
3101         t = FAILURE;
3102       }
3103     }
3104
3105   /* Character lengths of use associated functions may contains references to
3106      symbols not referenced from the current program unit otherwise.  Make sure
3107      those symbols are marked as referenced.  */
3108
3109   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3110       && expr->value.function.esym->attr.use_assoc)
3111     {
3112       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3113     }
3114
3115   /* Make sure that the expression has a typespec that works.  */
3116   if (expr->ts.type == BT_UNKNOWN)
3117     {
3118       if (expr->symtree->n.sym->result
3119             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3120             && !expr->symtree->n.sym->result->attr.proc_pointer)
3121         expr->ts = expr->symtree->n.sym->result->ts;
3122     }
3123
3124   return t;
3125 }
3126
3127
3128 /************* Subroutine resolution *************/
3129
3130 static void
3131 pure_subroutine (gfc_code *c, gfc_symbol *sym)
3132 {
3133   if (gfc_pure (sym))
3134     return;
3135
3136   if (forall_flag)
3137     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
3138                sym->name, &c->loc);
3139   else if (gfc_pure (NULL))
3140     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
3141                &c->loc);
3142 }
3143
3144
3145 static match
3146 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3147 {
3148   gfc_symbol *s;
3149
3150   if (sym->attr.generic)
3151     {
3152       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3153       if (s != NULL)
3154         {
3155           c->resolved_sym = s;
3156           pure_subroutine (c, s);
3157           return MATCH_YES;
3158         }
3159
3160       /* TODO: Need to search for elemental references in generic interface.  */
3161     }
3162
3163   if (sym->attr.intrinsic)
3164     return gfc_intrinsic_sub_interface (c, 0);
3165
3166   return MATCH_NO;
3167 }
3168
3169
3170 static gfc_try
3171 resolve_generic_s (gfc_code *c)
3172 {
3173   gfc_symbol *sym;
3174   match m;
3175
3176   sym = c->symtree->n.sym;
3177
3178   for (;;)
3179     {
3180       m = resolve_generic_s0 (c, sym);
3181       if (m == MATCH_YES)
3182         return SUCCESS;
3183       else if (m == MATCH_ERROR)
3184         return FAILURE;
3185
3186 generic:
3187       if (sym->ns->parent == NULL)
3188         break;
3189       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3190
3191       if (sym == NULL)
3192         break;
3193       if (!generic_sym (sym))
3194         goto generic;
3195     }
3196
3197   /* Last ditch attempt.  See if the reference is to an intrinsic
3198      that possesses a matching interface.  14.1.2.4  */
3199   sym = c->symtree->n.sym;
3200
3201   if (!gfc_is_intrinsic (sym, 1, c->loc))
3202     {
3203       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3204                  sym->name, &c->loc);
3205       return FAILURE;
3206     }
3207
3208   m = gfc_intrinsic_sub_interface (c, 0);
3209   if (m == MATCH_YES)
3210     return SUCCESS;
3211   if (m == MATCH_NO)
3212     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3213                "intrinsic subroutine interface", sym->name, &c->loc);
3214
3215   return FAILURE;
3216 }
3217
3218
3219 /* Set the name and binding label of the subroutine symbol in the call
3220    expression represented by 'c' to include the type and kind of the
3221    second parameter.  This function is for resolving the appropriate
3222    version of c_f_pointer() and c_f_procpointer().  For example, a
3223    call to c_f_pointer() for a default integer pointer could have a
3224    name of c_f_pointer_i4.  If no second arg exists, which is an error
3225    for these two functions, it defaults to the generic symbol's name
3226    and binding label.  */
3227
3228 static void
3229 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3230                     char *name, char *binding_label)
3231 {
3232   gfc_expr *arg = NULL;
3233   char type;
3234   int kind;
3235
3236   /* The second arg of c_f_pointer and c_f_procpointer determines
3237      the type and kind for the procedure name.  */
3238   arg = c->ext.actual->next->expr;
3239
3240   if (arg != NULL)
3241     {
3242       /* Set up the name to have the given symbol's name,
3243          plus the type and kind.  */
3244       /* a derived type is marked with the type letter 'u' */
3245       if (arg->ts.type == BT_DERIVED)
3246         {
3247           type = 'd';
3248           kind = 0; /* set the kind as 0 for now */
3249         }
3250       else
3251         {
3252           type = gfc_type_letter (arg->ts.type);
3253           kind = arg->ts.kind;
3254         }
3255
3256       if (arg->ts.type == BT_CHARACTER)
3257         /* Kind info for character strings not needed.  */
3258         kind = 0;
3259
3260       sprintf (name, "%s_%c%d", sym->name, type, kind);
3261       /* Set up the binding label as the given symbol's label plus
3262          the type and kind.  */
3263       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
3264     }
3265   else
3266     {
3267       /* If the second arg is missing, set the name and label as
3268          was, cause it should at least be found, and the missing
3269          arg error will be caught by compare_parameters().  */
3270       sprintf (name, "%s", sym->name);
3271       sprintf (binding_label, "%s", sym->binding_label);
3272     }
3273    
3274   return;
3275 }
3276
3277
3278 /* Resolve a generic version of the iso_c_binding procedure given
3279    (sym) to the specific one based on the type and kind of the
3280    argument(s).  Currently, this function resolves c_f_pointer() and
3281    c_f_procpointer based on the type and kind of the second argument
3282    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3283    Upon successfully exiting, c->resolved_sym will hold the resolved
3284    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3285    otherwise.  */
3286
3287 match
3288 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3289 {
3290   gfc_symbol *new_sym;
3291   /* this is fine, since we know the names won't use the max */
3292   char name[GFC_MAX_SYMBOL_LEN + 1];
3293   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3294   /* default to success; will override if find error */
3295   match m = MATCH_YES;
3296
3297   /* Make sure the actual arguments are in the necessary order (based on the 
3298      formal args) before resolving.  */
3299   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3300
3301   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3302       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3303     {
3304       set_name_and_label (c, sym, name, binding_label);
3305       
3306       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3307         {
3308           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3309             {
3310               /* Make sure we got a third arg if the second arg has non-zero
3311                  rank.  We must also check that the type and rank are
3312                  correct since we short-circuit this check in
3313                  gfc_procedure_use() (called above to sort actual args).  */
3314               if (c->ext.actual->next->expr->rank != 0)
3315                 {
3316                   if(c->ext.actual->next->next == NULL 
3317                      || c->ext.actual->next->next->expr == NULL)
3318                     {
3319                       m = MATCH_ERROR;
3320                       gfc_error ("Missing SHAPE parameter for call to %s "
3321                                  "at %L", sym->name, &(c->loc));
3322                     }
3323                   else if (c->ext.actual->next->next->expr->ts.type
3324                            != BT_INTEGER
3325                            || c->ext.actual->next->next->expr->rank != 1)
3326                     {
3327                       m = MATCH_ERROR;
3328                       gfc_error ("SHAPE parameter for call to %s at %L must "
3329                                  "be a rank 1 INTEGER array", sym->name,
3330                                  &(c->loc));
3331                     }
3332                 }
3333             }
3334         }
3335       
3336       if (m != MATCH_ERROR)
3337         {
3338           /* the 1 means to add the optional arg to formal list */
3339           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3340          
3341           /* for error reporting, say it's declared where the original was */
3342           new_sym->declared_at = sym->declared_at;
3343         }
3344     }
3345   else
3346     {
3347       /* no differences for c_loc or c_funloc */
3348       new_sym = sym;
3349     }
3350
3351   /* set the resolved symbol */
3352   if (m != MATCH_ERROR)
3353     c->resolved_sym = new_sym;
3354   else
3355     c->resolved_sym = sym;
3356   
3357   return m;
3358 }
3359
3360
3361 /* Resolve a subroutine call known to be specific.  */
3362
3363 static match
3364 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3365 {
3366   match m;
3367
3368   if(sym->attr.is_iso_c)
3369     {
3370       m = gfc_iso_c_sub_interface (c,sym);
3371       return m;
3372     }
3373   
3374   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3375     {
3376       if (sym->attr.dummy)
3377         {
3378           sym->attr.proc = PROC_DUMMY;
3379           goto found;
3380         }
3381
3382       sym->attr.proc = PROC_EXTERNAL;
3383       goto found;
3384     }
3385
3386   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3387     goto found;
3388
3389   if (sym->attr.intrinsic)
3390     {
3391       m = gfc_intrinsic_sub_interface (c, 1);
3392       if (m == MATCH_YES)
3393         return MATCH_YES;
3394       if (m == MATCH_NO)
3395         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3396                    "with an intrinsic", sym->name, &c->loc);
3397
3398       return MATCH_ERROR;
3399     }
3400
3401   return MATCH_NO;
3402
3403 found:
3404   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3405
3406   c->resolved_sym = sym;
3407   pure_subroutine (c, sym);
3408
3409   return MATCH_YES;
3410 }
3411
3412
3413 static gfc_try
3414 resolve_specific_s (gfc_code *c)
3415 {
3416   gfc_symbol *sym;
3417   match m;
3418
3419   sym = c->symtree->n.sym;
3420
3421   for (;;)
3422     {
3423       m = resolve_specific_s0 (c, sym);
3424       if (m == MATCH_YES)
3425         return SUCCESS;
3426       if (m == MATCH_ERROR)
3427         return FAILURE;
3428
3429       if (sym->ns->parent == NULL)
3430         break;
3431
3432       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3433
3434       if (sym == NULL)
3435         break;
3436     }
3437
3438   sym = c->symtree->n.sym;
3439   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3440              sym->name, &c->loc);
3441
3442   return FAILURE;
3443 }
3444
3445
3446 /* Resolve a subroutine call not known to be generic nor specific.  */
3447
3448 static gfc_try
3449 resolve_unknown_s (gfc_code *c)
3450 {
3451   gfc_symbol *sym;
3452
3453   sym = c->symtree->n.sym;
3454
3455   if (sym->attr.dummy)
3456     {
3457       sym->attr.proc = PROC_DUMMY;
3458       goto found;
3459     }
3460
3461   /* See if we have an intrinsic function reference.  */
3462
3463   if (gfc_is_intrinsic (sym, 1, c->loc))
3464     {
3465       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3466         return SUCCESS;
3467       return FAILURE;
3468     }
3469
3470   /* The reference is to an external name.  */
3471
3472 found:
3473   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3474
3475   c->resolved_sym = sym;
3476
3477   pure_subroutine (c, sym);
3478
3479   return SUCCESS;
3480 }
3481
3482
3483 /* Resolve a subroutine call.  Although it was tempting to use the same code
3484    for functions, subroutines and functions are stored differently and this
3485    makes things awkward.  */
3486
3487 static gfc_try
3488 resolve_call (gfc_code *c)
3489 {
3490   gfc_try t;
3491   procedure_type ptype = PROC_INTRINSIC;
3492   gfc_symbol *csym, *sym;
3493   bool no_formal_args;
3494
3495   csym = c->symtree ? c->symtree->n.sym : NULL;
3496
3497   if (csym && csym->ts.type != BT_UNKNOWN)
3498     {
3499       gfc_error ("'%s' at %L has a type, which is not consistent with "
3500                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3501       return FAILURE;
3502     }
3503
3504   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3505     {
3506       gfc_symtree *st;
3507       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3508       sym = st ? st->n.sym : NULL;
3509       if (sym && csym != sym
3510               && sym->ns == gfc_current_ns
3511               && sym->attr.flavor == FL_PROCEDURE
3512               && sym->attr.contained)
3513         {
3514           sym->refs++;
3515           if (csym->attr.generic)
3516             c->symtree->n.sym = sym;
3517           else
3518             c->symtree = st;
3519           csym = c->symtree->n.sym;
3520         }
3521     }
3522
3523   /* If this ia a deferred TBP with an abstract interface
3524      (which may of course be referenced), c->expr1 will be set.  */
3525   if (csym && csym->attr.abstract && !c->expr1)
3526     {
3527       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3528                  csym->name, &c->loc);
3529       return FAILURE;
3530     }
3531
3532   /* Subroutines without the RECURSIVE attribution are not allowed to
3533    * call themselves.  */
3534   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3535     {
3536       if (csym->attr.entry && csym->ns->entries)
3537         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3538                    " subroutine '%s' is not RECURSIVE",
3539                    csym->name, &c->loc, csym->ns->entries->sym->name);
3540       else
3541         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3542                    " is not RECURSIVE", csym->name, &c->loc);
3543
3544       t = FAILURE;
3545     }
3546
3547   /* Switch off assumed size checking and do this again for certain kinds
3548      of procedure, once the procedure itself is resolved.  */
3549   need_full_assumed_size++;
3550
3551   if (csym)
3552     ptype = csym->attr.proc;
3553
3554   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3555   if (resolve_actual_arglist (c->ext.actual, ptype,
3556                               no_formal_args) == FAILURE)
3557     return FAILURE;
3558
3559   /* Resume assumed_size checking.  */
3560   need_full_assumed_size--;
3561
3562   /* If external, check for usage.  */
3563   if (csym && is_external_proc (csym))
3564     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3565
3566   t = SUCCESS;
3567   if (c->resolved_sym == NULL)
3568     {
3569       c->resolved_isym = NULL;
3570       switch (procedure_kind (csym))
3571         {
3572         case PTYPE_GENERIC:
3573           t = resolve_generic_s (c);
3574           break;
3575
3576         case PTYPE_SPECIFIC:
3577           t = resolve_specific_s (c);
3578           break;
3579
3580         case PTYPE_UNKNOWN:
3581           t = resolve_unknown_s (c);
3582           break;
3583
3584         default:
3585           gfc_internal_error ("resolve_subroutine(): bad function type");
3586         }
3587     }
3588
3589   /* Some checks of elemental subroutine actual arguments.  */
3590   if (resolve_elemental_actual (NULL, c) == FAILURE)
3591     return FAILURE;
3592
3593   return t;
3594 }
3595
3596
3597 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3598    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3599    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3600    if their shapes do not match.  If either op1->shape or op2->shape is
3601    NULL, return SUCCESS.  */
3602
3603 static gfc_try
3604 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3605 {
3606   gfc_try t;
3607   int i;
3608
3609   t = SUCCESS;
3610
3611   if (op1->shape != NULL && op2->shape != NULL)
3612     {
3613       for (i = 0; i < op1->rank; i++)
3614         {
3615           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3616            {
3617              gfc_error ("Shapes for operands at %L and %L are not conformable",
3618                          &op1->where, &op2->where);
3619              t = FAILURE;
3620              break;
3621            }
3622         }
3623     }
3624
3625   return t;
3626 }
3627
3628
3629 /* Resolve an operator expression node.  This can involve replacing the
3630    operation with a user defined function call.  */
3631
3632 static gfc_try
3633 resolve_operator (gfc_expr *e)
3634 {
3635   gfc_expr *op1, *op2;
3636   char msg[200];
3637   bool dual_locus_error;
3638   gfc_try t;
3639
3640   /* Resolve all subnodes-- give them types.  */
3641
3642   switch (e->value.op.op)
3643     {
3644     default:
3645       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3646         return FAILURE;
3647
3648     /* Fall through...  */
3649
3650     case INTRINSIC_NOT:
3651     case INTRINSIC_UPLUS:
3652     case INTRINSIC_UMINUS:
3653     case INTRINSIC_PARENTHESES:
3654       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3655         return FAILURE;
3656       break;
3657     }
3658
3659   /* Typecheck the new node.  */
3660
3661   op1 = e->value.op.op1;
3662   op2 = e->value.op.op2;
3663   dual_locus_error = false;
3664
3665   if ((op1 && op1->expr_type == EXPR_NULL)
3666       || (op2 && op2->expr_type == EXPR_NULL))
3667     {
3668       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3669       goto bad_op;
3670     }
3671
3672   switch (e->value.op.op)
3673     {
3674     case INTRINSIC_UPLUS:
3675     case INTRINSIC_UMINUS:
3676       if (op1->ts.type == BT_INTEGER
3677           || op1->ts.type == BT_REAL
3678           || op1->ts.type == BT_COMPLEX)
3679         {
3680           e->ts = op1->ts;
3681           break;
3682         }
3683
3684       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3685                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3686       goto bad_op;
3687
3688     case INTRINSIC_PLUS:
3689     case INTRINSIC_MINUS:
3690     case INTRINSIC_TIMES:
3691     case INTRINSIC_DIVIDE:
3692     case INTRINSIC_POWER:
3693       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3694         {
3695           gfc_type_convert_binary (e, 1);
3696           break;
3697         }
3698
3699       sprintf (msg,
3700                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3701                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3702                gfc_typename (&op2->ts));
3703       goto bad_op;
3704
3705     case INTRINSIC_CONCAT:
3706       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3707           && op1->ts.kind == op2->ts.kind)
3708         {
3709           e->ts.type = BT_CHARACTER;
3710           e->ts.kind = op1->ts.kind;
3711           break;
3712         }
3713
3714       sprintf (msg,
3715                _("Operands of string concatenation operator at %%L are %s/%s"),
3716                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3717       goto bad_op;
3718
3719     case INTRINSIC_AND:
3720     case INTRINSIC_OR:
3721     case INTRINSIC_EQV:
3722     case INTRINSIC_NEQV:
3723       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3724         {
3725           e->ts.type = BT_LOGICAL;
3726           e->ts.kind = gfc_kind_max (op1, op2);
3727           if (op1->ts.kind < e->ts.kind)
3728             gfc_convert_type (op1, &e->ts, 2);
3729           else if (op2->ts.kind < e->ts.kind)
3730             gfc_convert_type (op2, &e->ts, 2);
3731           break;
3732         }
3733
3734       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3735                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3736                gfc_typename (&op2->ts));
3737
3738       goto bad_op;
3739
3740     case INTRINSIC_NOT:
3741       if (op1->ts.type == BT_LOGICAL)
3742         {
3743           e->ts.type = BT_LOGICAL;
3744           e->ts.kind = op1->ts.kind;
3745           break;
3746         }
3747
3748       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3749                gfc_typename (&op1->ts));
3750       goto bad_op;
3751
3752     case INTRINSIC_GT:
3753     case INTRINSIC_GT_OS:
3754     case INTRINSIC_GE:
3755     case INTRINSIC_GE_OS:
3756     case INTRINSIC_LT:
3757     case INTRINSIC_LT_OS:
3758     case INTRINSIC_LE:
3759     case INTRINSIC_LE_OS:
3760       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3761         {
3762           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3763           goto bad_op;
3764         }
3765
3766       /* Fall through...  */
3767
3768     case INTRINSIC_EQ:
3769     case INTRINSIC_EQ_OS:
3770     case INTRINSIC_NE:
3771     case INTRINSIC_NE_OS:
3772       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3773           && op1->ts.kind == op2->ts.kind)
3774         {
3775           e->ts.type = BT_LOGICAL;
3776           e->ts.kind = gfc_default_logical_kind;
3777           break;
3778         }
3779
3780       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3781         {
3782           gfc_type_convert_binary (e, 1);
3783
3784           e->ts.type = BT_LOGICAL;
3785           e->ts.kind = gfc_default_logical_kind;
3786           break;
3787         }
3788
3789       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3790         sprintf (msg,
3791                  _("Logicals at %%L must be compared with %s instead of %s"),
3792                  (e->value.op.op == INTRINSIC_EQ 
3793                   || e->value.op.op == INTRINSIC_EQ_OS)
3794                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3795       else
3796         sprintf (msg,
3797                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3798                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3799                  gfc_typename (&op2->ts));
3800
3801       goto bad_op;
3802
3803     case INTRINSIC_USER:
3804       if (e->value.op.uop->op == NULL)
3805         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3806       else if (op2 == NULL)
3807         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3808                  e->value.op.uop->name, gfc_typename (&op1->ts));
3809       else
3810         {
3811           sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3812                    e->value.op.uop->name, gfc_typename (&op1->ts),
3813                    gfc_typename (&op2->ts));
3814           e->value.op.uop->op->sym->attr.referenced = 1;
3815         }
3816
3817       goto bad_op;
3818
3819     case INTRINSIC_PARENTHESES:
3820       e->ts = op1->ts;
3821       if (e->ts.type == BT_CHARACTER)
3822         e->ts.u.cl = op1->ts.u.cl;
3823       break;
3824
3825     default:
3826       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3827     }
3828
3829   /* Deal with arrayness of an operand through an operator.  */
3830
3831   t = SUCCESS;
3832
3833   switch (e->value.op.op)
3834     {
3835     case INTRINSIC_PLUS:
3836     case INTRINSIC_MINUS:
3837     case INTRINSIC_TIMES:
3838     case INTRINSIC_DIVIDE:
3839     case INTRINSIC_POWER:
3840     case INTRINSIC_CONCAT:
3841     case INTRINSIC_AND:
3842     case INTRINSIC_OR:
3843     case INTRINSIC_EQV:
3844     case INTRINSIC_NEQV:
3845     case INTRINSIC_EQ:
3846     case INTRINSIC_EQ_OS:
3847     case INTRINSIC_NE:
3848     case INTRINSIC_NE_OS:
3849     case INTRINSIC_GT:
3850     case INTRINSIC_GT_OS:
3851     case INTRINSIC_GE:
3852     case INTRINSIC_GE_OS:
3853     case INTRINSIC_LT:
3854     case INTRINSIC_LT_OS:
3855     case INTRINSIC_LE:
3856     case INTRINSIC_LE_OS:
3857
3858       if (op1->rank == 0 && op2->rank == 0)
3859         e->rank = 0;
3860
3861       if (op1->rank == 0 && op2->rank != 0)
3862         {
3863           e->rank = op2->rank;
3864
3865           if (e->shape == NULL)
3866             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3867         }
3868
3869       if (op1->rank != 0 && op2->rank == 0)
3870         {
3871           e->rank = op1->rank;
3872
3873           if (e->shape == NULL)
3874             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3875         }
3876
3877       if (op1->rank != 0 && op2->rank != 0)
3878         {
3879           if (op1->rank == op2->rank)
3880             {
3881               e->rank = op1->rank;
3882               if (e->shape == NULL)
3883                 {
3884                   t = compare_shapes (op1, op2);
3885                   if (t == FAILURE)
3886                     e->shape = NULL;
3887                   else
3888                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
3889                 }
3890             }
3891           else
3892             {
3893               /* Allow higher level expressions to work.  */
3894               e->rank = 0;
3895
3896               /* Try user-defined operators, and otherwise throw an error.  */
3897               dual_locus_error = true;
3898               sprintf (msg,
3899                        _("Inconsistent ranks for operator at %%L and %%L"));
3900               goto bad_op;
3901             }
3902         }
3903
3904       break;
3905
3906     case INTRINSIC_PARENTHESES:
3907     case INTRINSIC_NOT:
3908     case INTRINSIC_UPLUS:
3909     case INTRINSIC_UMINUS:
3910       /* Simply copy arrayness attribute */
3911       e->rank = op1->rank;
3912
3913       if (e->shape == NULL)
3914         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3915
3916       break;
3917
3918     default:
3919       break;
3920     }
3921
3922   /* Attempt to simplify the expression.  */
3923   if (t == SUCCESS)
3924     {
3925       t = gfc_simplify_expr (e, 0);
3926       /* Some calls do not succeed in simplification and return FAILURE
3927          even though there is no error; e.g. variable references to
3928          PARAMETER arrays.  */
3929       if (!gfc_is_constant_expr (e))
3930         t = SUCCESS;
3931     }
3932   return t;
3933
3934 bad_op:
3935
3936   {
3937     bool real_error;
3938     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3939       return SUCCESS;
3940
3941     if (real_error)
3942       return FAILURE;
3943   }
3944
3945   if (dual_locus_error)
3946     gfc_error (msg, &op1->where, &op2->where);
3947   else
3948     gfc_error (msg, &e->where);
3949
3950   return FAILURE;
3951 }
3952
3953
3954 /************** Array resolution subroutines **************/
3955
3956 typedef enum
3957 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
3958 comparison;
3959
3960 /* Compare two integer expressions.  */
3961
3962 static comparison
3963 compare_bound (gfc_expr *a, gfc_expr *b)
3964 {
3965   int i;
3966
3967   if (a == NULL || a->expr_type != EXPR_CONSTANT
3968       || b == NULL || b->expr_type != EXPR_CONSTANT)
3969     return CMP_UNKNOWN;
3970
3971   /* If either of the types isn't INTEGER, we must have
3972      raised an error earlier.  */
3973
3974   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
3975     return CMP_UNKNOWN;
3976
3977   i = mpz_cmp (a->value.integer, b->value.integer);
3978
3979   if (i < 0)
3980     return CMP_LT;
3981   if (i > 0)
3982     return CMP_GT;
3983   return CMP_EQ;
3984 }
3985
3986
3987 /* Compare an integer expression with an integer.  */
3988
3989 static comparison
3990 compare_bound_int (gfc_expr *a, int b)
3991 {
3992   int i;
3993
3994   if (a == NULL || a->expr_type != EXPR_CONSTANT)
3995     return CMP_UNKNOWN;
3996
3997   if (a->ts.type != BT_INTEGER)
3998     gfc_internal_error ("compare_bound_int(): Bad expression");
3999
4000   i = mpz_cmp_si (a->value.integer, b);
4001
4002   if (i < 0)
4003     return CMP_LT;
4004   if (i > 0)
4005     return CMP_GT;
4006   return CMP_EQ;
4007 }
4008
4009
4010 /* Compare an integer expression with a mpz_t.  */
4011
4012 static comparison
4013 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
4014 {
4015   int i;
4016
4017   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4018     return CMP_UNKNOWN;
4019
4020   if (a->ts.type != BT_INTEGER)
4021     gfc_internal_error ("compare_bound_int(): Bad expression");
4022
4023   i = mpz_cmp (a->value.integer, b);
4024
4025   if (i < 0)
4026     return CMP_LT;
4027   if (i > 0)
4028     return CMP_GT;
4029   return CMP_EQ;
4030 }
4031
4032
4033 /* Compute the last value of a sequence given by a triplet.  
4034    Return 0 if it wasn't able to compute the last value, or if the
4035    sequence if empty, and 1 otherwise.  */
4036
4037 static int
4038 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
4039                                 gfc_expr *stride, mpz_t last)
4040 {
4041   mpz_t rem;
4042
4043   if (start == NULL || start->expr_type != EXPR_CONSTANT
4044       || end == NULL || end->expr_type != EXPR_CONSTANT
4045       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
4046     return 0;
4047
4048   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
4049       || (stride != NULL && stride->ts.type != BT_INTEGER))
4050     return 0;
4051
4052   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
4053     {
4054       if (compare_bound (start, end) == CMP_GT)
4055         return 0;
4056       mpz_set (last, end->value.integer);
4057       return 1;
4058     }
4059
4060   if (compare_bound_int (stride, 0) == CMP_GT)
4061     {
4062       /* Stride is positive */
4063       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
4064         return 0;
4065     }
4066   else
4067     {
4068       /* Stride is negative */
4069       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
4070         return 0;
4071     }
4072
4073   mpz_init (rem);
4074   mpz_sub (rem, end->value.integer, start->value.integer);
4075   mpz_tdiv_r (rem, rem, stride->value.integer);
4076   mpz_sub (last, end->value.integer, rem);
4077   mpz_clear (rem);
4078
4079   return 1;
4080 }
4081
4082
4083 /* Compare a single dimension of an array reference to the array
4084    specification.  */
4085
4086 static gfc_try
4087 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
4088 {
4089   mpz_t last_value;
4090
4091   if (ar->dimen_type[i] == DIMEN_STAR)
4092     {
4093       gcc_assert (ar->stride[i] == NULL);
4094       /* This implies [*] as [*:] and [*:3] are not possible.  */
4095       if (ar->start[i] == NULL)
4096         {
4097           gcc_assert (ar->end[i] == NULL);
4098           return SUCCESS;
4099         }
4100     }
4101
4102 /* Given start, end and stride values, calculate the minimum and
4103    maximum referenced indexes.  */
4104
4105   switch (ar->dimen_type[i])
4106     {
4107     case DIMEN_VECTOR:
4108       break;
4109
4110     case DIMEN_STAR:
4111     case DIMEN_ELEMENT:
4112       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4113         {
4114           if (i < as->rank)
4115             gfc_warning ("Array reference at %L is out of bounds "
4116                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
4117                          mpz_get_si (ar->start[i]->value.integer),
4118                          mpz_get_si (as->lower[i]->value.integer), i+1);
4119           else
4120             gfc_warning ("Array reference at %L is out of bounds "
4121                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
4122                          mpz_get_si (ar->start[i]->value.integer),
4123                          mpz_get_si (as->lower[i]->value.integer),
4124                          i + 1 - as->rank);
4125           return SUCCESS;
4126         }
4127       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4128         {
4129           if (i < as->rank)
4130             gfc_warning ("Array reference at %L is out of bounds "
4131                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
4132                          mpz_get_si (ar->start[i]->value.integer),
4133                          mpz_get_si (as->upper[i]->value.integer), i+1);
4134           else
4135             gfc_warning ("Array reference at %L is out of bounds "
4136                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
4137                          mpz_get_si (ar->start[i]->value.integer),
4138                          mpz_get_si (as->upper[i]->value.integer),
4139                          i + 1 - as->rank);
4140           return SUCCESS;
4141         }
4142
4143       break;
4144
4145     case DIMEN_RANGE:
4146       {
4147 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4148 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4149
4150         comparison comp_start_end = compare_bound (AR_START, AR_END);
4151
4152         /* Check for zero stride, which is not allowed.  */
4153         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4154           {
4155             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4156             return FAILURE;
4157           }
4158
4159         /* if start == len || (stride > 0 && start < len)
4160                            || (stride < 0 && start > len),
4161            then the array section contains at least one element.  In this
4162            case, there is an out-of-bounds access if
4163            (start < lower || start > upper).  */
4164         if (compare_bound (AR_START, AR_END) == CMP_EQ
4165             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4166                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4167             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4168                 && comp_start_end == CMP_GT))
4169           {
4170             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4171               {
4172                 gfc_warning ("Lower array reference at %L is out of bounds "
4173                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4174                        mpz_get_si (AR_START->value.integer),
4175                        mpz_get_si (as->lower[i]->value.integer), i+1);
4176                 return SUCCESS;
4177               }
4178             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4179               {
4180                 gfc_warning ("Lower array reference at %L is out of bounds "
4181                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4182                        mpz_get_si (AR_START->value.integer),
4183                        mpz_get_si (as->upper[i]->value.integer), i+1);
4184                 return SUCCESS;
4185               }
4186           }
4187
4188         /* If we can compute the highest index of the array section,
4189            then it also has to be between lower and upper.  */
4190         mpz_init (last_value);
4191         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4192                                             last_value))
4193           {
4194             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4195               {
4196                 gfc_warning ("Upper array reference at %L is out of bounds "
4197                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4198                        mpz_get_si (last_value),
4199                        mpz_get_si (as->lower[i]->value.integer), i+1);
4200                 mpz_clear (last_value);
4201                 return SUCCESS;
4202               }
4203             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4204               {
4205                 gfc_warning ("Upper array reference at %L is out of bounds "
4206                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4207                        mpz_get_si (last_value),
4208                        mpz_get_si (as->upper[i]->value.integer), i+1);
4209                 mpz_clear (last_value);
4210                 return SUCCESS;
4211               }
4212           }
4213         mpz_clear (last_value);
4214
4215 #undef AR_START
4216 #undef AR_END
4217       }
4218       break;
4219
4220     default:
4221       gfc_internal_error ("check_dimension(): Bad array reference");
4222     }
4223
4224   return SUCCESS;
4225 }
4226
4227
4228 /* Compare an array reference with an array specification.  */
4229
4230 static gfc_try
4231 compare_spec_to_ref (gfc_array_ref *ar)
4232 {
4233   gfc_array_spec *as;
4234   int i;
4235
4236   as = ar->as;
4237   i = as->rank - 1;
4238   /* TODO: Full array sections are only allowed as actual parameters.  */
4239   if (as->type == AS_ASSUMED_SIZE
4240       && (/*ar->type == AR_FULL
4241           ||*/ (ar->type == AR_SECTION
4242               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4243     {
4244       gfc_error ("Rightmost upper bound of assumed size array section "
4245                  "not specified at %L", &ar->where);
4246       return FAILURE;
4247     }
4248
4249   if (ar->type == AR_FULL)
4250     return SUCCESS;
4251
4252   if (as->rank != ar->dimen)
4253     {
4254       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4255                  &ar->where, ar->dimen, as->rank);
4256       return FAILURE;
4257     }
4258
4259   /* ar->codimen == 0 is a local array.  */
4260   if (as->corank != ar->codimen && ar->codimen != 0)
4261     {
4262       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4263                  &ar->where, ar->codimen, as->corank);
4264       return FAILURE;
4265     }
4266
4267   for (i = 0; i < as->rank; i++)
4268     if (check_dimension (i, ar, as) == FAILURE)
4269       return FAILURE;
4270
4271   /* Local access has no coarray spec.  */
4272   if (ar->codimen != 0)
4273     for (i = as->rank; i < as->rank + as->corank; i++)
4274       {
4275         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate)
4276           {
4277             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4278                        i + 1 - as->rank, &ar->where);
4279             return FAILURE;
4280           }
4281         if (check_dimension (i, ar, as) == FAILURE)
4282           return FAILURE;
4283       }
4284
4285   return SUCCESS;
4286 }
4287
4288
4289 /* Resolve one part of an array index.  */
4290
4291 static gfc_try
4292 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4293                      int force_index_integer_kind)
4294 {
4295   gfc_typespec ts;
4296
4297   if (index == NULL)
4298     return SUCCESS;
4299
4300   if (gfc_resolve_expr (index) == FAILURE)
4301     return FAILURE;
4302
4303   if (check_scalar && index->rank != 0)
4304     {
4305       gfc_error ("Array index at %L must be scalar", &index->where);
4306       return FAILURE;
4307     }
4308
4309   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4310     {
4311       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4312                  &index->where, gfc_basic_typename (index->ts.type));
4313       return FAILURE;
4314     }
4315
4316   if (index->ts.type == BT_REAL)
4317     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4318                         &index->where) == FAILURE)
4319       return FAILURE;
4320
4321   if ((index->ts.kind != gfc_index_integer_kind
4322        && force_index_integer_kind)
4323       || index->ts.type != BT_INTEGER)
4324     {
4325       gfc_clear_ts (&ts);
4326       ts.type = BT_INTEGER;
4327       ts.kind = gfc_index_integer_kind;
4328
4329       gfc_convert_type_warn (index, &ts, 2, 0);
4330     }
4331
4332   return SUCCESS;
4333 }
4334
4335 /* Resolve one part of an array index.  */
4336
4337 gfc_try
4338 gfc_resolve_index (gfc_expr *index, int check_scalar)
4339 {
4340   return gfc_resolve_index_1 (index, check_scalar, 1);
4341 }
4342
4343 /* Resolve a dim argument to an intrinsic function.  */
4344
4345 gfc_try
4346 gfc_resolve_dim_arg (gfc_expr *dim)
4347 {
4348   if (dim == NULL)
4349     return SUCCESS;
4350
4351   if (gfc_resolve_expr (dim) == FAILURE)
4352     return FAILURE;
4353
4354   if (dim->rank != 0)
4355     {
4356       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4357       return FAILURE;
4358
4359     }
4360
4361   if (dim->ts.type != BT_INTEGER)
4362     {
4363       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4364       return FAILURE;
4365     }
4366
4367   if (dim->ts.kind != gfc_index_integer_kind)
4368     {
4369       gfc_typespec ts;
4370
4371       gfc_clear_ts (&ts);
4372       ts.type = BT_INTEGER;
4373       ts.kind = gfc_index_integer_kind;
4374
4375       gfc_convert_type_warn (dim, &ts, 2, 0);
4376     }
4377
4378   return SUCCESS;
4379 }
4380
4381 /* Given an expression that contains array references, update those array
4382    references to point to the right array specifications.  While this is
4383    filled in during matching, this information is difficult to save and load
4384    in a module, so we take care of it here.
4385
4386    The idea here is that the original array reference comes from the
4387    base symbol.  We traverse the list of reference structures, setting
4388    the stored reference to references.  Component references can
4389    provide an additional array specification.  */
4390
4391 static void
4392 find_array_spec (gfc_expr *e)
4393 {
4394   gfc_array_spec *as;
4395   gfc_component *c;
4396   gfc_symbol *derived;
4397   gfc_ref *ref;
4398
4399   if (e->symtree->n.sym->ts.type == BT_CLASS)
4400     as = CLASS_DATA (e->symtree->n.sym)->as;
4401   else
4402     as = e->symtree->n.sym->as;
4403   derived = NULL;
4404
4405   for (ref = e->ref; ref; ref = ref->next)
4406     switch (ref->type)
4407       {
4408       case REF_ARRAY:
4409         if (as == NULL)
4410           gfc_internal_error ("find_array_spec(): Missing spec");
4411
4412         ref->u.ar.as = as;
4413         as = NULL;
4414         break;
4415
4416       case REF_COMPONENT:
4417         if (derived == NULL)
4418           derived = e->symtree->n.sym->ts.u.derived;
4419
4420         if (derived->attr.is_class)
4421           derived = derived->components->ts.u.derived;
4422
4423         c = derived->components;
4424
4425         for (; c; c = c->next)
4426           if (c == ref->u.c.component)
4427             {
4428               /* Track the sequence of component references.  */
4429               if (c->ts.type == BT_DERIVED)
4430                 derived = c->ts.u.derived;
4431               break;
4432             }
4433
4434         if (c == NULL)
4435           gfc_internal_error ("find_array_spec(): Component not found");
4436
4437         if (c->attr.dimension)
4438           {
4439             if (as != NULL)
4440               gfc_internal_error ("find_array_spec(): unused as(1)");
4441             as = c->as;
4442           }
4443
4444         break;
4445
4446       case REF_SUBSTRING:
4447         break;
4448       }
4449
4450   if (as != NULL)
4451     gfc_internal_error ("find_array_spec(): unused as(2)");
4452 }
4453
4454
4455 /* Resolve an array reference.  */
4456
4457 static gfc_try
4458 resolve_array_ref (gfc_array_ref *ar)
4459 {
4460   int i, check_scalar;
4461   gfc_expr *e;
4462
4463   for (i = 0; i < ar->dimen + ar->codimen; i++)
4464     {
4465       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4466
4467       /* Do not force gfc_index_integer_kind for the start.  We can
4468          do fine with any integer kind.  This avoids temporary arrays
4469          created for indexing with a vector.  */
4470       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4471         return FAILURE;
4472       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4473         return FAILURE;
4474       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4475         return FAILURE;
4476
4477       e = ar->start[i];
4478
4479       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4480         switch (e->rank)
4481           {
4482           case 0:
4483             ar->dimen_type[i] = DIMEN_ELEMENT;
4484             break;
4485
4486           case 1:
4487             ar->dimen_type[i] = DIMEN_VECTOR;
4488             if (e->expr_type == EXPR_VARIABLE
4489                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4490               ar->start[i] = gfc_get_parentheses (e);
4491             break;
4492
4493           default:
4494             gfc_error ("Array index at %L is an array of rank %d",
4495                        &ar->c_where[i], e->rank);
4496             return FAILURE;
4497           }
4498
4499       /* Fill in the upper bound, which may be lower than the
4500          specified one for something like a(2:10:5), which is
4501          identical to a(2:7:5).  Only relevant for strides not equal
4502          to one.  */
4503       if (ar->dimen_type[i] == DIMEN_RANGE
4504           && ar->stride[i] != NULL && ar->stride[i]->expr_type == EXPR_CONSTANT
4505           && mpz_cmp_si (ar->stride[i]->value.integer, 1L) != 0)
4506         {
4507           mpz_t size, end;
4508
4509           if (gfc_ref_dimen_size (ar, i, &size, &end) == SUCCESS)
4510             {
4511               if (ar->end[i] == NULL)
4512                 {
4513                   ar->end[i] =
4514                     gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
4515                                            &ar->where);
4516                   mpz_set (ar->end[i]->value.integer, end);
4517                 }
4518               else if (ar->end[i]->ts.type == BT_INTEGER
4519                        && ar->end[i]->expr_type == EXPR_CONSTANT)
4520                 {
4521                   mpz_set (ar->end[i]->value.integer, end);
4522                 }
4523               else
4524                 gcc_unreachable ();
4525
4526               mpz_clear (size);
4527               mpz_clear (end);
4528             }
4529         }
4530     }
4531
4532   if (ar->type == AR_FULL && ar->as->rank == 0)
4533     ar->type = AR_ELEMENT;
4534
4535   /* If the reference type is unknown, figure out what kind it is.  */
4536
4537   if (ar->type == AR_UNKNOWN)
4538     {
4539       ar->type = AR_ELEMENT;
4540       for (i = 0; i < ar->dimen; i++)
4541         if (ar->dimen_type[i] == DIMEN_RANGE
4542             || ar->dimen_type[i] == DIMEN_VECTOR)
4543           {
4544             ar->type = AR_SECTION;
4545             break;
4546           }
4547     }
4548
4549   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4550     return FAILURE;
4551
4552   return SUCCESS;
4553 }
4554
4555
4556 static gfc_try
4557 resolve_substring (gfc_ref *ref)
4558 {
4559   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4560
4561   if (ref->u.ss.start != NULL)
4562     {
4563       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4564         return FAILURE;
4565
4566       if (ref->u.ss.start->ts.type != BT_INTEGER)
4567         {
4568           gfc_error ("Substring start index at %L must be of type INTEGER",
4569                      &ref->u.ss.start->where);
4570           return FAILURE;
4571         }
4572
4573       if (ref->u.ss.start->rank != 0)
4574         {
4575           gfc_error ("Substring start index at %L must be scalar",
4576                      &ref->u.ss.start->where);
4577           return FAILURE;
4578         }
4579
4580       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4581           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4582               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4583         {
4584           gfc_error ("Substring start index at %L is less than one",
4585                      &ref->u.ss.start->where);
4586           return FAILURE;
4587         }
4588     }
4589
4590   if (ref->u.ss.end != NULL)
4591     {
4592       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4593         return FAILURE;
4594
4595       if (ref->u.ss.end->ts.type != BT_INTEGER)
4596         {
4597           gfc_error ("Substring end index at %L must be of type INTEGER",
4598                      &ref->u.ss.end->where);
4599           return FAILURE;
4600         }
4601
4602       if (ref->u.ss.end->rank != 0)
4603         {
4604           gfc_error ("Substring end index at %L must be scalar",
4605                      &ref->u.ss.end->where);
4606           return FAILURE;
4607         }
4608
4609       if (ref->u.ss.length != NULL
4610           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4611           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4612               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4613         {
4614           gfc_error ("Substring end index at %L exceeds the string length",
4615                      &ref->u.ss.start->where);
4616           return FAILURE;
4617         }
4618
4619       if (compare_bound_mpz_t (ref->u.ss.end,
4620                                gfc_integer_kinds[k].huge) == CMP_GT
4621           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4622               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4623         {
4624           gfc_error ("Substring end index at %L is too large",
4625                      &ref->u.ss.end->where);
4626           return FAILURE;
4627         }
4628     }
4629
4630   return SUCCESS;
4631 }
4632
4633
4634 /* This function supplies missing substring charlens.  */
4635
4636 void
4637 gfc_resolve_substring_charlen (gfc_expr *e)
4638 {
4639   gfc_ref *char_ref;
4640   gfc_expr *start, *end;
4641
4642   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4643     if (char_ref->type == REF_SUBSTRING)
4644       break;
4645
4646   if (!char_ref)
4647     return;
4648
4649   gcc_assert (char_ref->next == NULL);
4650
4651   if (e->ts.u.cl)
4652     {
4653       if (e->ts.u.cl->length)
4654         gfc_free_expr (e->ts.u.cl->length);
4655       else if (e->expr_type == EXPR_VARIABLE
4656                  && e->symtree->n.sym->attr.dummy)
4657         return;
4658     }
4659
4660   e->ts.type = BT_CHARACTER;
4661   e->ts.kind = gfc_default_character_kind;
4662
4663   if (!e->ts.u.cl)
4664     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4665
4666   if (char_ref->u.ss.start)
4667     start = gfc_copy_expr (char_ref->u.ss.start);
4668   else
4669     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4670
4671   if (char_ref->u.ss.end)
4672     end = gfc_copy_expr (char_ref->u.ss.end);
4673   else if (e->expr_type == EXPR_VARIABLE)
4674     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4675   else
4676     end = NULL;
4677
4678   if (!start || !end)
4679     return;
4680
4681   /* Length = (end - start +1).  */
4682   e->ts.u.cl->length = gfc_subtract (end, start);
4683   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4684                                 gfc_get_int_expr (gfc_default_integer_kind,
4685                                                   NULL, 1));
4686
4687   e->ts.u.cl->length->ts.type = BT_INTEGER;
4688   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4689
4690   /* Make sure that the length is simplified.  */
4691   gfc_simplify_expr (e->ts.u.cl->length, 1);
4692   gfc_resolve_expr (e->ts.u.cl->length);
4693 }
4694
4695
4696 /* Resolve subtype references.  */
4697
4698 static gfc_try
4699 resolve_ref (gfc_expr *expr)
4700 {
4701   int current_part_dimension, n_components, seen_part_dimension;
4702   gfc_ref *ref;
4703
4704   for (ref = expr->ref; ref; ref = ref->next)
4705     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4706       {
4707         find_array_spec (expr);
4708         break;
4709       }
4710
4711   for (ref = expr->ref; ref; ref = ref->next)
4712     switch (ref->type)
4713       {
4714       case REF_ARRAY:
4715         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4716           return FAILURE;
4717         break;
4718
4719       case REF_COMPONENT:
4720         break;
4721
4722       case REF_SUBSTRING:
4723         resolve_substring (ref);
4724         break;
4725       }
4726
4727   /* Check constraints on part references.  */
4728
4729   current_part_dimension = 0;
4730   seen_part_dimension = 0;
4731   n_components = 0;
4732
4733   for (ref = expr->ref; ref; ref = ref->next)
4734     {
4735       switch (ref->type)
4736         {
4737         case REF_ARRAY:
4738           switch (ref->u.ar.type)
4739             {
4740             case AR_FULL:
4741               /* Coarray scalar.  */
4742               if (ref->u.ar.as->rank == 0)
4743                 {
4744                   current_part_dimension = 0;
4745                   break;
4746                 }
4747               /* Fall through.  */
4748             case AR_SECTION:
4749               current_part_dimension = 1;
4750               break;
4751
4752             case AR_ELEMENT:
4753               current_part_dimension = 0;
4754               break;
4755
4756             case AR_UNKNOWN:
4757               gfc_internal_error ("resolve_ref(): Bad array reference");
4758             }
4759
4760           break;
4761
4762         case REF_COMPONENT:
4763           if (current_part_dimension || seen_part_dimension)
4764             {
4765               /* F03:C614.  */
4766               if (ref->u.c.component->attr.pointer
4767                   || ref->u.c.component->attr.proc_pointer)
4768                 {
4769                   gfc_error ("Component to the right of a part reference "
4770                              "with nonzero rank must not have the POINTER "
4771                              "attribute at %L", &expr->where);
4772                   return FAILURE;
4773                 }
4774               else if (ref->u.c.component->attr.allocatable)
4775                 {
4776                   gfc_error ("Component to the right of a part reference "
4777                              "with nonzero rank must not have the ALLOCATABLE "
4778                              "attribute at %L", &expr->where);
4779                   return FAILURE;
4780                 }
4781             }
4782
4783           n_components++;
4784           break;
4785
4786         case REF_SUBSTRING:
4787           break;
4788         }
4789
4790       if (((ref->type == REF_COMPONENT && n_components > 1)
4791            || ref->next == NULL)
4792           && current_part_dimension
4793           && seen_part_dimension)
4794         {
4795           gfc_error ("Two or more part references with nonzero rank must "
4796                      "not be specified at %L", &expr->where);
4797           return FAILURE;
4798         }
4799
4800       if (ref->type == REF_COMPONENT)
4801         {
4802           if (current_part_dimension)
4803             seen_part_dimension = 1;
4804
4805           /* reset to make sure */
4806           current_part_dimension = 0;
4807         }
4808     }
4809
4810   return SUCCESS;
4811 }
4812
4813
4814 /* Given an expression, determine its shape.  This is easier than it sounds.
4815    Leaves the shape array NULL if it is not possible to determine the shape.  */
4816
4817 static void
4818 expression_shape (gfc_expr *e)
4819 {
4820   mpz_t array[GFC_MAX_DIMENSIONS];
4821   int i;
4822
4823   if (e->rank == 0 || e->shape != NULL)
4824     return;
4825
4826   for (i = 0; i < e->rank; i++)
4827     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4828       goto fail;
4829
4830   e->shape = gfc_get_shape (e->rank);
4831
4832   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4833
4834   return;
4835
4836 fail:
4837   for (i--; i >= 0; i--)
4838     mpz_clear (array[i]);
4839 }
4840
4841
4842 /* Given a variable expression node, compute the rank of the expression by
4843    examining the base symbol and any reference structures it may have.  */
4844
4845 static void
4846 expression_rank (gfc_expr *e)
4847 {
4848   gfc_ref *ref;
4849   int i, rank;
4850
4851   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4852      could lead to serious confusion...  */
4853   gcc_assert (e->expr_type != EXPR_COMPCALL);
4854
4855   if (e->ref == NULL)
4856     {
4857       if (e->expr_type == EXPR_ARRAY)
4858         goto done;
4859       /* Constructors can have a rank different from one via RESHAPE().  */
4860
4861       if (e->symtree == NULL)
4862         {
4863           e->rank = 0;
4864           goto done;
4865         }
4866
4867       e->rank = (e->symtree->n.sym->as == NULL)
4868                 ? 0 : e->symtree->n.sym->as->rank;
4869       goto done;
4870     }
4871
4872   rank = 0;
4873
4874   for (ref = e->ref; ref; ref = ref->next)
4875     {
4876       if (ref->type != REF_ARRAY)
4877         continue;
4878
4879       if (ref->u.ar.type == AR_FULL)
4880         {
4881           rank = ref->u.ar.as->rank;
4882           break;
4883         }
4884
4885       if (ref->u.ar.type == AR_SECTION)
4886         {
4887           /* Figure out the rank of the section.  */
4888           if (rank != 0)
4889             gfc_internal_error ("expression_rank(): Two array specs");
4890
4891           for (i = 0; i < ref->u.ar.dimen; i++)
4892             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4893                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4894               rank++;
4895
4896           break;
4897         }
4898     }
4899
4900   e->rank = rank;
4901
4902 done:
4903   expression_shape (e);
4904 }
4905
4906
4907 /* Resolve a variable expression.  */
4908
4909 static gfc_try
4910 resolve_variable (gfc_expr *e)
4911 {
4912   gfc_symbol *sym;
4913   gfc_try t;
4914
4915   t = SUCCESS;
4916
4917   if (e->symtree == NULL)
4918     return FAILURE;
4919   sym = e->symtree->n.sym;
4920
4921   /* If this is an associate-name, it may be parsed with an array reference
4922      in error even though the target is scalar.  Fail directly in this case.  */
4923   if (sym->assoc && !sym->attr.dimension && e->ref && e->ref->type == REF_ARRAY)
4924     return FAILURE;
4925
4926   /* On the other hand, the parser may not have known this is an array;
4927      in this case, we have to add a FULL reference.  */
4928   if (sym->assoc && sym->attr.dimension && !e->ref)
4929     {
4930       e->ref = gfc_get_ref ();
4931       e->ref->type = REF_ARRAY;
4932       e->ref->u.ar.type = AR_FULL;
4933       e->ref->u.ar.dimen = 0;
4934     }
4935
4936   if (e->ref && resolve_ref (e) == FAILURE)
4937     return FAILURE;
4938
4939   if (sym->attr.flavor == FL_PROCEDURE
4940       && (!sym->attr.function
4941           || (sym->attr.function && sym->result
4942               && sym->result->attr.proc_pointer
4943               && !sym->result->attr.function)))
4944     {
4945       e->ts.type = BT_PROCEDURE;
4946       goto resolve_procedure;
4947     }
4948
4949   if (sym->ts.type != BT_UNKNOWN)
4950     gfc_variable_attr (e, &e->ts);
4951   else
4952     {
4953       /* Must be a simple variable reference.  */
4954       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
4955         return FAILURE;
4956       e->ts = sym->ts;
4957     }
4958
4959   if (check_assumed_size_reference (sym, e))
4960     return FAILURE;
4961
4962   /* Deal with forward references to entries during resolve_code, to
4963      satisfy, at least partially, 12.5.2.5.  */
4964   if (gfc_current_ns->entries
4965       && current_entry_id == sym->entry_id
4966       && cs_base
4967       && cs_base->current
4968       && cs_base->current->op != EXEC_ENTRY)
4969     {
4970       gfc_entry_list *entry;
4971       gfc_formal_arglist *formal;
4972       int n;
4973       bool seen;
4974
4975       /* If the symbol is a dummy...  */
4976       if (sym->attr.dummy && sym->ns == gfc_current_ns)
4977         {
4978           entry = gfc_current_ns->entries;
4979           seen = false;
4980
4981           /* ...test if the symbol is a parameter of previous entries.  */
4982           for (; entry && entry->id <= current_entry_id; entry = entry->next)
4983             for (formal = entry->sym->formal; formal; formal = formal->next)
4984               {
4985                 if (formal->sym && sym->name == formal->sym->name)
4986                   seen = true;
4987               }
4988
4989           /*  If it has not been seen as a dummy, this is an error.  */
4990           if (!seen)
4991             {
4992               if (specification_expr)
4993                 gfc_error ("Variable '%s', used in a specification expression"
4994                            ", is referenced at %L before the ENTRY statement "
4995                            "in which it is a parameter",
4996                            sym->name, &cs_base->current->loc);
4997               else
4998                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
4999                            "statement in which it is a parameter",
5000                            sym->name, &cs_base->current->loc);
5001               t = FAILURE;
5002             }
5003         }
5004
5005       /* Now do the same check on the specification expressions.  */
5006       specification_expr = 1;
5007       if (sym->ts.type == BT_CHARACTER
5008           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
5009         t = FAILURE;
5010
5011       if (sym->as)
5012         for (n = 0; n < sym->as->rank; n++)
5013           {
5014              specification_expr = 1;
5015              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
5016                t = FAILURE;
5017              specification_expr = 1;
5018              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
5019                t = FAILURE;
5020           }
5021       specification_expr = 0;
5022
5023       if (t == SUCCESS)
5024         /* Update the symbol's entry level.  */
5025         sym->entry_id = current_entry_id + 1;
5026     }
5027
5028   /* If a symbol has been host_associated mark it.  This is used latter,
5029      to identify if aliasing is possible via host association.  */
5030   if (sym->attr.flavor == FL_VARIABLE
5031         && gfc_current_ns->parent
5032         && (gfc_current_ns->parent == sym->ns
5033               || (gfc_current_ns->parent->parent
5034                     && gfc_current_ns->parent->parent == sym->ns)))
5035     sym->attr.host_assoc = 1;
5036
5037 resolve_procedure:
5038   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
5039     t = FAILURE;
5040
5041   /* F2008, C617 and C1229.  */
5042   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5043       && gfc_is_coindexed (e))
5044     {
5045       gfc_ref *ref, *ref2 = NULL;
5046
5047       for (ref = e->ref; ref; ref = ref->next)
5048         {
5049           if (ref->type == REF_COMPONENT)
5050             ref2 = ref;
5051           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5052             break;
5053         }
5054
5055       for ( ; ref; ref = ref->next)
5056         if (ref->type == REF_COMPONENT)
5057           break;
5058
5059       /* Expression itself is not coindexed object.  */
5060       if (ref && e->ts.type == BT_CLASS)
5061         {
5062           gfc_error ("Polymorphic subobject of coindexed object at %L",
5063                      &e->where);
5064           t = FAILURE;
5065         }
5066
5067       /* Expression itself is coindexed object.  */
5068       if (ref == NULL)
5069         {
5070           gfc_component *c;
5071           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5072           for ( ; c; c = c->next)
5073             if (c->attr.allocatable && c->ts.type == BT_CLASS)
5074               {
5075                 gfc_error ("Coindexed object with polymorphic allocatable "
5076                          "subcomponent at %L", &e->where);
5077                 t = FAILURE;
5078                 break;
5079               }
5080         }
5081     }
5082
5083   return t;
5084 }
5085
5086
5087 /* Checks to see that the correct symbol has been host associated.
5088    The only situation where this arises is that in which a twice
5089    contained function is parsed after the host association is made.
5090    Therefore, on detecting this, change the symbol in the expression
5091    and convert the array reference into an actual arglist if the old
5092    symbol is a variable.  */
5093 static bool
5094 check_host_association (gfc_expr *e)
5095 {
5096   gfc_symbol *sym, *old_sym;
5097   gfc_symtree *st;
5098   int n;
5099   gfc_ref *ref;
5100   gfc_actual_arglist *arg, *tail = NULL;
5101   bool retval = e->expr_type == EXPR_FUNCTION;
5102
5103   /*  If the expression is the result of substitution in
5104       interface.c(gfc_extend_expr) because there is no way in
5105       which the host association can be wrong.  */
5106   if (e->symtree == NULL
5107         || e->symtree->n.sym == NULL
5108         || e->user_operator)
5109     return retval;
5110
5111   old_sym = e->symtree->n.sym;
5112
5113   if (gfc_current_ns->parent
5114         && old_sym->ns != gfc_current_ns)
5115     {
5116       /* Use the 'USE' name so that renamed module symbols are
5117          correctly handled.  */
5118       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5119
5120       if (sym && old_sym != sym
5121               && sym->ts.type == old_sym->ts.type
5122               && sym->attr.flavor == FL_PROCEDURE
5123               && sym->attr.contained)
5124         {
5125           /* Clear the shape, since it might not be valid.  */
5126           if (e->shape != NULL)
5127             {
5128               for (n = 0; n < e->rank; n++)
5129                 mpz_clear (e->shape[n]);
5130
5131               gfc_free (e->shape);
5132             }
5133
5134           /* Give the expression the right symtree!  */
5135           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5136           gcc_assert (st != NULL);
5137
5138           if (old_sym->attr.flavor == FL_PROCEDURE
5139                 || e->expr_type == EXPR_FUNCTION)
5140             {
5141               /* Original was function so point to the new symbol, since
5142                  the actual argument list is already attached to the
5143                  expression. */
5144               e->value.function.esym = NULL;
5145               e->symtree = st;
5146             }
5147           else
5148             {
5149               /* Original was variable so convert array references into
5150                  an actual arglist. This does not need any checking now
5151                  since gfc_resolve_function will take care of it.  */
5152               e->value.function.actual = NULL;
5153               e->expr_type = EXPR_FUNCTION;
5154               e->symtree = st;
5155
5156               /* Ambiguity will not arise if the array reference is not
5157                  the last reference.  */
5158               for (ref = e->ref; ref; ref = ref->next)
5159                 if (ref->type == REF_ARRAY && ref->next == NULL)
5160                   break;
5161
5162               gcc_assert (ref->type == REF_ARRAY);
5163
5164               /* Grab the start expressions from the array ref and
5165                  copy them into actual arguments.  */
5166               for (n = 0; n < ref->u.ar.dimen; n++)
5167                 {
5168                   arg = gfc_get_actual_arglist ();
5169                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5170                   if (e->value.function.actual == NULL)
5171                     tail = e->value.function.actual = arg;
5172                   else
5173                     {
5174                       tail->next = arg;
5175                       tail = arg;
5176                     }
5177                 }
5178
5179               /* Dump the reference list and set the rank.  */
5180               gfc_free_ref_list (e->ref);
5181               e->ref = NULL;
5182               e->rank = sym->as ? sym->as->rank : 0;
5183             }
5184
5185           gfc_resolve_expr (e);
5186           sym->refs++;
5187         }
5188     }
5189   /* This might have changed!  */
5190   return e->expr_type == EXPR_FUNCTION;
5191 }
5192
5193
5194 static void
5195 gfc_resolve_character_operator (gfc_expr *e)
5196 {
5197   gfc_expr *op1 = e->value.op.op1;
5198   gfc_expr *op2 = e->value.op.op2;
5199   gfc_expr *e1 = NULL;
5200   gfc_expr *e2 = NULL;
5201
5202   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5203
5204   if (op1->ts.u.cl && op1->ts.u.cl->length)
5205     e1 = gfc_copy_expr (op1->ts.u.cl->length);
5206   else if (op1->expr_type == EXPR_CONSTANT)
5207     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5208                            op1->value.character.length);
5209
5210   if (op2->ts.u.cl && op2->ts.u.cl->length)
5211     e2 = gfc_copy_expr (op2->ts.u.cl->length);
5212   else if (op2->expr_type == EXPR_CONSTANT)
5213     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5214                            op2->value.character.length);
5215
5216   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5217
5218   if (!e1 || !e2)
5219     return;
5220
5221   e->ts.u.cl->length = gfc_add (e1, e2);
5222   e->ts.u.cl->length->ts.type = BT_INTEGER;
5223   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5224   gfc_simplify_expr (e->ts.u.cl->length, 0);
5225   gfc_resolve_expr (e->ts.u.cl->length);
5226
5227   return;
5228 }
5229
5230
5231 /*  Ensure that an character expression has a charlen and, if possible, a
5232     length expression.  */
5233
5234 static void
5235 fixup_charlen (gfc_expr *e)
5236 {
5237   /* The cases fall through so that changes in expression type and the need
5238      for multiple fixes are picked up.  In all circumstances, a charlen should
5239      be available for the middle end to hang a backend_decl on.  */
5240   switch (e->expr_type)
5241     {
5242     case EXPR_OP:
5243       gfc_resolve_character_operator (e);
5244
5245     case EXPR_ARRAY:
5246       if (e->expr_type == EXPR_ARRAY)
5247         gfc_resolve_character_array_constructor (e);
5248
5249     case EXPR_SUBSTRING:
5250       if (!e->ts.u.cl && e->ref)
5251         gfc_resolve_substring_charlen (e);
5252
5253     default:
5254       if (!e->ts.u.cl)
5255         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5256
5257       break;
5258     }
5259 }
5260
5261
5262 /* Update an actual argument to include the passed-object for type-bound
5263    procedures at the right position.  */
5264
5265 static gfc_actual_arglist*
5266 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5267                      const char *name)
5268 {
5269   gcc_assert (argpos > 0);
5270
5271   if (argpos == 1)
5272     {
5273       gfc_actual_arglist* result;
5274
5275       result = gfc_get_actual_arglist ();
5276       result->expr = po;
5277       result->next = lst;
5278       if (name)
5279         result->name = name;
5280
5281       return result;
5282     }
5283
5284   if (lst)
5285     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5286   else
5287     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5288   return lst;
5289 }
5290
5291
5292 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5293
5294 static gfc_expr*
5295 extract_compcall_passed_object (gfc_expr* e)
5296 {
5297   gfc_expr* po;
5298
5299   gcc_assert (e->expr_type == EXPR_COMPCALL);
5300
5301   if (e->value.compcall.base_object)
5302     po = gfc_copy_expr (e->value.compcall.base_object);
5303   else
5304     {
5305       po = gfc_get_expr ();
5306       po->expr_type = EXPR_VARIABLE;
5307       po->symtree = e->symtree;
5308       po->ref = gfc_copy_ref (e->ref);
5309       po->where = e->where;
5310     }
5311
5312   if (gfc_resolve_expr (po) == FAILURE)
5313     return NULL;
5314
5315   return po;
5316 }
5317
5318
5319 /* Update the arglist of an EXPR_COMPCALL expression to include the
5320    passed-object.  */
5321
5322 static gfc_try
5323 update_compcall_arglist (gfc_expr* e)
5324 {
5325   gfc_expr* po;
5326   gfc_typebound_proc* tbp;
5327
5328   tbp = e->value.compcall.tbp;
5329
5330   if (tbp->error)
5331     return FAILURE;
5332
5333   po = extract_compcall_passed_object (e);
5334   if (!po)
5335     return FAILURE;
5336
5337   if (tbp->nopass || e->value.compcall.ignore_pass)
5338     {
5339       gfc_free_expr (po);
5340       return SUCCESS;
5341     }
5342
5343   gcc_assert (tbp->pass_arg_num > 0);
5344   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5345                                                   tbp->pass_arg_num,
5346                                                   tbp->pass_arg);
5347
5348   return SUCCESS;
5349 }
5350
5351
5352 /* Extract the passed object from a PPC call (a copy of it).  */
5353
5354 static gfc_expr*
5355 extract_ppc_passed_object (gfc_expr *e)
5356 {
5357   gfc_expr *po;
5358   gfc_ref **ref;
5359
5360   po = gfc_get_expr ();
5361   po->expr_type = EXPR_VARIABLE;
5362   po->symtree = e->symtree;
5363   po->ref = gfc_copy_ref (e->ref);
5364   po->where = e->where;
5365
5366   /* Remove PPC reference.  */
5367   ref = &po->ref;
5368   while ((*ref)->next)
5369     ref = &(*ref)->next;
5370   gfc_free_ref_list (*ref);
5371   *ref = NULL;
5372
5373   if (gfc_resolve_expr (po) == FAILURE)
5374     return NULL;
5375
5376   return po;
5377 }
5378
5379
5380 /* Update the actual arglist of a procedure pointer component to include the
5381    passed-object.  */
5382
5383 static gfc_try
5384 update_ppc_arglist (gfc_expr* e)
5385 {
5386   gfc_expr* po;
5387   gfc_component *ppc;
5388   gfc_typebound_proc* tb;
5389
5390   if (!gfc_is_proc_ptr_comp (e, &ppc))
5391     return FAILURE;
5392
5393   tb = ppc->tb;
5394
5395   if (tb->error)
5396     return FAILURE;
5397   else if (tb->nopass)
5398     return SUCCESS;
5399
5400   po = extract_ppc_passed_object (e);
5401   if (!po)
5402     return FAILURE;
5403
5404   /* F08:R739.  */
5405   if (po->rank > 0)
5406     {
5407       gfc_error ("Passed-object at %L must be scalar", &e->where);
5408       return FAILURE;
5409     }
5410
5411   /* F08:C611.  */
5412   if (po->ts.type == BT_DERIVED && po->ts.u.derived->attr.abstract)
5413     {
5414       gfc_error ("Base object for procedure-pointer component call at %L is of"
5415                  " ABSTRACT type '%s'", &e->where, po->ts.u.derived->name);
5416       return FAILURE;
5417     }
5418
5419   gcc_assert (tb->pass_arg_num > 0);
5420   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5421                                                   tb->pass_arg_num,
5422                                                   tb->pass_arg);
5423
5424   return SUCCESS;
5425 }
5426
5427
5428 /* Check that the object a TBP is called on is valid, i.e. it must not be
5429    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5430
5431 static gfc_try
5432 check_typebound_baseobject (gfc_expr* e)
5433 {
5434   gfc_expr* base;
5435   gfc_try return_value = FAILURE;
5436
5437   base = extract_compcall_passed_object (e);
5438   if (!base)
5439     return FAILURE;
5440
5441   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5442
5443   /* F08:C611.  */
5444   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5445     {
5446       gfc_error ("Base object for type-bound procedure call at %L is of"
5447                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5448       goto cleanup;
5449     }
5450
5451   /* F08:C1230. If the procedure called is NOPASS,
5452      the base object must be scalar.  */
5453   if (e->value.compcall.tbp->nopass && base->rank > 0)
5454     {
5455       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5456                  " be scalar", &e->where);
5457       goto cleanup;
5458     }
5459
5460   /* FIXME: Remove once PR 43214 is fixed (TBP with non-scalar PASS).  */
5461   if (base->rank > 0)
5462     {
5463       gfc_error ("Non-scalar base object at %L currently not implemented",
5464                  &e->where);
5465       goto cleanup;
5466     }
5467
5468   return_value = SUCCESS;
5469
5470 cleanup:
5471   gfc_free_expr (base);
5472   return return_value;
5473 }
5474
5475
5476 /* Resolve a call to a type-bound procedure, either function or subroutine,
5477    statically from the data in an EXPR_COMPCALL expression.  The adapted
5478    arglist and the target-procedure symtree are returned.  */
5479
5480 static gfc_try
5481 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5482                           gfc_actual_arglist** actual)
5483 {
5484   gcc_assert (e->expr_type == EXPR_COMPCALL);
5485   gcc_assert (!e->value.compcall.tbp->is_generic);
5486
5487   /* Update the actual arglist for PASS.  */
5488   if (update_compcall_arglist (e) == FAILURE)
5489     return FAILURE;
5490
5491   *actual = e->value.compcall.actual;
5492   *target = e->value.compcall.tbp->u.specific;
5493
5494   gfc_free_ref_list (e->ref);
5495   e->ref = NULL;
5496   e->value.compcall.actual = NULL;
5497
5498   return SUCCESS;
5499 }
5500
5501
5502 /* Get the ultimate declared type from an expression.  In addition,
5503    return the last class/derived type reference and the copy of the
5504    reference list.  */
5505 static gfc_symbol*
5506 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5507                         gfc_expr *e)
5508 {
5509   gfc_symbol *declared;
5510   gfc_ref *ref;
5511
5512   declared = NULL;
5513   if (class_ref)
5514     *class_ref = NULL;
5515   if (new_ref)
5516     *new_ref = gfc_copy_ref (e->ref);
5517
5518   for (ref = e->ref; ref; ref = ref->next)
5519     {
5520       if (ref->type != REF_COMPONENT)
5521         continue;
5522
5523       if (ref->u.c.component->ts.type == BT_CLASS
5524             || ref->u.c.component->ts.type == BT_DERIVED)
5525         {
5526           declared = ref->u.c.component->ts.u.derived;
5527           if (class_ref)
5528             *class_ref = ref;
5529         }
5530     }
5531
5532   if (declared == NULL)
5533     declared = e->symtree->n.sym->ts.u.derived;
5534
5535   return declared;
5536 }
5537
5538
5539 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5540    which of the specific bindings (if any) matches the arglist and transform
5541    the expression into a call of that binding.  */
5542
5543 static gfc_try
5544 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5545 {
5546   gfc_typebound_proc* genproc;
5547   const char* genname;
5548   gfc_symtree *st;
5549   gfc_symbol *derived;
5550
5551   gcc_assert (e->expr_type == EXPR_COMPCALL);
5552   genname = e->value.compcall.name;
5553   genproc = e->value.compcall.tbp;
5554
5555   if (!genproc->is_generic)
5556     return SUCCESS;
5557
5558   /* Try the bindings on this type and in the inheritance hierarchy.  */
5559   for (; genproc; genproc = genproc->overridden)
5560     {
5561       gfc_tbp_generic* g;
5562
5563       gcc_assert (genproc->is_generic);
5564       for (g = genproc->u.generic; g; g = g->next)
5565         {
5566           gfc_symbol* target;
5567           gfc_actual_arglist* args;
5568           bool matches;
5569
5570           gcc_assert (g->specific);
5571
5572           if (g->specific->error)
5573             continue;
5574
5575           target = g->specific->u.specific->n.sym;
5576
5577           /* Get the right arglist by handling PASS/NOPASS.  */
5578           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5579           if (!g->specific->nopass)
5580             {
5581               gfc_expr* po;
5582               po = extract_compcall_passed_object (e);
5583               if (!po)
5584                 return FAILURE;
5585
5586               gcc_assert (g->specific->pass_arg_num > 0);
5587               gcc_assert (!g->specific->error);
5588               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5589                                           g->specific->pass_arg);
5590             }
5591           resolve_actual_arglist (args, target->attr.proc,
5592                                   is_external_proc (target) && !target->formal);
5593
5594           /* Check if this arglist matches the formal.  */
5595           matches = gfc_arglist_matches_symbol (&args, target);
5596
5597           /* Clean up and break out of the loop if we've found it.  */
5598           gfc_free_actual_arglist (args);
5599           if (matches)
5600             {
5601               e->value.compcall.tbp = g->specific;
5602               genname = g->specific_st->name;
5603               /* Pass along the name for CLASS methods, where the vtab
5604                  procedure pointer component has to be referenced.  */
5605               if (name)
5606                 *name = genname;
5607               goto success;
5608             }
5609         }
5610     }
5611
5612   /* Nothing matching found!  */
5613   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5614              " '%s' at %L", genname, &e->where);
5615   return FAILURE;
5616
5617 success:
5618   /* Make sure that we have the right specific instance for the name.  */
5619   derived = get_declared_from_expr (NULL, NULL, e);
5620
5621   st = gfc_find_typebound_proc (derived, NULL, genname, false, &e->where);
5622   if (st)
5623     e->value.compcall.tbp = st->n.tb;
5624
5625   return SUCCESS;
5626 }
5627
5628
5629 /* Resolve a call to a type-bound subroutine.  */
5630
5631 static gfc_try
5632 resolve_typebound_call (gfc_code* c, const char **name)
5633 {
5634   gfc_actual_arglist* newactual;
5635   gfc_symtree* target;
5636
5637   /* Check that's really a SUBROUTINE.  */
5638   if (!c->expr1->value.compcall.tbp->subroutine)
5639     {
5640       gfc_error ("'%s' at %L should be a SUBROUTINE",
5641                  c->expr1->value.compcall.name, &c->loc);
5642       return FAILURE;
5643     }
5644
5645   if (check_typebound_baseobject (c->expr1) == FAILURE)
5646     return FAILURE;
5647
5648   /* Pass along the name for CLASS methods, where the vtab
5649      procedure pointer component has to be referenced.  */
5650   if (name)
5651     *name = c->expr1->value.compcall.name;
5652
5653   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5654     return FAILURE;
5655
5656   /* Transform into an ordinary EXEC_CALL for now.  */
5657
5658   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5659     return FAILURE;
5660
5661   c->ext.actual = newactual;
5662   c->symtree = target;
5663   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5664
5665   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5666
5667   gfc_free_expr (c->expr1);
5668   c->expr1 = gfc_get_expr ();
5669   c->expr1->expr_type = EXPR_FUNCTION;
5670   c->expr1->symtree = target;
5671   c->expr1->where = c->loc;
5672
5673   return resolve_call (c);
5674 }
5675
5676
5677 /* Resolve a component-call expression.  */
5678 static gfc_try
5679 resolve_compcall (gfc_expr* e, const char **name)
5680 {
5681   gfc_actual_arglist* newactual;
5682   gfc_symtree* target;
5683
5684   /* Check that's really a FUNCTION.  */
5685   if (!e->value.compcall.tbp->function)
5686     {
5687       gfc_error ("'%s' at %L should be a FUNCTION",
5688                  e->value.compcall.name, &e->where);
5689       return FAILURE;
5690     }
5691
5692   /* These must not be assign-calls!  */
5693   gcc_assert (!e->value.compcall.assign);
5694
5695   if (check_typebound_baseobject (e) == FAILURE)
5696     return FAILURE;
5697
5698   /* Pass along the name for CLASS methods, where the vtab
5699      procedure pointer component has to be referenced.  */
5700   if (name)
5701     *name = e->value.compcall.name;
5702
5703   if (resolve_typebound_generic_call (e, name) == FAILURE)
5704     return FAILURE;
5705   gcc_assert (!e->value.compcall.tbp->is_generic);
5706
5707   /* Take the rank from the function's symbol.  */
5708   if (e->value.compcall.tbp->u.specific->n.sym->as)
5709     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5710
5711   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5712      arglist to the TBP's binding target.  */
5713
5714   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5715     return FAILURE;
5716
5717   e->value.function.actual = newactual;
5718   e->value.function.name = NULL;
5719   e->value.function.esym = target->n.sym;
5720   e->value.function.isym = NULL;
5721   e->symtree = target;
5722   e->ts = target->n.sym->ts;
5723   e->expr_type = EXPR_FUNCTION;
5724
5725   /* Resolution is not necessary if this is a class subroutine; this
5726      function only has to identify the specific proc. Resolution of
5727      the call will be done next in resolve_typebound_call.  */
5728   return gfc_resolve_expr (e);
5729 }
5730
5731
5732
5733 /* Resolve a typebound function, or 'method'. First separate all
5734    the non-CLASS references by calling resolve_compcall directly.  */
5735
5736 static gfc_try
5737 resolve_typebound_function (gfc_expr* e)
5738 {
5739   gfc_symbol *declared;
5740   gfc_component *c;
5741   gfc_ref *new_ref;
5742   gfc_ref *class_ref;
5743   gfc_symtree *st;
5744   const char *name;
5745   gfc_typespec ts;
5746   gfc_expr *expr;
5747
5748   st = e->symtree;
5749
5750   /* Deal with typebound operators for CLASS objects.  */
5751   expr = e->value.compcall.base_object;
5752   if (expr && expr->ts.type == BT_CLASS && e->value.compcall.name)
5753     {
5754       /* Since the typebound operators are generic, we have to ensure
5755          that any delays in resolution are corrected and that the vtab
5756          is present.  */
5757       ts = expr->ts;
5758       declared = ts.u.derived;
5759       c = gfc_find_component (declared, "_vptr", true, true);
5760       if (c->ts.u.derived == NULL)
5761         c->ts.u.derived = gfc_find_derived_vtab (declared);
5762
5763       if (resolve_compcall (e, &name) == FAILURE)
5764         return FAILURE;
5765
5766       /* Use the generic name if it is there.  */
5767       name = name ? name : e->value.function.esym->name;
5768       e->symtree = expr->symtree;
5769       e->ref = gfc_copy_ref (expr->ref);
5770       gfc_add_vptr_component (e);
5771       gfc_add_component_ref (e, name);
5772       e->value.function.esym = NULL;
5773       return SUCCESS;
5774     }
5775
5776   if (st == NULL)
5777     return resolve_compcall (e, NULL);
5778
5779   if (resolve_ref (e) == FAILURE)
5780     return FAILURE;
5781
5782   /* Get the CLASS declared type.  */
5783   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5784
5785   /* Weed out cases of the ultimate component being a derived type.  */
5786   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5787          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5788     {
5789       gfc_free_ref_list (new_ref);
5790       return resolve_compcall (e, NULL);
5791     }
5792
5793   c = gfc_find_component (declared, "_data", true, true);
5794   declared = c->ts.u.derived;
5795
5796   /* Treat the call as if it is a typebound procedure, in order to roll
5797      out the correct name for the specific function.  */
5798   if (resolve_compcall (e, &name) == FAILURE)
5799     return FAILURE;
5800   ts = e->ts;
5801
5802   /* Then convert the expression to a procedure pointer component call.  */
5803   e->value.function.esym = NULL;
5804   e->symtree = st;
5805
5806   if (new_ref)  
5807     e->ref = new_ref;
5808
5809   /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5810   gfc_add_vptr_component (e);
5811   gfc_add_component_ref (e, name);
5812
5813   /* Recover the typespec for the expression.  This is really only
5814      necessary for generic procedures, where the additional call
5815      to gfc_add_component_ref seems to throw the collection of the
5816      correct typespec.  */
5817   e->ts = ts;
5818   return SUCCESS;
5819 }
5820
5821 /* Resolve a typebound subroutine, or 'method'. First separate all
5822    the non-CLASS references by calling resolve_typebound_call
5823    directly.  */
5824
5825 static gfc_try
5826 resolve_typebound_subroutine (gfc_code *code)
5827 {
5828   gfc_symbol *declared;
5829   gfc_component *c;
5830   gfc_ref *new_ref;
5831   gfc_ref *class_ref;
5832   gfc_symtree *st;
5833   const char *name;
5834   gfc_typespec ts;
5835   gfc_expr *expr;
5836
5837   st = code->expr1->symtree;
5838
5839   /* Deal with typebound operators for CLASS objects.  */
5840   expr = code->expr1->value.compcall.base_object;
5841   if (expr && expr->symtree->n.sym->ts.type == BT_CLASS
5842         && code->expr1->value.compcall.name)
5843     {
5844       /* Since the typebound operators are generic, we have to ensure
5845          that any delays in resolution are corrected and that the vtab
5846          is present.  */
5847       ts = expr->symtree->n.sym->ts;
5848       declared = ts.u.derived;
5849       c = gfc_find_component (declared, "_vptr", true, true);
5850       if (c->ts.u.derived == NULL)
5851         c->ts.u.derived = gfc_find_derived_vtab (declared);
5852
5853       if (resolve_typebound_call (code, &name) == FAILURE)
5854         return FAILURE;
5855
5856       /* Use the generic name if it is there.  */
5857       name = name ? name : code->expr1->value.function.esym->name;
5858       code->expr1->symtree = expr->symtree;
5859       expr->symtree->n.sym->ts.u.derived = declared;
5860       gfc_add_vptr_component (code->expr1);
5861       gfc_add_component_ref (code->expr1, name);
5862       code->expr1->value.function.esym = NULL;
5863       return SUCCESS;
5864     }
5865
5866   if (st == NULL)
5867     return resolve_typebound_call (code, NULL);
5868
5869   if (resolve_ref (code->expr1) == FAILURE)
5870     return FAILURE;
5871
5872   /* Get the CLASS declared type.  */
5873   get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5874
5875   /* Weed out cases of the ultimate component being a derived type.  */
5876   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5877          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5878     {
5879       gfc_free_ref_list (new_ref);
5880       return resolve_typebound_call (code, NULL);
5881     }
5882
5883   if (resolve_typebound_call (code, &name) == FAILURE)
5884     return FAILURE;
5885   ts = code->expr1->ts;
5886
5887   /* Then convert the expression to a procedure pointer component call.  */
5888   code->expr1->value.function.esym = NULL;
5889   code->expr1->symtree = st;
5890
5891   if (new_ref)
5892     code->expr1->ref = new_ref;
5893
5894   /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5895   gfc_add_vptr_component (code->expr1);
5896   gfc_add_component_ref (code->expr1, name);
5897
5898   /* Recover the typespec for the expression.  This is really only
5899      necessary for generic procedures, where the additional call
5900      to gfc_add_component_ref seems to throw the collection of the
5901      correct typespec.  */
5902   code->expr1->ts = ts;
5903   return SUCCESS;
5904 }
5905
5906
5907 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5908
5909 static gfc_try
5910 resolve_ppc_call (gfc_code* c)
5911 {
5912   gfc_component *comp;
5913   bool b;
5914
5915   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5916   gcc_assert (b);
5917
5918   c->resolved_sym = c->expr1->symtree->n.sym;
5919   c->expr1->expr_type = EXPR_VARIABLE;
5920
5921   if (!comp->attr.subroutine)
5922     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5923
5924   if (resolve_ref (c->expr1) == FAILURE)
5925     return FAILURE;
5926
5927   if (update_ppc_arglist (c->expr1) == FAILURE)
5928     return FAILURE;
5929
5930   c->ext.actual = c->expr1->value.compcall.actual;
5931
5932   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
5933                               comp->formal == NULL) == FAILURE)
5934     return FAILURE;
5935
5936   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
5937
5938   return SUCCESS;
5939 }
5940
5941
5942 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
5943
5944 static gfc_try
5945 resolve_expr_ppc (gfc_expr* e)
5946 {
5947   gfc_component *comp;
5948   bool b;
5949
5950   b = gfc_is_proc_ptr_comp (e, &comp);
5951   gcc_assert (b);
5952
5953   /* Convert to EXPR_FUNCTION.  */
5954   e->expr_type = EXPR_FUNCTION;
5955   e->value.function.isym = NULL;
5956   e->value.function.actual = e->value.compcall.actual;
5957   e->ts = comp->ts;
5958   if (comp->as != NULL)
5959     e->rank = comp->as->rank;
5960
5961   if (!comp->attr.function)
5962     gfc_add_function (&comp->attr, comp->name, &e->where);
5963
5964   if (resolve_ref (e) == FAILURE)
5965     return FAILURE;
5966
5967   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
5968                               comp->formal == NULL) == FAILURE)
5969     return FAILURE;
5970
5971   if (update_ppc_arglist (e) == FAILURE)
5972     return FAILURE;
5973
5974   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
5975
5976   return SUCCESS;
5977 }
5978
5979
5980 static bool
5981 gfc_is_expandable_expr (gfc_expr *e)
5982 {
5983   gfc_constructor *con;
5984
5985   if (e->expr_type == EXPR_ARRAY)
5986     {
5987       /* Traverse the constructor looking for variables that are flavor
5988          parameter.  Parameters must be expanded since they are fully used at
5989          compile time.  */
5990       con = gfc_constructor_first (e->value.constructor);
5991       for (; con; con = gfc_constructor_next (con))
5992         {
5993           if (con->expr->expr_type == EXPR_VARIABLE
5994               && con->expr->symtree
5995               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
5996               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
5997             return true;
5998           if (con->expr->expr_type == EXPR_ARRAY
5999               && gfc_is_expandable_expr (con->expr))
6000             return true;
6001         }
6002     }
6003
6004   return false;
6005 }
6006
6007 /* Resolve an expression.  That is, make sure that types of operands agree
6008    with their operators, intrinsic operators are converted to function calls
6009    for overloaded types and unresolved function references are resolved.  */
6010
6011 gfc_try
6012 gfc_resolve_expr (gfc_expr *e)
6013 {
6014   gfc_try t;
6015   bool inquiry_save;
6016
6017   if (e == NULL)
6018     return SUCCESS;
6019
6020   /* inquiry_argument only applies to variables.  */
6021   inquiry_save = inquiry_argument;
6022   if (e->expr_type != EXPR_VARIABLE)
6023     inquiry_argument = false;
6024
6025   switch (e->expr_type)
6026     {
6027     case EXPR_OP:
6028       t = resolve_operator (e);
6029       break;
6030
6031     case EXPR_FUNCTION:
6032     case EXPR_VARIABLE:
6033
6034       if (check_host_association (e))
6035         t = resolve_function (e);
6036       else
6037         {
6038           t = resolve_variable (e);
6039           if (t == SUCCESS)
6040             expression_rank (e);
6041         }
6042
6043       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6044           && e->ref->type != REF_SUBSTRING)
6045         gfc_resolve_substring_charlen (e);
6046
6047       break;
6048
6049     case EXPR_COMPCALL:
6050       t = resolve_typebound_function (e);
6051       break;
6052
6053     case EXPR_SUBSTRING:
6054       t = resolve_ref (e);
6055       break;
6056
6057     case EXPR_CONSTANT:
6058     case EXPR_NULL:
6059       t = SUCCESS;
6060       break;
6061
6062     case EXPR_PPC:
6063       t = resolve_expr_ppc (e);
6064       break;
6065
6066     case EXPR_ARRAY:
6067       t = FAILURE;
6068       if (resolve_ref (e) == FAILURE)
6069         break;
6070
6071       t = gfc_resolve_array_constructor (e);
6072       /* Also try to expand a constructor.  */
6073       if (t == SUCCESS)
6074         {
6075           expression_rank (e);
6076           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6077             gfc_expand_constructor (e, false);
6078         }
6079
6080       /* This provides the opportunity for the length of constructors with
6081          character valued function elements to propagate the string length
6082          to the expression.  */
6083       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
6084         {
6085           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6086              here rather then add a duplicate test for it above.  */ 
6087           gfc_expand_constructor (e, false);
6088           t = gfc_resolve_character_array_constructor (e);
6089         }
6090
6091       break;
6092
6093     case EXPR_STRUCTURE:
6094       t = resolve_ref (e);
6095       if (t == FAILURE)
6096         break;
6097
6098       t = resolve_structure_cons (e, 0);
6099       if (t == FAILURE)
6100         break;
6101
6102       t = gfc_simplify_expr (e, 0);
6103       break;
6104
6105     default:
6106       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6107     }
6108
6109   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
6110     fixup_charlen (e);
6111
6112   inquiry_argument = inquiry_save;
6113
6114   return t;
6115 }
6116
6117
6118 /* Resolve an expression from an iterator.  They must be scalar and have
6119    INTEGER or (optionally) REAL type.  */
6120
6121 static gfc_try
6122 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6123                            const char *name_msgid)
6124 {
6125   if (gfc_resolve_expr (expr) == FAILURE)
6126     return FAILURE;
6127
6128   if (expr->rank != 0)
6129     {
6130       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6131       return FAILURE;
6132     }
6133
6134   if (expr->ts.type != BT_INTEGER)
6135     {
6136       if (expr->ts.type == BT_REAL)
6137         {
6138           if (real_ok)
6139             return gfc_notify_std (GFC_STD_F95_DEL,
6140                                    "Deleted feature: %s at %L must be integer",
6141                                    _(name_msgid), &expr->where);
6142           else
6143             {
6144               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6145                          &expr->where);
6146               return FAILURE;
6147             }
6148         }
6149       else
6150         {
6151           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6152           return FAILURE;
6153         }
6154     }
6155   return SUCCESS;
6156 }
6157
6158
6159 /* Resolve the expressions in an iterator structure.  If REAL_OK is
6160    false allow only INTEGER type iterators, otherwise allow REAL types.  */
6161
6162 gfc_try
6163 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
6164 {
6165   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
6166       == FAILURE)
6167     return FAILURE;
6168
6169   if (gfc_check_vardef_context (iter->var, false, _("iterator variable"))
6170       == FAILURE)
6171     return FAILURE;
6172
6173   if (gfc_resolve_iterator_expr (iter->start, real_ok,
6174                                  "Start expression in DO loop") == FAILURE)
6175     return FAILURE;
6176
6177   if (gfc_resolve_iterator_expr (iter->end, real_ok,
6178                                  "End expression in DO loop") == FAILURE)
6179     return FAILURE;
6180
6181   if (gfc_resolve_iterator_expr (iter->step, real_ok,
6182                                  "Step expression in DO loop") == FAILURE)
6183     return FAILURE;
6184
6185   if (iter->step->expr_type == EXPR_CONSTANT)
6186     {
6187       if ((iter->step->ts.type == BT_INTEGER
6188            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6189           || (iter->step->ts.type == BT_REAL
6190               && mpfr_sgn (iter->step->value.real) == 0))
6191         {
6192           gfc_error ("Step expression in DO loop at %L cannot be zero",
6193                      &iter->step->where);
6194           return FAILURE;
6195         }
6196     }
6197
6198   /* Convert start, end, and step to the same type as var.  */
6199   if (iter->start->ts.kind != iter->var->ts.kind
6200       || iter->start->ts.type != iter->var->ts.type)
6201     gfc_convert_type (iter->start, &iter->var->ts, 2);
6202
6203   if (iter->end->ts.kind != iter->var->ts.kind
6204       || iter->end->ts.type != iter->var->ts.type)
6205     gfc_convert_type (iter->end, &iter->var->ts, 2);
6206
6207   if (iter->step->ts.kind != iter->var->ts.kind
6208       || iter->step->ts.type != iter->var->ts.type)
6209     gfc_convert_type (iter->step, &iter->var->ts, 2);
6210
6211   if (iter->start->expr_type == EXPR_CONSTANT
6212       && iter->end->expr_type == EXPR_CONSTANT
6213       && iter->step->expr_type == EXPR_CONSTANT)
6214     {
6215       int sgn, cmp;
6216       if (iter->start->ts.type == BT_INTEGER)
6217         {
6218           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6219           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6220         }
6221       else
6222         {
6223           sgn = mpfr_sgn (iter->step->value.real);
6224           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6225         }
6226       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
6227         gfc_warning ("DO loop at %L will be executed zero times",
6228                      &iter->step->where);
6229     }
6230
6231   return SUCCESS;
6232 }
6233
6234
6235 /* Traversal function for find_forall_index.  f == 2 signals that
6236    that variable itself is not to be checked - only the references.  */
6237
6238 static bool
6239 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6240 {
6241   if (expr->expr_type != EXPR_VARIABLE)
6242     return false;
6243   
6244   /* A scalar assignment  */
6245   if (!expr->ref || *f == 1)
6246     {
6247       if (expr->symtree->n.sym == sym)
6248         return true;
6249       else
6250         return false;
6251     }
6252
6253   if (*f == 2)
6254     *f = 1;
6255   return false;
6256 }
6257
6258
6259 /* Check whether the FORALL index appears in the expression or not.
6260    Returns SUCCESS if SYM is found in EXPR.  */
6261
6262 gfc_try
6263 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6264 {
6265   if (gfc_traverse_expr (expr, sym, forall_index, f))
6266     return SUCCESS;
6267   else
6268     return FAILURE;
6269 }
6270
6271
6272 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6273    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6274    INTEGERs, and if stride is a constant it must be nonzero.
6275    Furthermore "A subscript or stride in a forall-triplet-spec shall
6276    not contain a reference to any index-name in the
6277    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6278
6279 static void
6280 resolve_forall_iterators (gfc_forall_iterator *it)
6281 {
6282   gfc_forall_iterator *iter, *iter2;
6283
6284   for (iter = it; iter; iter = iter->next)
6285     {
6286       if (gfc_resolve_expr (iter->var) == SUCCESS
6287           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6288         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6289                    &iter->var->where);
6290
6291       if (gfc_resolve_expr (iter->start) == SUCCESS
6292           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6293         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6294                    &iter->start->where);
6295       if (iter->var->ts.kind != iter->start->ts.kind)
6296         gfc_convert_type (iter->start, &iter->var->ts, 2);
6297
6298       if (gfc_resolve_expr (iter->end) == SUCCESS
6299           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6300         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6301                    &iter->end->where);
6302       if (iter->var->ts.kind != iter->end->ts.kind)
6303         gfc_convert_type (iter->end, &iter->var->ts, 2);
6304
6305       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6306         {
6307           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6308             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6309                        &iter->stride->where, "INTEGER");
6310
6311           if (iter->stride->expr_type == EXPR_CONSTANT
6312               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6313             gfc_error ("FORALL stride expression at %L cannot be zero",
6314                        &iter->stride->where);
6315         }
6316       if (iter->var->ts.kind != iter->stride->ts.kind)
6317         gfc_convert_type (iter->stride, &iter->var->ts, 2);
6318     }
6319
6320   for (iter = it; iter; iter = iter->next)
6321     for (iter2 = iter; iter2; iter2 = iter2->next)
6322       {
6323         if (find_forall_index (iter2->start,
6324                                iter->var->symtree->n.sym, 0) == SUCCESS
6325             || find_forall_index (iter2->end,
6326                                   iter->var->symtree->n.sym, 0) == SUCCESS
6327             || find_forall_index (iter2->stride,
6328                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6329           gfc_error ("FORALL index '%s' may not appear in triplet "
6330                      "specification at %L", iter->var->symtree->name,
6331                      &iter2->start->where);
6332       }
6333 }
6334
6335
6336 /* Given a pointer to a symbol that is a derived type, see if it's
6337    inaccessible, i.e. if it's defined in another module and the components are
6338    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6339    inaccessible components are found, nonzero otherwise.  */
6340
6341 static int
6342 derived_inaccessible (gfc_symbol *sym)
6343 {
6344   gfc_component *c;
6345
6346   if (sym->attr.use_assoc && sym->attr.private_comp)
6347     return 1;
6348
6349   for (c = sym->components; c; c = c->next)
6350     {
6351         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6352           return 1;
6353     }
6354
6355   return 0;
6356 }
6357
6358
6359 /* Resolve the argument of a deallocate expression.  The expression must be
6360    a pointer or a full array.  */
6361
6362 static gfc_try
6363 resolve_deallocate_expr (gfc_expr *e)
6364 {
6365   symbol_attribute attr;
6366   int allocatable, pointer;
6367   gfc_ref *ref;
6368   gfc_symbol *sym;
6369   gfc_component *c;
6370
6371   if (gfc_resolve_expr (e) == FAILURE)
6372     return FAILURE;
6373
6374   if (e->expr_type != EXPR_VARIABLE)
6375     goto bad;
6376
6377   sym = e->symtree->n.sym;
6378
6379   if (sym->ts.type == BT_CLASS)
6380     {
6381       allocatable = CLASS_DATA (sym)->attr.allocatable;
6382       pointer = CLASS_DATA (sym)->attr.class_pointer;
6383     }
6384   else
6385     {
6386       allocatable = sym->attr.allocatable;
6387       pointer = sym->attr.pointer;
6388     }
6389   for (ref = e->ref; ref; ref = ref->next)
6390     {
6391       switch (ref->type)
6392         {
6393         case REF_ARRAY:
6394           if (ref->u.ar.type != AR_FULL)
6395             allocatable = 0;
6396           break;
6397
6398         case REF_COMPONENT:
6399           c = ref->u.c.component;
6400           if (c->ts.type == BT_CLASS)
6401             {
6402               allocatable = CLASS_DATA (c)->attr.allocatable;
6403               pointer = CLASS_DATA (c)->attr.class_pointer;
6404             }
6405           else
6406             {
6407               allocatable = c->attr.allocatable;
6408               pointer = c->attr.pointer;
6409             }
6410           break;
6411
6412         case REF_SUBSTRING:
6413           allocatable = 0;
6414           break;
6415         }
6416     }
6417
6418   attr = gfc_expr_attr (e);
6419
6420   if (allocatable == 0 && attr.pointer == 0)
6421     {
6422     bad:
6423       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6424                  &e->where);
6425       return FAILURE;
6426     }
6427
6428   if (pointer
6429       && gfc_check_vardef_context (e, true, _("DEALLOCATE object")) == FAILURE)
6430     return FAILURE;
6431   if (gfc_check_vardef_context (e, false, _("DEALLOCATE object")) == FAILURE)
6432     return FAILURE;
6433
6434   return SUCCESS;
6435 }
6436
6437
6438 /* Returns true if the expression e contains a reference to the symbol sym.  */
6439 static bool
6440 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6441 {
6442   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6443     return true;
6444
6445   return false;
6446 }
6447
6448 bool
6449 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6450 {
6451   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6452 }
6453
6454
6455 /* Given the expression node e for an allocatable/pointer of derived type to be
6456    allocated, get the expression node to be initialized afterwards (needed for
6457    derived types with default initializers, and derived types with allocatable
6458    components that need nullification.)  */
6459
6460 gfc_expr *
6461 gfc_expr_to_initialize (gfc_expr *e)
6462 {
6463   gfc_expr *result;
6464   gfc_ref *ref;
6465   int i;
6466
6467   result = gfc_copy_expr (e);
6468
6469   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6470   for (ref = result->ref; ref; ref = ref->next)
6471     if (ref->type == REF_ARRAY && ref->next == NULL)
6472       {
6473         ref->u.ar.type = AR_FULL;
6474
6475         for (i = 0; i < ref->u.ar.dimen; i++)
6476           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6477
6478         result->rank = ref->u.ar.dimen;
6479         break;
6480       }
6481
6482   return result;
6483 }
6484
6485
6486 /* If the last ref of an expression is an array ref, return a copy of the
6487    expression with that one removed.  Otherwise, a copy of the original
6488    expression.  This is used for allocate-expressions and pointer assignment
6489    LHS, where there may be an array specification that needs to be stripped
6490    off when using gfc_check_vardef_context.  */
6491
6492 static gfc_expr*
6493 remove_last_array_ref (gfc_expr* e)
6494 {
6495   gfc_expr* e2;
6496   gfc_ref** r;
6497
6498   e2 = gfc_copy_expr (e);
6499   for (r = &e2->ref; *r; r = &(*r)->next)
6500     if ((*r)->type == REF_ARRAY && !(*r)->next)
6501       {
6502         gfc_free_ref_list (*r);
6503         *r = NULL;
6504         break;
6505       }
6506
6507   return e2;
6508 }
6509
6510
6511 /* Used in resolve_allocate_expr to check that a allocation-object and
6512    a source-expr are conformable.  This does not catch all possible 
6513    cases; in particular a runtime checking is needed.  */
6514
6515 static gfc_try
6516 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6517 {
6518   gfc_ref *tail;
6519   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6520   
6521   /* First compare rank.  */
6522   if (tail && e1->rank != tail->u.ar.as->rank)
6523     {
6524       gfc_error ("Source-expr at %L must be scalar or have the "
6525                  "same rank as the allocate-object at %L",
6526                  &e1->where, &e2->where);
6527       return FAILURE;
6528     }
6529
6530   if (e1->shape)
6531     {
6532       int i;
6533       mpz_t s;
6534
6535       mpz_init (s);
6536
6537       for (i = 0; i < e1->rank; i++)
6538         {
6539           if (tail->u.ar.end[i])
6540             {
6541               mpz_set (s, tail->u.ar.end[i]->value.integer);
6542               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6543               mpz_add_ui (s, s, 1);
6544             }
6545           else
6546             {
6547               mpz_set (s, tail->u.ar.start[i]->value.integer);
6548             }
6549
6550           if (mpz_cmp (e1->shape[i], s) != 0)
6551             {
6552               gfc_error ("Source-expr at %L and allocate-object at %L must "
6553                          "have the same shape", &e1->where, &e2->where);
6554               mpz_clear (s);
6555               return FAILURE;
6556             }
6557         }
6558
6559       mpz_clear (s);
6560     }
6561
6562   return SUCCESS;
6563 }
6564
6565
6566 /* Resolve the expression in an ALLOCATE statement, doing the additional
6567    checks to see whether the expression is OK or not.  The expression must
6568    have a trailing array reference that gives the size of the array.  */
6569
6570 static gfc_try
6571 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6572 {
6573   int i, pointer, allocatable, dimension, is_abstract;
6574   int codimension;
6575   symbol_attribute attr;
6576   gfc_ref *ref, *ref2;
6577   gfc_expr *e2;
6578   gfc_array_ref *ar;
6579   gfc_symbol *sym = NULL;
6580   gfc_alloc *a;
6581   gfc_component *c;
6582   gfc_try t;
6583
6584   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6585      checking of coarrays.  */
6586   for (ref = e->ref; ref; ref = ref->next)
6587     if (ref->next == NULL)
6588       break;
6589
6590   if (ref && ref->type == REF_ARRAY)
6591     ref->u.ar.in_allocate = true;
6592
6593   if (gfc_resolve_expr (e) == FAILURE)
6594     goto failure;
6595
6596   /* Make sure the expression is allocatable or a pointer.  If it is
6597      pointer, the next-to-last reference must be a pointer.  */
6598
6599   ref2 = NULL;
6600   if (e->symtree)
6601     sym = e->symtree->n.sym;
6602
6603   /* Check whether ultimate component is abstract and CLASS.  */
6604   is_abstract = 0;
6605
6606   if (e->expr_type != EXPR_VARIABLE)
6607     {
6608       allocatable = 0;
6609       attr = gfc_expr_attr (e);
6610       pointer = attr.pointer;
6611       dimension = attr.dimension;
6612       codimension = attr.codimension;
6613     }
6614   else
6615     {
6616       if (sym->ts.type == BT_CLASS)
6617         {
6618           allocatable = CLASS_DATA (sym)->attr.allocatable;
6619           pointer = CLASS_DATA (sym)->attr.class_pointer;
6620           dimension = CLASS_DATA (sym)->attr.dimension;
6621           codimension = CLASS_DATA (sym)->attr.codimension;
6622           is_abstract = CLASS_DATA (sym)->attr.abstract;
6623         }
6624       else
6625         {
6626           allocatable = sym->attr.allocatable;
6627           pointer = sym->attr.pointer;
6628           dimension = sym->attr.dimension;
6629           codimension = sym->attr.codimension;
6630         }
6631
6632       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6633         {
6634           switch (ref->type)
6635             {
6636               case REF_ARRAY:
6637                 if (ref->next != NULL)
6638                   pointer = 0;
6639                 break;
6640
6641               case REF_COMPONENT:
6642                 /* F2008, C644.  */
6643                 if (gfc_is_coindexed (e))
6644                   {
6645                     gfc_error ("Coindexed allocatable object at %L",
6646                                &e->where);
6647                     goto failure;
6648                   }
6649
6650                 c = ref->u.c.component;
6651                 if (c->ts.type == BT_CLASS)
6652                   {
6653                     allocatable = CLASS_DATA (c)->attr.allocatable;
6654                     pointer = CLASS_DATA (c)->attr.class_pointer;
6655                     dimension = CLASS_DATA (c)->attr.dimension;
6656                     codimension = CLASS_DATA (c)->attr.codimension;
6657                     is_abstract = CLASS_DATA (c)->attr.abstract;
6658                   }
6659                 else
6660                   {
6661                     allocatable = c->attr.allocatable;
6662                     pointer = c->attr.pointer;
6663                     dimension = c->attr.dimension;
6664                     codimension = c->attr.codimension;
6665                     is_abstract = c->attr.abstract;
6666                   }
6667                 break;
6668
6669               case REF_SUBSTRING:
6670                 allocatable = 0;
6671                 pointer = 0;
6672                 break;
6673             }
6674         }
6675     }
6676
6677   if (allocatable == 0 && pointer == 0)
6678     {
6679       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6680                  &e->where);
6681       goto failure;
6682     }
6683
6684   /* Some checks for the SOURCE tag.  */
6685   if (code->expr3)
6686     {
6687       /* Check F03:C631.  */
6688       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6689         {
6690           gfc_error ("Type of entity at %L is type incompatible with "
6691                       "source-expr at %L", &e->where, &code->expr3->where);
6692           goto failure;
6693         }
6694
6695       /* Check F03:C632 and restriction following Note 6.18.  */
6696       if (code->expr3->rank > 0
6697           && conformable_arrays (code->expr3, e) == FAILURE)
6698         goto failure;
6699
6700       /* Check F03:C633.  */
6701       if (code->expr3->ts.kind != e->ts.kind)
6702         {
6703           gfc_error ("The allocate-object at %L and the source-expr at %L "
6704                       "shall have the same kind type parameter",
6705                       &e->where, &code->expr3->where);
6706           goto failure;
6707         }
6708     }
6709
6710   /* Check F08:C629.  */
6711   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
6712       && !code->expr3)
6713     {
6714       gcc_assert (e->ts.type == BT_CLASS);
6715       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6716                  "type-spec or source-expr", sym->name, &e->where);
6717       goto failure;
6718     }
6719
6720   /* In the variable definition context checks, gfc_expr_attr is used
6721      on the expression.  This is fooled by the array specification
6722      present in e, thus we have to eliminate that one temporarily.  */
6723   e2 = remove_last_array_ref (e);
6724   t = SUCCESS;
6725   if (t == SUCCESS && pointer)
6726     t = gfc_check_vardef_context (e2, true, _("ALLOCATE object"));
6727   if (t == SUCCESS)
6728     t = gfc_check_vardef_context (e2, false, _("ALLOCATE object"));
6729   gfc_free_expr (e2);
6730   if (t == FAILURE)
6731     goto failure;
6732
6733   if (!code->expr3)
6734     {
6735       /* Set up default initializer if needed.  */
6736       gfc_typespec ts;
6737       gfc_expr *init_e;
6738
6739       if (code->ext.alloc.ts.type == BT_DERIVED)
6740         ts = code->ext.alloc.ts;
6741       else
6742         ts = e->ts;
6743
6744       if (ts.type == BT_CLASS)
6745         ts = ts.u.derived->components->ts;
6746
6747       if (ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&ts)))
6748         {
6749           gfc_code *init_st = gfc_get_code ();
6750           init_st->loc = code->loc;
6751           init_st->op = EXEC_INIT_ASSIGN;
6752           init_st->expr1 = gfc_expr_to_initialize (e);
6753           init_st->expr2 = init_e;
6754           init_st->next = code->next;
6755           code->next = init_st;
6756         }
6757     }
6758   else if (code->expr3->mold && code->expr3->ts.type == BT_DERIVED)
6759     {
6760       /* Default initialization via MOLD (non-polymorphic).  */
6761       gfc_expr *rhs = gfc_default_initializer (&code->expr3->ts);
6762       gfc_resolve_expr (rhs);
6763       gfc_free_expr (code->expr3);
6764       code->expr3 = rhs;
6765     }
6766
6767   if (e->ts.type == BT_CLASS)
6768     {
6769       /* Make sure the vtab symbol is present when
6770          the module variables are generated.  */
6771       gfc_typespec ts = e->ts;
6772       if (code->expr3)
6773         ts = code->expr3->ts;
6774       else if (code->ext.alloc.ts.type == BT_DERIVED)
6775         ts = code->ext.alloc.ts;
6776       gfc_find_derived_vtab (ts.u.derived);
6777     }
6778
6779   if (pointer || (dimension == 0 && codimension == 0))
6780     goto success;
6781
6782   /* Make sure the last reference node is an array specifiction.  */
6783
6784   if (!ref2 || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
6785       || (dimension && ref2->u.ar.dimen == 0))
6786     {
6787       gfc_error ("Array specification required in ALLOCATE statement "
6788                  "at %L", &e->where);
6789       goto failure;
6790     }
6791
6792   /* Make sure that the array section reference makes sense in the
6793     context of an ALLOCATE specification.  */
6794
6795   ar = &ref2->u.ar;
6796
6797   if (codimension && ar->codimen == 0)
6798     {
6799       gfc_error ("Coarray specification required in ALLOCATE statement "
6800                  "at %L", &e->where);
6801       goto failure;
6802     }
6803
6804   for (i = 0; i < ar->dimen; i++)
6805     {
6806       if (ref2->u.ar.type == AR_ELEMENT)
6807         goto check_symbols;
6808
6809       switch (ar->dimen_type[i])
6810         {
6811         case DIMEN_ELEMENT:
6812           break;
6813
6814         case DIMEN_RANGE:
6815           if (ar->start[i] != NULL
6816               && ar->end[i] != NULL
6817               && ar->stride[i] == NULL)
6818             break;
6819
6820           /* Fall Through...  */
6821
6822         case DIMEN_UNKNOWN:
6823         case DIMEN_VECTOR:
6824         case DIMEN_STAR:
6825           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6826                      &e->where);
6827           goto failure;
6828         }
6829
6830 check_symbols:
6831       for (a = code->ext.alloc.list; a; a = a->next)
6832         {
6833           sym = a->expr->symtree->n.sym;
6834
6835           /* TODO - check derived type components.  */
6836           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6837             continue;
6838
6839           if ((ar->start[i] != NULL
6840                && gfc_find_sym_in_expr (sym, ar->start[i]))
6841               || (ar->end[i] != NULL
6842                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6843             {
6844               gfc_error ("'%s' must not appear in the array specification at "
6845                          "%L in the same ALLOCATE statement where it is "
6846                          "itself allocated", sym->name, &ar->where);
6847               goto failure;
6848             }
6849         }
6850     }
6851
6852   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
6853     {
6854       if (ar->dimen_type[i] == DIMEN_ELEMENT
6855           || ar->dimen_type[i] == DIMEN_RANGE)
6856         {
6857           if (i == (ar->dimen + ar->codimen - 1))
6858             {
6859               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
6860                          "statement at %L", &e->where);
6861               goto failure;
6862             }
6863           break;
6864         }
6865
6866       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
6867           && ar->stride[i] == NULL)
6868         break;
6869
6870       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
6871                  &e->where);
6872       goto failure;
6873     }
6874
6875   if (codimension && ar->as->rank == 0)
6876     {
6877       gfc_error ("Sorry, allocatable scalar coarrays are not yet supported "
6878                  "at %L", &e->where);
6879       goto failure;
6880     }
6881
6882 success:
6883   if (e->ts.deferred)
6884     {
6885       gfc_error ("Support for entity at %L with deferred type parameter "
6886                  "not yet implemented", &e->where);
6887       return FAILURE;
6888     }
6889   return SUCCESS;
6890
6891 failure:
6892   return FAILURE;
6893 }
6894
6895 static void
6896 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
6897 {
6898   gfc_expr *stat, *errmsg, *pe, *qe;
6899   gfc_alloc *a, *p, *q;
6900
6901   stat = code->expr1;
6902   errmsg = code->expr2;
6903
6904   /* Check the stat variable.  */
6905   if (stat)
6906     {
6907       gfc_check_vardef_context (stat, false, _("STAT variable"));
6908
6909       if ((stat->ts.type != BT_INTEGER
6910            && !(stat->ref && (stat->ref->type == REF_ARRAY
6911                               || stat->ref->type == REF_COMPONENT)))
6912           || stat->rank > 0)
6913         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
6914                    "variable", &stat->where);
6915
6916       for (p = code->ext.alloc.list; p; p = p->next)
6917         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
6918           {
6919             gfc_ref *ref1, *ref2;
6920             bool found = true;
6921
6922             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
6923                  ref1 = ref1->next, ref2 = ref2->next)
6924               {
6925                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
6926                   continue;
6927                 if (ref1->u.c.component->name != ref2->u.c.component->name)
6928                   {
6929                     found = false;
6930                     break;
6931                   }
6932               }
6933
6934             if (found)
6935               {
6936                 gfc_error ("Stat-variable at %L shall not be %sd within "
6937                            "the same %s statement", &stat->where, fcn, fcn);
6938                 break;
6939               }
6940           }
6941     }
6942
6943   /* Check the errmsg variable.  */
6944   if (errmsg)
6945     {
6946       if (!stat)
6947         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
6948                      &errmsg->where);
6949
6950       gfc_check_vardef_context (errmsg, false, _("ERRMSG variable"));
6951
6952       if ((errmsg->ts.type != BT_CHARACTER
6953            && !(errmsg->ref
6954                 && (errmsg->ref->type == REF_ARRAY
6955                     || errmsg->ref->type == REF_COMPONENT)))
6956           || errmsg->rank > 0 )
6957         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
6958                    "variable", &errmsg->where);
6959
6960       for (p = code->ext.alloc.list; p; p = p->next)
6961         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
6962           {
6963             gfc_ref *ref1, *ref2;
6964             bool found = true;
6965
6966             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
6967                  ref1 = ref1->next, ref2 = ref2->next)
6968               {
6969                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
6970                   continue;
6971                 if (ref1->u.c.component->name != ref2->u.c.component->name)
6972                   {
6973                     found = false;
6974                     break;
6975                   }
6976               }
6977
6978             if (found)
6979               {
6980                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
6981                            "the same %s statement", &errmsg->where, fcn, fcn);
6982                 break;
6983               }
6984           }
6985     }
6986
6987   /* Check that an allocate-object appears only once in the statement.  
6988      FIXME: Checking derived types is disabled.  */
6989   for (p = code->ext.alloc.list; p; p = p->next)
6990     {
6991       pe = p->expr;
6992       for (q = p->next; q; q = q->next)
6993         {
6994           qe = q->expr;
6995           if (pe->symtree->n.sym->name == qe->symtree->n.sym->name)
6996             {
6997               /* This is a potential collision.  */
6998               gfc_ref *pr = pe->ref;
6999               gfc_ref *qr = qe->ref;
7000               
7001               /* Follow the references  until
7002                  a) They start to differ, in which case there is no error;
7003                  you can deallocate a%b and a%c in a single statement
7004                  b) Both of them stop, which is an error
7005                  c) One of them stops, which is also an error.  */
7006               while (1)
7007                 {
7008                   if (pr == NULL && qr == NULL)
7009                     {
7010                       gfc_error ("Allocate-object at %L also appears at %L",
7011                                  &pe->where, &qe->where);
7012                       break;
7013                     }
7014                   else if (pr != NULL && qr == NULL)
7015                     {
7016                       gfc_error ("Allocate-object at %L is subobject of"
7017                                  " object at %L", &pe->where, &qe->where);
7018                       break;
7019                     }
7020                   else if (pr == NULL && qr != NULL)
7021                     {
7022                       gfc_error ("Allocate-object at %L is subobject of"
7023                                  " object at %L", &qe->where, &pe->where);
7024                       break;
7025                     }
7026                   /* Here, pr != NULL && qr != NULL  */
7027                   gcc_assert(pr->type == qr->type);
7028                   if (pr->type == REF_ARRAY)
7029                     {
7030                       /* Handle cases like allocate(v(3)%x(3), v(2)%x(3)),
7031                          which are legal.  */
7032                       gcc_assert (qr->type == REF_ARRAY);
7033
7034                       if (pr->next && qr->next)
7035                         {
7036                           gfc_array_ref *par = &(pr->u.ar);
7037                           gfc_array_ref *qar = &(qr->u.ar);
7038                           if (gfc_dep_compare_expr (par->start[0],
7039                                                     qar->start[0]) != 0)
7040                               break;
7041                         }
7042                     }
7043                   else
7044                     {
7045                       if (pr->u.c.component->name != qr->u.c.component->name)
7046                         break;
7047                     }
7048                   
7049                   pr = pr->next;
7050                   qr = qr->next;
7051                 }
7052             }
7053         }
7054     }
7055
7056   if (strcmp (fcn, "ALLOCATE") == 0)
7057     {
7058       for (a = code->ext.alloc.list; a; a = a->next)
7059         resolve_allocate_expr (a->expr, code);
7060     }
7061   else
7062     {
7063       for (a = code->ext.alloc.list; a; a = a->next)
7064         resolve_deallocate_expr (a->expr);
7065     }
7066 }
7067
7068
7069 /************ SELECT CASE resolution subroutines ************/
7070
7071 /* Callback function for our mergesort variant.  Determines interval
7072    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7073    op1 > op2.  Assumes we're not dealing with the default case.  
7074    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7075    There are nine situations to check.  */
7076
7077 static int
7078 compare_cases (const gfc_case *op1, const gfc_case *op2)
7079 {
7080   int retval;
7081
7082   if (op1->low == NULL) /* op1 = (:L)  */
7083     {
7084       /* op2 = (:N), so overlap.  */
7085       retval = 0;
7086       /* op2 = (M:) or (M:N),  L < M  */
7087       if (op2->low != NULL
7088           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7089         retval = -1;
7090     }
7091   else if (op1->high == NULL) /* op1 = (K:)  */
7092     {
7093       /* op2 = (M:), so overlap.  */
7094       retval = 0;
7095       /* op2 = (:N) or (M:N), K > N  */
7096       if (op2->high != NULL
7097           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7098         retval = 1;
7099     }
7100   else /* op1 = (K:L)  */
7101     {
7102       if (op2->low == NULL)       /* op2 = (:N), K > N  */
7103         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7104                  ? 1 : 0;
7105       else if (op2->high == NULL) /* op2 = (M:), L < M  */
7106         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7107                  ? -1 : 0;
7108       else                      /* op2 = (M:N)  */
7109         {
7110           retval =  0;
7111           /* L < M  */
7112           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7113             retval =  -1;
7114           /* K > N  */
7115           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7116             retval =  1;
7117         }
7118     }
7119
7120   return retval;
7121 }
7122
7123
7124 /* Merge-sort a double linked case list, detecting overlap in the
7125    process.  LIST is the head of the double linked case list before it
7126    is sorted.  Returns the head of the sorted list if we don't see any
7127    overlap, or NULL otherwise.  */
7128
7129 static gfc_case *
7130 check_case_overlap (gfc_case *list)
7131 {
7132   gfc_case *p, *q, *e, *tail;
7133   int insize, nmerges, psize, qsize, cmp, overlap_seen;
7134
7135   /* If the passed list was empty, return immediately.  */
7136   if (!list)
7137     return NULL;
7138
7139   overlap_seen = 0;
7140   insize = 1;
7141
7142   /* Loop unconditionally.  The only exit from this loop is a return
7143      statement, when we've finished sorting the case list.  */
7144   for (;;)
7145     {
7146       p = list;
7147       list = NULL;
7148       tail = NULL;
7149
7150       /* Count the number of merges we do in this pass.  */
7151       nmerges = 0;
7152
7153       /* Loop while there exists a merge to be done.  */
7154       while (p)
7155         {
7156           int i;
7157
7158           /* Count this merge.  */
7159           nmerges++;
7160
7161           /* Cut the list in two pieces by stepping INSIZE places
7162              forward in the list, starting from P.  */
7163           psize = 0;
7164           q = p;
7165           for (i = 0; i < insize; i++)
7166             {
7167               psize++;
7168               q = q->right;
7169               if (!q)
7170                 break;
7171             }
7172           qsize = insize;
7173
7174           /* Now we have two lists.  Merge them!  */
7175           while (psize > 0 || (qsize > 0 && q != NULL))
7176             {
7177               /* See from which the next case to merge comes from.  */
7178               if (psize == 0)
7179                 {
7180                   /* P is empty so the next case must come from Q.  */
7181                   e = q;
7182                   q = q->right;
7183                   qsize--;
7184                 }
7185               else if (qsize == 0 || q == NULL)
7186                 {
7187                   /* Q is empty.  */
7188                   e = p;
7189                   p = p->right;
7190                   psize--;
7191                 }
7192               else
7193                 {
7194                   cmp = compare_cases (p, q);
7195                   if (cmp < 0)
7196                     {
7197                       /* The whole case range for P is less than the
7198                          one for Q.  */
7199                       e = p;
7200                       p = p->right;
7201                       psize--;
7202                     }
7203                   else if (cmp > 0)
7204                     {
7205                       /* The whole case range for Q is greater than
7206                          the case range for P.  */
7207                       e = q;
7208                       q = q->right;
7209                       qsize--;
7210                     }
7211                   else
7212                     {
7213                       /* The cases overlap, or they are the same
7214                          element in the list.  Either way, we must
7215                          issue an error and get the next case from P.  */
7216                       /* FIXME: Sort P and Q by line number.  */
7217                       gfc_error ("CASE label at %L overlaps with CASE "
7218                                  "label at %L", &p->where, &q->where);
7219                       overlap_seen = 1;
7220                       e = p;
7221                       p = p->right;
7222                       psize--;
7223                     }
7224                 }
7225
7226                 /* Add the next element to the merged list.  */
7227               if (tail)
7228                 tail->right = e;
7229               else
7230                 list = e;
7231               e->left = tail;
7232               tail = e;
7233             }
7234
7235           /* P has now stepped INSIZE places along, and so has Q.  So
7236              they're the same.  */
7237           p = q;
7238         }
7239       tail->right = NULL;
7240
7241       /* If we have done only one merge or none at all, we've
7242          finished sorting the cases.  */
7243       if (nmerges <= 1)
7244         {
7245           if (!overlap_seen)
7246             return list;
7247           else
7248             return NULL;
7249         }
7250
7251       /* Otherwise repeat, merging lists twice the size.  */
7252       insize *= 2;
7253     }
7254 }
7255
7256
7257 /* Check to see if an expression is suitable for use in a CASE statement.
7258    Makes sure that all case expressions are scalar constants of the same
7259    type.  Return FAILURE if anything is wrong.  */
7260
7261 static gfc_try
7262 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7263 {
7264   if (e == NULL) return SUCCESS;
7265
7266   if (e->ts.type != case_expr->ts.type)
7267     {
7268       gfc_error ("Expression in CASE statement at %L must be of type %s",
7269                  &e->where, gfc_basic_typename (case_expr->ts.type));
7270       return FAILURE;
7271     }
7272
7273   /* C805 (R808) For a given case-construct, each case-value shall be of
7274      the same type as case-expr.  For character type, length differences
7275      are allowed, but the kind type parameters shall be the same.  */
7276
7277   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7278     {
7279       gfc_error ("Expression in CASE statement at %L must be of kind %d",
7280                  &e->where, case_expr->ts.kind);
7281       return FAILURE;
7282     }
7283
7284   /* Convert the case value kind to that of case expression kind,
7285      if needed */
7286
7287   if (e->ts.kind != case_expr->ts.kind)
7288     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7289
7290   if (e->rank != 0)
7291     {
7292       gfc_error ("Expression in CASE statement at %L must be scalar",
7293                  &e->where);
7294       return FAILURE;
7295     }
7296
7297   return SUCCESS;
7298 }
7299
7300
7301 /* Given a completely parsed select statement, we:
7302
7303      - Validate all expressions and code within the SELECT.
7304      - Make sure that the selection expression is not of the wrong type.
7305      - Make sure that no case ranges overlap.
7306      - Eliminate unreachable cases and unreachable code resulting from
7307        removing case labels.
7308
7309    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7310    they are a hassle for code generation, and to prevent that, we just
7311    cut them out here.  This is not necessary for overlapping cases
7312    because they are illegal and we never even try to generate code.
7313
7314    We have the additional caveat that a SELECT construct could have
7315    been a computed GOTO in the source code. Fortunately we can fairly
7316    easily work around that here: The case_expr for a "real" SELECT CASE
7317    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7318    we have to do is make sure that the case_expr is a scalar integer
7319    expression.  */
7320
7321 static void
7322 resolve_select (gfc_code *code)
7323 {
7324   gfc_code *body;
7325   gfc_expr *case_expr;
7326   gfc_case *cp, *default_case, *tail, *head;
7327   int seen_unreachable;
7328   int seen_logical;
7329   int ncases;
7330   bt type;
7331   gfc_try t;
7332
7333   if (code->expr1 == NULL)
7334     {
7335       /* This was actually a computed GOTO statement.  */
7336       case_expr = code->expr2;
7337       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7338         gfc_error ("Selection expression in computed GOTO statement "
7339                    "at %L must be a scalar integer expression",
7340                    &case_expr->where);
7341
7342       /* Further checking is not necessary because this SELECT was built
7343          by the compiler, so it should always be OK.  Just move the
7344          case_expr from expr2 to expr so that we can handle computed
7345          GOTOs as normal SELECTs from here on.  */
7346       code->expr1 = code->expr2;
7347       code->expr2 = NULL;
7348       return;
7349     }
7350
7351   case_expr = code->expr1;
7352
7353   type = case_expr->ts.type;
7354   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7355     {
7356       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7357                  &case_expr->where, gfc_typename (&case_expr->ts));
7358
7359       /* Punt. Going on here just produce more garbage error messages.  */
7360       return;
7361     }
7362
7363   if (case_expr->rank != 0)
7364     {
7365       gfc_error ("Argument of SELECT statement at %L must be a scalar "
7366                  "expression", &case_expr->where);
7367
7368       /* Punt.  */
7369       return;
7370     }
7371
7372
7373   /* Raise a warning if an INTEGER case value exceeds the range of
7374      the case-expr. Later, all expressions will be promoted to the
7375      largest kind of all case-labels.  */
7376
7377   if (type == BT_INTEGER)
7378     for (body = code->block; body; body = body->block)
7379       for (cp = body->ext.case_list; cp; cp = cp->next)
7380         {
7381           if (cp->low
7382               && gfc_check_integer_range (cp->low->value.integer,
7383                                           case_expr->ts.kind) != ARITH_OK)
7384             gfc_warning ("Expression in CASE statement at %L is "
7385                          "not in the range of %s", &cp->low->where,
7386                          gfc_typename (&case_expr->ts));
7387
7388           if (cp->high
7389               && cp->low != cp->high
7390               && gfc_check_integer_range (cp->high->value.integer,
7391                                           case_expr->ts.kind) != ARITH_OK)
7392             gfc_warning ("Expression in CASE statement at %L is "
7393                          "not in the range of %s", &cp->high->where,
7394                          gfc_typename (&case_expr->ts));
7395         }
7396
7397   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7398      of the SELECT CASE expression and its CASE values.  Walk the lists
7399      of case values, and if we find a mismatch, promote case_expr to
7400      the appropriate kind.  */
7401
7402   if (type == BT_LOGICAL || type == BT_INTEGER)
7403     {
7404       for (body = code->block; body; body = body->block)
7405         {
7406           /* Walk the case label list.  */
7407           for (cp = body->ext.case_list; cp; cp = cp->next)
7408             {
7409               /* Intercept the DEFAULT case.  It does not have a kind.  */
7410               if (cp->low == NULL && cp->high == NULL)
7411                 continue;
7412
7413               /* Unreachable case ranges are discarded, so ignore.  */
7414               if (cp->low != NULL && cp->high != NULL
7415                   && cp->low != cp->high
7416                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7417                 continue;
7418
7419               if (cp->low != NULL
7420                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7421                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7422
7423               if (cp->high != NULL
7424                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7425                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7426             }
7427          }
7428     }
7429
7430   /* Assume there is no DEFAULT case.  */
7431   default_case = NULL;
7432   head = tail = NULL;
7433   ncases = 0;
7434   seen_logical = 0;
7435
7436   for (body = code->block; body; body = body->block)
7437     {
7438       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7439       t = SUCCESS;
7440       seen_unreachable = 0;
7441
7442       /* Walk the case label list, making sure that all case labels
7443          are legal.  */
7444       for (cp = body->ext.case_list; cp; cp = cp->next)
7445         {
7446           /* Count the number of cases in the whole construct.  */
7447           ncases++;
7448
7449           /* Intercept the DEFAULT case.  */
7450           if (cp->low == NULL && cp->high == NULL)
7451             {
7452               if (default_case != NULL)
7453                 {
7454                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7455                              "by a second DEFAULT CASE at %L",
7456                              &default_case->where, &cp->where);
7457                   t = FAILURE;
7458                   break;
7459                 }
7460               else
7461                 {
7462                   default_case = cp;
7463                   continue;
7464                 }
7465             }
7466
7467           /* Deal with single value cases and case ranges.  Errors are
7468              issued from the validation function.  */
7469           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7470               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7471             {
7472               t = FAILURE;
7473               break;
7474             }
7475
7476           if (type == BT_LOGICAL
7477               && ((cp->low == NULL || cp->high == NULL)
7478                   || cp->low != cp->high))
7479             {
7480               gfc_error ("Logical range in CASE statement at %L is not "
7481                          "allowed", &cp->low->where);
7482               t = FAILURE;
7483               break;
7484             }
7485
7486           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7487             {
7488               int value;
7489               value = cp->low->value.logical == 0 ? 2 : 1;
7490               if (value & seen_logical)
7491                 {
7492                   gfc_error ("Constant logical value in CASE statement "
7493                              "is repeated at %L",
7494                              &cp->low->where);
7495                   t = FAILURE;
7496                   break;
7497                 }
7498               seen_logical |= value;
7499             }
7500
7501           if (cp->low != NULL && cp->high != NULL
7502               && cp->low != cp->high
7503               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7504             {
7505               if (gfc_option.warn_surprising)
7506                 gfc_warning ("Range specification at %L can never "
7507                              "be matched", &cp->where);
7508
7509               cp->unreachable = 1;
7510               seen_unreachable = 1;
7511             }
7512           else
7513             {
7514               /* If the case range can be matched, it can also overlap with
7515                  other cases.  To make sure it does not, we put it in a
7516                  double linked list here.  We sort that with a merge sort
7517                  later on to detect any overlapping cases.  */
7518               if (!head)
7519                 {
7520                   head = tail = cp;
7521                   head->right = head->left = NULL;
7522                 }
7523               else
7524                 {
7525                   tail->right = cp;
7526                   tail->right->left = tail;
7527                   tail = tail->right;
7528                   tail->right = NULL;
7529                 }
7530             }
7531         }
7532
7533       /* It there was a failure in the previous case label, give up
7534          for this case label list.  Continue with the next block.  */
7535       if (t == FAILURE)
7536         continue;
7537
7538       /* See if any case labels that are unreachable have been seen.
7539          If so, we eliminate them.  This is a bit of a kludge because
7540          the case lists for a single case statement (label) is a
7541          single forward linked lists.  */
7542       if (seen_unreachable)
7543       {
7544         /* Advance until the first case in the list is reachable.  */
7545         while (body->ext.case_list != NULL
7546                && body->ext.case_list->unreachable)
7547           {
7548             gfc_case *n = body->ext.case_list;
7549             body->ext.case_list = body->ext.case_list->next;
7550             n->next = NULL;
7551             gfc_free_case_list (n);
7552           }
7553
7554         /* Strip all other unreachable cases.  */
7555         if (body->ext.case_list)
7556           {
7557             for (cp = body->ext.case_list; cp->next; cp = cp->next)
7558               {
7559                 if (cp->next->unreachable)
7560                   {
7561                     gfc_case *n = cp->next;
7562                     cp->next = cp->next->next;
7563                     n->next = NULL;
7564                     gfc_free_case_list (n);
7565                   }
7566               }
7567           }
7568       }
7569     }
7570
7571   /* See if there were overlapping cases.  If the check returns NULL,
7572      there was overlap.  In that case we don't do anything.  If head
7573      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7574      then used during code generation for SELECT CASE constructs with
7575      a case expression of a CHARACTER type.  */
7576   if (head)
7577     {
7578       head = check_case_overlap (head);
7579
7580       /* Prepend the default_case if it is there.  */
7581       if (head != NULL && default_case)
7582         {
7583           default_case->left = NULL;
7584           default_case->right = head;
7585           head->left = default_case;
7586         }
7587     }
7588
7589   /* Eliminate dead blocks that may be the result if we've seen
7590      unreachable case labels for a block.  */
7591   for (body = code; body && body->block; body = body->block)
7592     {
7593       if (body->block->ext.case_list == NULL)
7594         {
7595           /* Cut the unreachable block from the code chain.  */
7596           gfc_code *c = body->block;
7597           body->block = c->block;
7598
7599           /* Kill the dead block, but not the blocks below it.  */
7600           c->block = NULL;
7601           gfc_free_statements (c);
7602         }
7603     }
7604
7605   /* More than two cases is legal but insane for logical selects.
7606      Issue a warning for it.  */
7607   if (gfc_option.warn_surprising && type == BT_LOGICAL
7608       && ncases > 2)
7609     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7610                  &code->loc);
7611 }
7612
7613
7614 /* Check if a derived type is extensible.  */
7615
7616 bool
7617 gfc_type_is_extensible (gfc_symbol *sym)
7618 {
7619   return !(sym->attr.is_bind_c || sym->attr.sequence);
7620 }
7621
7622
7623 /* Resolve an associate name:  Resolve target and ensure the type-spec is
7624    correct as well as possibly the array-spec.  */
7625
7626 static void
7627 resolve_assoc_var (gfc_symbol* sym, bool resolve_target)
7628 {
7629   gfc_expr* target;
7630
7631   gcc_assert (sym->assoc);
7632   gcc_assert (sym->attr.flavor == FL_VARIABLE);
7633
7634   /* If this is for SELECT TYPE, the target may not yet be set.  In that
7635      case, return.  Resolution will be called later manually again when
7636      this is done.  */
7637   target = sym->assoc->target;
7638   if (!target)
7639     return;
7640   gcc_assert (!sym->assoc->dangling);
7641
7642   if (resolve_target && gfc_resolve_expr (target) != SUCCESS)
7643     return;
7644
7645   /* For variable targets, we get some attributes from the target.  */
7646   if (target->expr_type == EXPR_VARIABLE)
7647     {
7648       gfc_symbol* tsym;
7649
7650       gcc_assert (target->symtree);
7651       tsym = target->symtree->n.sym;
7652
7653       sym->attr.asynchronous = tsym->attr.asynchronous;
7654       sym->attr.volatile_ = tsym->attr.volatile_;
7655
7656       sym->attr.target = (tsym->attr.target || tsym->attr.pointer);
7657     }
7658
7659   /* Get type if this was not already set.  Note that it can be
7660      some other type than the target in case this is a SELECT TYPE
7661      selector!  So we must not update when the type is already there.  */
7662   if (sym->ts.type == BT_UNKNOWN)
7663     sym->ts = target->ts;
7664   gcc_assert (sym->ts.type != BT_UNKNOWN);
7665
7666   /* See if this is a valid association-to-variable.  */
7667   sym->assoc->variable = (target->expr_type == EXPR_VARIABLE
7668                           && !gfc_has_vector_subscript (target));
7669
7670   /* Finally resolve if this is an array or not.  */
7671   if (sym->attr.dimension && target->rank == 0)
7672     {
7673       gfc_error ("Associate-name '%s' at %L is used as array",
7674                  sym->name, &sym->declared_at);
7675       sym->attr.dimension = 0;
7676       return;
7677     }
7678   if (target->rank > 0)
7679     sym->attr.dimension = 1;
7680
7681   if (sym->attr.dimension)
7682     {
7683       sym->as = gfc_get_array_spec ();
7684       sym->as->rank = target->rank;
7685       sym->as->type = AS_DEFERRED;
7686
7687       /* Target must not be coindexed, thus the associate-variable
7688          has no corank.  */
7689       sym->as->corank = 0;
7690     }
7691 }
7692
7693
7694 /* Resolve a SELECT TYPE statement.  */
7695
7696 static void
7697 resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
7698 {
7699   gfc_symbol *selector_type;
7700   gfc_code *body, *new_st, *if_st, *tail;
7701   gfc_code *class_is = NULL, *default_case = NULL;
7702   gfc_case *c;
7703   gfc_symtree *st;
7704   char name[GFC_MAX_SYMBOL_LEN];
7705   gfc_namespace *ns;
7706   int error = 0;
7707
7708   ns = code->ext.block.ns;
7709   gfc_resolve (ns);
7710
7711   /* Check for F03:C813.  */
7712   if (code->expr1->ts.type != BT_CLASS
7713       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
7714     {
7715       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
7716                  "at %L", &code->loc);
7717       return;
7718     }
7719
7720   if (code->expr2)
7721     {
7722       if (code->expr1->symtree->n.sym->attr.untyped)
7723         code->expr1->symtree->n.sym->ts = code->expr2->ts;
7724       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
7725     }
7726   else
7727     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
7728
7729   /* Loop over TYPE IS / CLASS IS cases.  */
7730   for (body = code->block; body; body = body->block)
7731     {
7732       c = body->ext.case_list;
7733
7734       /* Check F03:C815.  */
7735       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7736           && !gfc_type_is_extensible (c->ts.u.derived))
7737         {
7738           gfc_error ("Derived type '%s' at %L must be extensible",
7739                      c->ts.u.derived->name, &c->where);
7740           error++;
7741           continue;
7742         }
7743
7744       /* Check F03:C816.  */
7745       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7746           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
7747         {
7748           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
7749                      c->ts.u.derived->name, &c->where, selector_type->name);
7750           error++;
7751           continue;
7752         }
7753
7754       /* Intercept the DEFAULT case.  */
7755       if (c->ts.type == BT_UNKNOWN)
7756         {
7757           /* Check F03:C818.  */
7758           if (default_case)
7759             {
7760               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7761                          "by a second DEFAULT CASE at %L",
7762                          &default_case->ext.case_list->where, &c->where);
7763               error++;
7764               continue;
7765             }
7766
7767           default_case = body;
7768         }
7769     }
7770     
7771   if (error > 0)
7772     return;
7773
7774   /* Transform SELECT TYPE statement to BLOCK and associate selector to
7775      target if present.  If there are any EXIT statements referring to the
7776      SELECT TYPE construct, this is no problem because the gfc_code
7777      reference stays the same and EXIT is equally possible from the BLOCK
7778      it is changed to.  */
7779   code->op = EXEC_BLOCK;
7780   if (code->expr2)
7781     {
7782       gfc_association_list* assoc;
7783
7784       assoc = gfc_get_association_list ();
7785       assoc->st = code->expr1->symtree;
7786       assoc->target = gfc_copy_expr (code->expr2);
7787       /* assoc->variable will be set by resolve_assoc_var.  */
7788       
7789       code->ext.block.assoc = assoc;
7790       code->expr1->symtree->n.sym->assoc = assoc;
7791
7792       resolve_assoc_var (code->expr1->symtree->n.sym, false);
7793     }
7794   else
7795     code->ext.block.assoc = NULL;
7796
7797   /* Add EXEC_SELECT to switch on type.  */
7798   new_st = gfc_get_code ();
7799   new_st->op = code->op;
7800   new_st->expr1 = code->expr1;
7801   new_st->expr2 = code->expr2;
7802   new_st->block = code->block;
7803   code->expr1 = code->expr2 =  NULL;
7804   code->block = NULL;
7805   if (!ns->code)
7806     ns->code = new_st;
7807   else
7808     ns->code->next = new_st;
7809   code = new_st;
7810   code->op = EXEC_SELECT;
7811   gfc_add_vptr_component (code->expr1);
7812   gfc_add_hash_component (code->expr1);
7813
7814   /* Loop over TYPE IS / CLASS IS cases.  */
7815   for (body = code->block; body; body = body->block)
7816     {
7817       c = body->ext.case_list;
7818
7819       if (c->ts.type == BT_DERIVED)
7820         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
7821                                              c->ts.u.derived->hash_value);
7822
7823       else if (c->ts.type == BT_UNKNOWN)
7824         continue;
7825
7826       /* Associate temporary to selector.  This should only be done
7827          when this case is actually true, so build a new ASSOCIATE
7828          that does precisely this here (instead of using the
7829          'global' one).  */
7830
7831       if (c->ts.type == BT_CLASS)
7832         sprintf (name, "__tmp_class_%s", c->ts.u.derived->name);
7833       else
7834         sprintf (name, "__tmp_type_%s", c->ts.u.derived->name);
7835       st = gfc_find_symtree (ns->sym_root, name);
7836       gcc_assert (st->n.sym->assoc);
7837       st->n.sym->assoc->target = gfc_get_variable_expr (code->expr1->symtree);
7838       if (c->ts.type == BT_DERIVED)
7839         gfc_add_data_component (st->n.sym->assoc->target);
7840
7841       new_st = gfc_get_code ();
7842       new_st->op = EXEC_BLOCK;
7843       new_st->ext.block.ns = gfc_build_block_ns (ns);
7844       new_st->ext.block.ns->code = body->next;
7845       body->next = new_st;
7846
7847       /* Chain in the new list only if it is marked as dangling.  Otherwise
7848          there is a CASE label overlap and this is already used.  Just ignore,
7849          the error is diagonsed elsewhere.  */
7850       if (st->n.sym->assoc->dangling)
7851         {
7852           new_st->ext.block.assoc = st->n.sym->assoc;
7853           st->n.sym->assoc->dangling = 0;
7854         }
7855
7856       resolve_assoc_var (st->n.sym, false);
7857     }
7858     
7859   /* Take out CLASS IS cases for separate treatment.  */
7860   body = code;
7861   while (body && body->block)
7862     {
7863       if (body->block->ext.case_list->ts.type == BT_CLASS)
7864         {
7865           /* Add to class_is list.  */
7866           if (class_is == NULL)
7867             { 
7868               class_is = body->block;
7869               tail = class_is;
7870             }
7871           else
7872             {
7873               for (tail = class_is; tail->block; tail = tail->block) ;
7874               tail->block = body->block;
7875               tail = tail->block;
7876             }
7877           /* Remove from EXEC_SELECT list.  */
7878           body->block = body->block->block;
7879           tail->block = NULL;
7880         }
7881       else
7882         body = body->block;
7883     }
7884
7885   if (class_is)
7886     {
7887       gfc_symbol *vtab;
7888       
7889       if (!default_case)
7890         {
7891           /* Add a default case to hold the CLASS IS cases.  */
7892           for (tail = code; tail->block; tail = tail->block) ;
7893           tail->block = gfc_get_code ();
7894           tail = tail->block;
7895           tail->op = EXEC_SELECT_TYPE;
7896           tail->ext.case_list = gfc_get_case ();
7897           tail->ext.case_list->ts.type = BT_UNKNOWN;
7898           tail->next = NULL;
7899           default_case = tail;
7900         }
7901
7902       /* More than one CLASS IS block?  */
7903       if (class_is->block)
7904         {
7905           gfc_code **c1,*c2;
7906           bool swapped;
7907           /* Sort CLASS IS blocks by extension level.  */
7908           do
7909             {
7910               swapped = false;
7911               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
7912                 {
7913                   c2 = (*c1)->block;
7914                   /* F03:C817 (check for doubles).  */
7915                   if ((*c1)->ext.case_list->ts.u.derived->hash_value
7916                       == c2->ext.case_list->ts.u.derived->hash_value)
7917                     {
7918                       gfc_error ("Double CLASS IS block in SELECT TYPE "
7919                                  "statement at %L", &c2->ext.case_list->where);
7920                       return;
7921                     }
7922                   if ((*c1)->ext.case_list->ts.u.derived->attr.extension
7923                       < c2->ext.case_list->ts.u.derived->attr.extension)
7924                     {
7925                       /* Swap.  */
7926                       (*c1)->block = c2->block;
7927                       c2->block = *c1;
7928                       *c1 = c2;
7929                       swapped = true;
7930                     }
7931                 }
7932             }
7933           while (swapped);
7934         }
7935         
7936       /* Generate IF chain.  */
7937       if_st = gfc_get_code ();
7938       if_st->op = EXEC_IF;
7939       new_st = if_st;
7940       for (body = class_is; body; body = body->block)
7941         {
7942           new_st->block = gfc_get_code ();
7943           new_st = new_st->block;
7944           new_st->op = EXEC_IF;
7945           /* Set up IF condition: Call _gfortran_is_extension_of.  */
7946           new_st->expr1 = gfc_get_expr ();
7947           new_st->expr1->expr_type = EXPR_FUNCTION;
7948           new_st->expr1->ts.type = BT_LOGICAL;
7949           new_st->expr1->ts.kind = 4;
7950           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
7951           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
7952           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
7953           /* Set up arguments.  */
7954           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
7955           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
7956           new_st->expr1->value.function.actual->expr->where = code->loc;
7957           gfc_add_vptr_component (new_st->expr1->value.function.actual->expr);
7958           vtab = gfc_find_derived_vtab (body->ext.case_list->ts.u.derived);
7959           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
7960           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
7961           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
7962           new_st->next = body->next;
7963         }
7964         if (default_case->next)
7965           {
7966             new_st->block = gfc_get_code ();
7967             new_st = new_st->block;
7968             new_st->op = EXEC_IF;
7969             new_st->next = default_case->next;
7970           }
7971           
7972         /* Replace CLASS DEFAULT code by the IF chain.  */
7973         default_case->next = if_st;
7974     }
7975
7976   /* Resolve the internal code.  This can not be done earlier because
7977      it requires that the sym->assoc of selectors is set already.  */
7978   gfc_current_ns = ns;
7979   gfc_resolve_blocks (code->block, gfc_current_ns);
7980   gfc_current_ns = old_ns;
7981
7982   resolve_select (code);
7983 }
7984
7985
7986 /* Resolve a transfer statement. This is making sure that:
7987    -- a derived type being transferred has only non-pointer components
7988    -- a derived type being transferred doesn't have private components, unless 
7989       it's being transferred from the module where the type was defined
7990    -- we're not trying to transfer a whole assumed size array.  */
7991
7992 static void
7993 resolve_transfer (gfc_code *code)
7994 {
7995   gfc_typespec *ts;
7996   gfc_symbol *sym;
7997   gfc_ref *ref;
7998   gfc_expr *exp;
7999
8000   exp = code->expr1;
8001
8002   while (exp != NULL && exp->expr_type == EXPR_OP
8003          && exp->value.op.op == INTRINSIC_PARENTHESES)
8004     exp = exp->value.op.op1;
8005
8006   if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
8007                       && exp->expr_type != EXPR_FUNCTION))
8008     return;
8009
8010   /* If we are reading, the variable will be changed.  Note that
8011      code->ext.dt may be NULL if the TRANSFER is related to
8012      an INQUIRE statement -- but in this case, we are not reading, either.  */
8013   if (code->ext.dt && code->ext.dt->dt_io_kind->value.iokind == M_READ
8014       && gfc_check_vardef_context (exp, false, _("item in READ")) == FAILURE)
8015     return;
8016
8017   sym = exp->symtree->n.sym;
8018   ts = &sym->ts;
8019
8020   /* Go to actual component transferred.  */
8021   for (ref = exp->ref; ref; ref = ref->next)
8022     if (ref->type == REF_COMPONENT)
8023       ts = &ref->u.c.component->ts;
8024
8025   if (ts->type == BT_CLASS)
8026     {
8027       /* FIXME: Test for defined input/output.  */
8028       gfc_error ("Data transfer element at %L cannot be polymorphic unless "
8029                 "it is processed by a defined input/output procedure",
8030                 &code->loc);
8031       return;
8032     }
8033
8034   if (ts->type == BT_DERIVED)
8035     {
8036       /* Check that transferred derived type doesn't contain POINTER
8037          components.  */
8038       if (ts->u.derived->attr.pointer_comp)
8039         {
8040           gfc_error ("Data transfer element at %L cannot have "
8041                      "POINTER components", &code->loc);
8042           return;
8043         }
8044
8045       if (ts->u.derived->attr.alloc_comp)
8046         {
8047           gfc_error ("Data transfer element at %L cannot have "
8048                      "ALLOCATABLE components", &code->loc);
8049           return;
8050         }
8051
8052       if (derived_inaccessible (ts->u.derived))
8053         {
8054           gfc_error ("Data transfer element at %L cannot have "
8055                      "PRIVATE components",&code->loc);
8056           return;
8057         }
8058     }
8059
8060   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
8061       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
8062     {
8063       gfc_error ("Data transfer element at %L cannot be a full reference to "
8064                  "an assumed-size array", &code->loc);
8065       return;
8066     }
8067 }
8068
8069
8070 /*********** Toplevel code resolution subroutines ***********/
8071
8072 /* Find the set of labels that are reachable from this block.  We also
8073    record the last statement in each block.  */
8074      
8075 static void
8076 find_reachable_labels (gfc_code *block)
8077 {
8078   gfc_code *c;
8079
8080   if (!block)
8081     return;
8082
8083   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
8084
8085   /* Collect labels in this block.  We don't keep those corresponding
8086      to END {IF|SELECT}, these are checked in resolve_branch by going
8087      up through the code_stack.  */
8088   for (c = block; c; c = c->next)
8089     {
8090       if (c->here && c->op != EXEC_END_BLOCK)
8091         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
8092     }
8093
8094   /* Merge with labels from parent block.  */
8095   if (cs_base->prev)
8096     {
8097       gcc_assert (cs_base->prev->reachable_labels);
8098       bitmap_ior_into (cs_base->reachable_labels,
8099                        cs_base->prev->reachable_labels);
8100     }
8101 }
8102
8103
8104 static void
8105 resolve_sync (gfc_code *code)
8106 {
8107   /* Check imageset. The * case matches expr1 == NULL.  */
8108   if (code->expr1)
8109     {
8110       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
8111         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
8112                    "INTEGER expression", &code->expr1->where);
8113       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
8114           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
8115         gfc_error ("Imageset argument at %L must between 1 and num_images()",
8116                    &code->expr1->where);
8117       else if (code->expr1->expr_type == EXPR_ARRAY
8118                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
8119         {
8120            gfc_constructor *cons;
8121            cons = gfc_constructor_first (code->expr1->value.constructor);
8122            for (; cons; cons = gfc_constructor_next (cons))
8123              if (cons->expr->expr_type == EXPR_CONSTANT
8124                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
8125                gfc_error ("Imageset argument at %L must between 1 and "
8126                           "num_images()", &cons->expr->where);
8127         }
8128     }
8129
8130   /* Check STAT.  */
8131   if (code->expr2
8132       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8133           || code->expr2->expr_type != EXPR_VARIABLE))
8134     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8135                &code->expr2->where);
8136
8137   /* Check ERRMSG.  */
8138   if (code->expr3
8139       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8140           || code->expr3->expr_type != EXPR_VARIABLE))
8141     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8142                &code->expr3->where);
8143 }
8144
8145
8146 /* Given a branch to a label, see if the branch is conforming.
8147    The code node describes where the branch is located.  */
8148
8149 static void
8150 resolve_branch (gfc_st_label *label, gfc_code *code)
8151 {
8152   code_stack *stack;
8153
8154   if (label == NULL)
8155     return;
8156
8157   /* Step one: is this a valid branching target?  */
8158
8159   if (label->defined == ST_LABEL_UNKNOWN)
8160     {
8161       gfc_error ("Label %d referenced at %L is never defined", label->value,
8162                  &label->where);
8163       return;
8164     }
8165
8166   if (label->defined != ST_LABEL_TARGET)
8167     {
8168       gfc_error ("Statement at %L is not a valid branch target statement "
8169                  "for the branch statement at %L", &label->where, &code->loc);
8170       return;
8171     }
8172
8173   /* Step two: make sure this branch is not a branch to itself ;-)  */
8174
8175   if (code->here == label)
8176     {
8177       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
8178       return;
8179     }
8180
8181   /* Step three:  See if the label is in the same block as the
8182      branching statement.  The hard work has been done by setting up
8183      the bitmap reachable_labels.  */
8184
8185   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8186     {
8187       /* Check now whether there is a CRITICAL construct; if so, check
8188          whether the label is still visible outside of the CRITICAL block,
8189          which is invalid.  */
8190       for (stack = cs_base; stack; stack = stack->prev)
8191         if (stack->current->op == EXEC_CRITICAL
8192             && bitmap_bit_p (stack->reachable_labels, label->value))
8193           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8194                       " at %L", &code->loc, &label->where);
8195
8196       return;
8197     }
8198
8199   /* Step four:  If we haven't found the label in the bitmap, it may
8200     still be the label of the END of the enclosing block, in which
8201     case we find it by going up the code_stack.  */
8202
8203   for (stack = cs_base; stack; stack = stack->prev)
8204     {
8205       if (stack->current->next && stack->current->next->here == label)
8206         break;
8207       if (stack->current->op == EXEC_CRITICAL)
8208         {
8209           /* Note: A label at END CRITICAL does not leave the CRITICAL
8210              construct as END CRITICAL is still part of it.  */
8211           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8212                       " at %L", &code->loc, &label->where);
8213           return;
8214         }
8215     }
8216
8217   if (stack)
8218     {
8219       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
8220       return;
8221     }
8222
8223   /* The label is not in an enclosing block, so illegal.  This was
8224      allowed in Fortran 66, so we allow it as extension.  No
8225      further checks are necessary in this case.  */
8226   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
8227                   "as the GOTO statement at %L", &label->where,
8228                   &code->loc);
8229   return;
8230 }
8231
8232
8233 /* Check whether EXPR1 has the same shape as EXPR2.  */
8234
8235 static gfc_try
8236 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8237 {
8238   mpz_t shape[GFC_MAX_DIMENSIONS];
8239   mpz_t shape2[GFC_MAX_DIMENSIONS];
8240   gfc_try result = FAILURE;
8241   int i;
8242
8243   /* Compare the rank.  */
8244   if (expr1->rank != expr2->rank)
8245     return result;
8246
8247   /* Compare the size of each dimension.  */
8248   for (i=0; i<expr1->rank; i++)
8249     {
8250       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
8251         goto ignore;
8252
8253       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
8254         goto ignore;
8255
8256       if (mpz_cmp (shape[i], shape2[i]))
8257         goto over;
8258     }
8259
8260   /* When either of the two expression is an assumed size array, we
8261      ignore the comparison of dimension sizes.  */
8262 ignore:
8263   result = SUCCESS;
8264
8265 over:
8266   for (i--; i >= 0; i--)
8267     {
8268       mpz_clear (shape[i]);
8269       mpz_clear (shape2[i]);
8270     }
8271   return result;
8272 }
8273
8274
8275 /* Check whether a WHERE assignment target or a WHERE mask expression
8276    has the same shape as the outmost WHERE mask expression.  */
8277
8278 static void
8279 resolve_where (gfc_code *code, gfc_expr *mask)
8280 {
8281   gfc_code *cblock;
8282   gfc_code *cnext;
8283   gfc_expr *e = NULL;
8284
8285   cblock = code->block;
8286
8287   /* Store the first WHERE mask-expr of the WHERE statement or construct.
8288      In case of nested WHERE, only the outmost one is stored.  */
8289   if (mask == NULL) /* outmost WHERE */
8290     e = cblock->expr1;
8291   else /* inner WHERE */
8292     e = mask;
8293
8294   while (cblock)
8295     {
8296       if (cblock->expr1)
8297         {
8298           /* Check if the mask-expr has a consistent shape with the
8299              outmost WHERE mask-expr.  */
8300           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
8301             gfc_error ("WHERE mask at %L has inconsistent shape",
8302                        &cblock->expr1->where);
8303          }
8304
8305       /* the assignment statement of a WHERE statement, or the first
8306          statement in where-body-construct of a WHERE construct */
8307       cnext = cblock->next;
8308       while (cnext)
8309         {
8310           switch (cnext->op)
8311             {
8312             /* WHERE assignment statement */
8313             case EXEC_ASSIGN:
8314
8315               /* Check shape consistent for WHERE assignment target.  */
8316               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
8317                gfc_error ("WHERE assignment target at %L has "
8318                           "inconsistent shape", &cnext->expr1->where);
8319               break;
8320
8321   
8322             case EXEC_ASSIGN_CALL:
8323               resolve_call (cnext);
8324               if (!cnext->resolved_sym->attr.elemental)
8325                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8326                           &cnext->ext.actual->expr->where);
8327               break;
8328
8329             /* WHERE or WHERE construct is part of a where-body-construct */
8330             case EXEC_WHERE:
8331               resolve_where (cnext, e);
8332               break;
8333
8334             default:
8335               gfc_error ("Unsupported statement inside WHERE at %L",
8336                          &cnext->loc);
8337             }
8338          /* the next statement within the same where-body-construct */
8339          cnext = cnext->next;
8340        }
8341     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8342     cblock = cblock->block;
8343   }
8344 }
8345
8346
8347 /* Resolve assignment in FORALL construct.
8348    NVAR is the number of FORALL index variables, and VAR_EXPR records the
8349    FORALL index variables.  */
8350
8351 static void
8352 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8353 {
8354   int n;
8355
8356   for (n = 0; n < nvar; n++)
8357     {
8358       gfc_symbol *forall_index;
8359
8360       forall_index = var_expr[n]->symtree->n.sym;
8361
8362       /* Check whether the assignment target is one of the FORALL index
8363          variable.  */
8364       if ((code->expr1->expr_type == EXPR_VARIABLE)
8365           && (code->expr1->symtree->n.sym == forall_index))
8366         gfc_error ("Assignment to a FORALL index variable at %L",
8367                    &code->expr1->where);
8368       else
8369         {
8370           /* If one of the FORALL index variables doesn't appear in the
8371              assignment variable, then there could be a many-to-one
8372              assignment.  Emit a warning rather than an error because the
8373              mask could be resolving this problem.  */
8374           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
8375             gfc_warning ("The FORALL with index '%s' is not used on the "
8376                          "left side of the assignment at %L and so might "
8377                          "cause multiple assignment to this object",
8378                          var_expr[n]->symtree->name, &code->expr1->where);
8379         }
8380     }
8381 }
8382
8383
8384 /* Resolve WHERE statement in FORALL construct.  */
8385
8386 static void
8387 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
8388                                   gfc_expr **var_expr)
8389 {
8390   gfc_code *cblock;
8391   gfc_code *cnext;
8392
8393   cblock = code->block;
8394   while (cblock)
8395     {
8396       /* the assignment statement of a WHERE statement, or the first
8397          statement in where-body-construct of a WHERE construct */
8398       cnext = cblock->next;
8399       while (cnext)
8400         {
8401           switch (cnext->op)
8402             {
8403             /* WHERE assignment statement */
8404             case EXEC_ASSIGN:
8405               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
8406               break;
8407   
8408             /* WHERE operator assignment statement */
8409             case EXEC_ASSIGN_CALL:
8410               resolve_call (cnext);
8411               if (!cnext->resolved_sym->attr.elemental)
8412                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8413                           &cnext->ext.actual->expr->where);
8414               break;
8415
8416             /* WHERE or WHERE construct is part of a where-body-construct */
8417             case EXEC_WHERE:
8418               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
8419               break;
8420
8421             default:
8422               gfc_error ("Unsupported statement inside WHERE at %L",
8423                          &cnext->loc);
8424             }
8425           /* the next statement within the same where-body-construct */
8426           cnext = cnext->next;
8427         }
8428       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8429       cblock = cblock->block;
8430     }
8431 }
8432
8433
8434 /* Traverse the FORALL body to check whether the following errors exist:
8435    1. For assignment, check if a many-to-one assignment happens.
8436    2. For WHERE statement, check the WHERE body to see if there is any
8437       many-to-one assignment.  */
8438
8439 static void
8440 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
8441 {
8442   gfc_code *c;
8443
8444   c = code->block->next;
8445   while (c)
8446     {
8447       switch (c->op)
8448         {
8449         case EXEC_ASSIGN:
8450         case EXEC_POINTER_ASSIGN:
8451           gfc_resolve_assign_in_forall (c, nvar, var_expr);
8452           break;
8453
8454         case EXEC_ASSIGN_CALL:
8455           resolve_call (c);
8456           break;
8457
8458         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
8459            there is no need to handle it here.  */
8460         case EXEC_FORALL:
8461           break;
8462         case EXEC_WHERE:
8463           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
8464           break;
8465         default:
8466           break;
8467         }
8468       /* The next statement in the FORALL body.  */
8469       c = c->next;
8470     }
8471 }
8472
8473
8474 /* Counts the number of iterators needed inside a forall construct, including
8475    nested forall constructs. This is used to allocate the needed memory 
8476    in gfc_resolve_forall.  */
8477
8478 static int 
8479 gfc_count_forall_iterators (gfc_code *code)
8480 {
8481   int max_iters, sub_iters, current_iters;
8482   gfc_forall_iterator *fa;
8483
8484   gcc_assert(code->op == EXEC_FORALL);
8485   max_iters = 0;
8486   current_iters = 0;
8487
8488   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8489     current_iters ++;
8490   
8491   code = code->block->next;
8492
8493   while (code)
8494     {          
8495       if (code->op == EXEC_FORALL)
8496         {
8497           sub_iters = gfc_count_forall_iterators (code);
8498           if (sub_iters > max_iters)
8499             max_iters = sub_iters;
8500         }
8501       code = code->next;
8502     }
8503
8504   return current_iters + max_iters;
8505 }
8506
8507
8508 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8509    gfc_resolve_forall_body to resolve the FORALL body.  */
8510
8511 static void
8512 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8513 {
8514   static gfc_expr **var_expr;
8515   static int total_var = 0;
8516   static int nvar = 0;
8517   int old_nvar, tmp;
8518   gfc_forall_iterator *fa;
8519   int i;
8520
8521   old_nvar = nvar;
8522
8523   /* Start to resolve a FORALL construct   */
8524   if (forall_save == 0)
8525     {
8526       /* Count the total number of FORALL index in the nested FORALL
8527          construct in order to allocate the VAR_EXPR with proper size.  */
8528       total_var = gfc_count_forall_iterators (code);
8529
8530       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8531       var_expr = (gfc_expr **) gfc_getmem (total_var * sizeof (gfc_expr *));
8532     }
8533
8534   /* The information about FORALL iterator, including FORALL index start, end
8535      and stride. The FORALL index can not appear in start, end or stride.  */
8536   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8537     {
8538       /* Check if any outer FORALL index name is the same as the current
8539          one.  */
8540       for (i = 0; i < nvar; i++)
8541         {
8542           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8543             {
8544               gfc_error ("An outer FORALL construct already has an index "
8545                          "with this name %L", &fa->var->where);
8546             }
8547         }
8548
8549       /* Record the current FORALL index.  */
8550       var_expr[nvar] = gfc_copy_expr (fa->var);
8551
8552       nvar++;
8553
8554       /* No memory leak.  */
8555       gcc_assert (nvar <= total_var);
8556     }
8557
8558   /* Resolve the FORALL body.  */
8559   gfc_resolve_forall_body (code, nvar, var_expr);
8560
8561   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8562   gfc_resolve_blocks (code->block, ns);
8563
8564   tmp = nvar;
8565   nvar = old_nvar;
8566   /* Free only the VAR_EXPRs allocated in this frame.  */
8567   for (i = nvar; i < tmp; i++)
8568      gfc_free_expr (var_expr[i]);
8569
8570   if (nvar == 0)
8571     {
8572       /* We are in the outermost FORALL construct.  */
8573       gcc_assert (forall_save == 0);
8574
8575       /* VAR_EXPR is not needed any more.  */
8576       gfc_free (var_expr);
8577       total_var = 0;
8578     }
8579 }
8580
8581
8582 /* Resolve a BLOCK construct statement.  */
8583
8584 static void
8585 resolve_block_construct (gfc_code* code)
8586 {
8587   /* Resolve the BLOCK's namespace.  */
8588   gfc_resolve (code->ext.block.ns);
8589
8590   /* For an ASSOCIATE block, the associations (and their targets) are already
8591      resolved during resolve_symbol.  */
8592 }
8593
8594
8595 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
8596    DO code nodes.  */
8597
8598 static void resolve_code (gfc_code *, gfc_namespace *);
8599
8600 void
8601 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8602 {
8603   gfc_try t;
8604
8605   for (; b; b = b->block)
8606     {
8607       t = gfc_resolve_expr (b->expr1);
8608       if (gfc_resolve_expr (b->expr2) == FAILURE)
8609         t = FAILURE;
8610
8611       switch (b->op)
8612         {
8613         case EXEC_IF:
8614           if (t == SUCCESS && b->expr1 != NULL
8615               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8616             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8617                        &b->expr1->where);
8618           break;
8619
8620         case EXEC_WHERE:
8621           if (t == SUCCESS
8622               && b->expr1 != NULL
8623               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8624             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8625                        &b->expr1->where);
8626           break;
8627
8628         case EXEC_GOTO:
8629           resolve_branch (b->label1, b);
8630           break;
8631
8632         case EXEC_BLOCK:
8633           resolve_block_construct (b);
8634           break;
8635
8636         case EXEC_SELECT:
8637         case EXEC_SELECT_TYPE:
8638         case EXEC_FORALL:
8639         case EXEC_DO:
8640         case EXEC_DO_WHILE:
8641         case EXEC_CRITICAL:
8642         case EXEC_READ:
8643         case EXEC_WRITE:
8644         case EXEC_IOLENGTH:
8645         case EXEC_WAIT:
8646           break;
8647
8648         case EXEC_OMP_ATOMIC:
8649         case EXEC_OMP_CRITICAL:
8650         case EXEC_OMP_DO:
8651         case EXEC_OMP_MASTER:
8652         case EXEC_OMP_ORDERED:
8653         case EXEC_OMP_PARALLEL:
8654         case EXEC_OMP_PARALLEL_DO:
8655         case EXEC_OMP_PARALLEL_SECTIONS:
8656         case EXEC_OMP_PARALLEL_WORKSHARE:
8657         case EXEC_OMP_SECTIONS:
8658         case EXEC_OMP_SINGLE:
8659         case EXEC_OMP_TASK:
8660         case EXEC_OMP_TASKWAIT:
8661         case EXEC_OMP_WORKSHARE:
8662           break;
8663
8664         default:
8665           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
8666         }
8667
8668       resolve_code (b->next, ns);
8669     }
8670 }
8671
8672
8673 /* Does everything to resolve an ordinary assignment.  Returns true
8674    if this is an interface assignment.  */
8675 static bool
8676 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
8677 {
8678   bool rval = false;
8679   gfc_expr *lhs;
8680   gfc_expr *rhs;
8681   int llen = 0;
8682   int rlen = 0;
8683   int n;
8684   gfc_ref *ref;
8685
8686   if (gfc_extend_assign (code, ns) == SUCCESS)
8687     {
8688       gfc_expr** rhsptr;
8689
8690       if (code->op == EXEC_ASSIGN_CALL)
8691         {
8692           lhs = code->ext.actual->expr;
8693           rhsptr = &code->ext.actual->next->expr;
8694         }
8695       else
8696         {
8697           gfc_actual_arglist* args;
8698           gfc_typebound_proc* tbp;
8699
8700           gcc_assert (code->op == EXEC_COMPCALL);
8701
8702           args = code->expr1->value.compcall.actual;
8703           lhs = args->expr;
8704           rhsptr = &args->next->expr;
8705
8706           tbp = code->expr1->value.compcall.tbp;
8707           gcc_assert (!tbp->is_generic);
8708         }
8709
8710       /* Make a temporary rhs when there is a default initializer
8711          and rhs is the same symbol as the lhs.  */
8712       if ((*rhsptr)->expr_type == EXPR_VARIABLE
8713             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
8714             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
8715             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
8716         *rhsptr = gfc_get_parentheses (*rhsptr);
8717
8718       return true;
8719     }
8720
8721   lhs = code->expr1;
8722   rhs = code->expr2;
8723
8724   if (rhs->is_boz
8725       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
8726                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
8727                          &code->loc) == FAILURE)
8728     return false;
8729
8730   /* Handle the case of a BOZ literal on the RHS.  */
8731   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
8732     {
8733       int rc;
8734       if (gfc_option.warn_surprising)
8735         gfc_warning ("BOZ literal at %L is bitwise transferred "
8736                      "non-integer symbol '%s'", &code->loc,
8737                      lhs->symtree->n.sym->name);
8738
8739       if (!gfc_convert_boz (rhs, &lhs->ts))
8740         return false;
8741       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
8742         {
8743           if (rc == ARITH_UNDERFLOW)
8744             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
8745                        ". This check can be disabled with the option "
8746                        "-fno-range-check", &rhs->where);
8747           else if (rc == ARITH_OVERFLOW)
8748             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
8749                        ". This check can be disabled with the option "
8750                        "-fno-range-check", &rhs->where);
8751           else if (rc == ARITH_NAN)
8752             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
8753                        ". This check can be disabled with the option "
8754                        "-fno-range-check", &rhs->where);
8755           return false;
8756         }
8757     }
8758
8759   if (lhs->ts.type == BT_CHARACTER
8760         && gfc_option.warn_character_truncation)
8761     {
8762       if (lhs->ts.u.cl != NULL
8763             && lhs->ts.u.cl->length != NULL
8764             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8765         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
8766
8767       if (rhs->expr_type == EXPR_CONSTANT)
8768         rlen = rhs->value.character.length;
8769
8770       else if (rhs->ts.u.cl != NULL
8771                  && rhs->ts.u.cl->length != NULL
8772                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8773         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
8774
8775       if (rlen && llen && rlen > llen)
8776         gfc_warning_now ("CHARACTER expression will be truncated "
8777                          "in assignment (%d/%d) at %L",
8778                          llen, rlen, &code->loc);
8779     }
8780
8781   /* Ensure that a vector index expression for the lvalue is evaluated
8782      to a temporary if the lvalue symbol is referenced in it.  */
8783   if (lhs->rank)
8784     {
8785       for (ref = lhs->ref; ref; ref= ref->next)
8786         if (ref->type == REF_ARRAY)
8787           {
8788             for (n = 0; n < ref->u.ar.dimen; n++)
8789               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
8790                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
8791                                            ref->u.ar.start[n]))
8792                 ref->u.ar.start[n]
8793                         = gfc_get_parentheses (ref->u.ar.start[n]);
8794           }
8795     }
8796
8797   if (gfc_pure (NULL))
8798     {
8799       if (lhs->ts.type == BT_DERIVED
8800             && lhs->expr_type == EXPR_VARIABLE
8801             && lhs->ts.u.derived->attr.pointer_comp
8802             && rhs->expr_type == EXPR_VARIABLE
8803             && (gfc_impure_variable (rhs->symtree->n.sym)
8804                 || gfc_is_coindexed (rhs)))
8805         {
8806           /* F2008, C1283.  */
8807           if (gfc_is_coindexed (rhs))
8808             gfc_error ("Coindexed expression at %L is assigned to "
8809                         "a derived type variable with a POINTER "
8810                         "component in a PURE procedure",
8811                         &rhs->where);
8812           else
8813             gfc_error ("The impure variable at %L is assigned to "
8814                         "a derived type variable with a POINTER "
8815                         "component in a PURE procedure (12.6)",
8816                         &rhs->where);
8817           return rval;
8818         }
8819
8820       /* Fortran 2008, C1283.  */
8821       if (gfc_is_coindexed (lhs))
8822         {
8823           gfc_error ("Assignment to coindexed variable at %L in a PURE "
8824                      "procedure", &rhs->where);
8825           return rval;
8826         }
8827     }
8828
8829   if (gfc_implicit_pure (NULL))
8830     {
8831       if (lhs->expr_type == EXPR_VARIABLE
8832             && lhs->symtree->n.sym != gfc_current_ns->proc_name
8833             && lhs->symtree->n.sym->ns != gfc_current_ns)
8834         gfc_current_ns->proc_name->attr.implicit_pure = 0;
8835
8836       if (lhs->ts.type == BT_DERIVED
8837             && lhs->expr_type == EXPR_VARIABLE
8838             && lhs->ts.u.derived->attr.pointer_comp
8839             && rhs->expr_type == EXPR_VARIABLE
8840             && (gfc_impure_variable (rhs->symtree->n.sym)
8841                 || gfc_is_coindexed (rhs)))
8842         gfc_current_ns->proc_name->attr.implicit_pure = 0;
8843
8844       /* Fortran 2008, C1283.  */
8845       if (gfc_is_coindexed (lhs))
8846         gfc_current_ns->proc_name->attr.implicit_pure = 0;
8847     }
8848
8849   /* F03:7.4.1.2.  */
8850   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
8851      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
8852   if (lhs->ts.type == BT_CLASS)
8853     {
8854       gfc_error ("Variable must not be polymorphic in assignment at %L",
8855                  &lhs->where);
8856       return false;
8857     }
8858
8859   /* F2008, Section 7.2.1.2.  */
8860   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
8861     {
8862       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
8863                  "component in assignment at %L", &lhs->where);
8864       return false;
8865     }
8866
8867   gfc_check_assign (lhs, rhs, 1);
8868   return false;
8869 }
8870
8871
8872 /* Given a block of code, recursively resolve everything pointed to by this
8873    code block.  */
8874
8875 static void
8876 resolve_code (gfc_code *code, gfc_namespace *ns)
8877 {
8878   int omp_workshare_save;
8879   int forall_save;
8880   code_stack frame;
8881   gfc_try t;
8882
8883   frame.prev = cs_base;
8884   frame.head = code;
8885   cs_base = &frame;
8886
8887   find_reachable_labels (code);
8888
8889   for (; code; code = code->next)
8890     {
8891       frame.current = code;
8892       forall_save = forall_flag;
8893
8894       if (code->op == EXEC_FORALL)
8895         {
8896           forall_flag = 1;
8897           gfc_resolve_forall (code, ns, forall_save);
8898           forall_flag = 2;
8899         }
8900       else if (code->block)
8901         {
8902           omp_workshare_save = -1;
8903           switch (code->op)
8904             {
8905             case EXEC_OMP_PARALLEL_WORKSHARE:
8906               omp_workshare_save = omp_workshare_flag;
8907               omp_workshare_flag = 1;
8908               gfc_resolve_omp_parallel_blocks (code, ns);
8909               break;
8910             case EXEC_OMP_PARALLEL:
8911             case EXEC_OMP_PARALLEL_DO:
8912             case EXEC_OMP_PARALLEL_SECTIONS:
8913             case EXEC_OMP_TASK:
8914               omp_workshare_save = omp_workshare_flag;
8915               omp_workshare_flag = 0;
8916               gfc_resolve_omp_parallel_blocks (code, ns);
8917               break;
8918             case EXEC_OMP_DO:
8919               gfc_resolve_omp_do_blocks (code, ns);
8920               break;
8921             case EXEC_SELECT_TYPE:
8922               /* Blocks are handled in resolve_select_type because we have
8923                  to transform the SELECT TYPE into ASSOCIATE first.  */
8924               break;
8925             case EXEC_OMP_WORKSHARE:
8926               omp_workshare_save = omp_workshare_flag;
8927               omp_workshare_flag = 1;
8928               /* FALLTHROUGH */
8929             default:
8930               gfc_resolve_blocks (code->block, ns);
8931               break;
8932             }
8933
8934           if (omp_workshare_save != -1)
8935             omp_workshare_flag = omp_workshare_save;
8936         }
8937
8938       t = SUCCESS;
8939       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
8940         t = gfc_resolve_expr (code->expr1);
8941       forall_flag = forall_save;
8942
8943       if (gfc_resolve_expr (code->expr2) == FAILURE)
8944         t = FAILURE;
8945
8946       if (code->op == EXEC_ALLOCATE
8947           && gfc_resolve_expr (code->expr3) == FAILURE)
8948         t = FAILURE;
8949
8950       switch (code->op)
8951         {
8952         case EXEC_NOP:
8953         case EXEC_END_BLOCK:
8954         case EXEC_CYCLE:
8955         case EXEC_PAUSE:
8956         case EXEC_STOP:
8957         case EXEC_ERROR_STOP:
8958         case EXEC_EXIT:
8959         case EXEC_CONTINUE:
8960         case EXEC_DT_END:
8961         case EXEC_ASSIGN_CALL:
8962         case EXEC_CRITICAL:
8963           break;
8964
8965         case EXEC_SYNC_ALL:
8966         case EXEC_SYNC_IMAGES:
8967         case EXEC_SYNC_MEMORY:
8968           resolve_sync (code);
8969           break;
8970
8971         case EXEC_ENTRY:
8972           /* Keep track of which entry we are up to.  */
8973           current_entry_id = code->ext.entry->id;
8974           break;
8975
8976         case EXEC_WHERE:
8977           resolve_where (code, NULL);
8978           break;
8979
8980         case EXEC_GOTO:
8981           if (code->expr1 != NULL)
8982             {
8983               if (code->expr1->ts.type != BT_INTEGER)
8984                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
8985                            "INTEGER variable", &code->expr1->where);
8986               else if (code->expr1->symtree->n.sym->attr.assign != 1)
8987                 gfc_error ("Variable '%s' has not been assigned a target "
8988                            "label at %L", code->expr1->symtree->n.sym->name,
8989                            &code->expr1->where);
8990             }
8991           else
8992             resolve_branch (code->label1, code);
8993           break;
8994
8995         case EXEC_RETURN:
8996           if (code->expr1 != NULL
8997                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
8998             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
8999                        "INTEGER return specifier", &code->expr1->where);
9000           break;
9001
9002         case EXEC_INIT_ASSIGN:
9003         case EXEC_END_PROCEDURE:
9004           break;
9005
9006         case EXEC_ASSIGN:
9007           if (t == FAILURE)
9008             break;
9009
9010           if (gfc_check_vardef_context (code->expr1, false, _("assignment"))
9011                 == FAILURE)
9012             break;
9013
9014           if (resolve_ordinary_assign (code, ns))
9015             {
9016               if (code->op == EXEC_COMPCALL)
9017                 goto compcall;
9018               else
9019                 goto call;
9020             }
9021           break;
9022
9023         case EXEC_LABEL_ASSIGN:
9024           if (code->label1->defined == ST_LABEL_UNKNOWN)
9025             gfc_error ("Label %d referenced at %L is never defined",
9026                        code->label1->value, &code->label1->where);
9027           if (t == SUCCESS
9028               && (code->expr1->expr_type != EXPR_VARIABLE
9029                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
9030                   || code->expr1->symtree->n.sym->ts.kind
9031                      != gfc_default_integer_kind
9032                   || code->expr1->symtree->n.sym->as != NULL))
9033             gfc_error ("ASSIGN statement at %L requires a scalar "
9034                        "default INTEGER variable", &code->expr1->where);
9035           break;
9036
9037         case EXEC_POINTER_ASSIGN:
9038           {
9039             gfc_expr* e;
9040
9041             if (t == FAILURE)
9042               break;
9043
9044             /* This is both a variable definition and pointer assignment
9045                context, so check both of them.  For rank remapping, a final
9046                array ref may be present on the LHS and fool gfc_expr_attr
9047                used in gfc_check_vardef_context.  Remove it.  */
9048             e = remove_last_array_ref (code->expr1);
9049             t = gfc_check_vardef_context (e, true, _("pointer assignment"));
9050             if (t == SUCCESS)
9051               t = gfc_check_vardef_context (e, false, _("pointer assignment"));
9052             gfc_free_expr (e);
9053             if (t == FAILURE)
9054               break;
9055
9056             gfc_check_pointer_assign (code->expr1, code->expr2);
9057             break;
9058           }
9059
9060         case EXEC_ARITHMETIC_IF:
9061           if (t == SUCCESS
9062               && code->expr1->ts.type != BT_INTEGER
9063               && code->expr1->ts.type != BT_REAL)
9064             gfc_error ("Arithmetic IF statement at %L requires a numeric "
9065                        "expression", &code->expr1->where);
9066
9067           resolve_branch (code->label1, code);
9068           resolve_branch (code->label2, code);
9069           resolve_branch (code->label3, code);
9070           break;
9071
9072         case EXEC_IF:
9073           if (t == SUCCESS && code->expr1 != NULL
9074               && (code->expr1->ts.type != BT_LOGICAL
9075                   || code->expr1->rank != 0))
9076             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9077                        &code->expr1->where);
9078           break;
9079
9080         case EXEC_CALL:
9081         call:
9082           resolve_call (code);
9083           break;
9084
9085         case EXEC_COMPCALL:
9086         compcall:
9087           resolve_typebound_subroutine (code);
9088           break;
9089
9090         case EXEC_CALL_PPC:
9091           resolve_ppc_call (code);
9092           break;
9093
9094         case EXEC_SELECT:
9095           /* Select is complicated. Also, a SELECT construct could be
9096              a transformed computed GOTO.  */
9097           resolve_select (code);
9098           break;
9099
9100         case EXEC_SELECT_TYPE:
9101           resolve_select_type (code, ns);
9102           break;
9103
9104         case EXEC_BLOCK:
9105           resolve_block_construct (code);
9106           break;
9107
9108         case EXEC_DO:
9109           if (code->ext.iterator != NULL)
9110             {
9111               gfc_iterator *iter = code->ext.iterator;
9112               if (gfc_resolve_iterator (iter, true) != FAILURE)
9113                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
9114             }
9115           break;
9116
9117         case EXEC_DO_WHILE:
9118           if (code->expr1 == NULL)
9119             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
9120           if (t == SUCCESS
9121               && (code->expr1->rank != 0
9122                   || code->expr1->ts.type != BT_LOGICAL))
9123             gfc_error ("Exit condition of DO WHILE loop at %L must be "
9124                        "a scalar LOGICAL expression", &code->expr1->where);
9125           break;
9126
9127         case EXEC_ALLOCATE:
9128           if (t == SUCCESS)
9129             resolve_allocate_deallocate (code, "ALLOCATE");
9130
9131           break;
9132
9133         case EXEC_DEALLOCATE:
9134           if (t == SUCCESS)
9135             resolve_allocate_deallocate (code, "DEALLOCATE");
9136
9137           break;
9138
9139         case EXEC_OPEN:
9140           if (gfc_resolve_open (code->ext.open) == FAILURE)
9141             break;
9142
9143           resolve_branch (code->ext.open->err, code);
9144           break;
9145
9146         case EXEC_CLOSE:
9147           if (gfc_resolve_close (code->ext.close) == FAILURE)
9148             break;
9149
9150           resolve_branch (code->ext.close->err, code);
9151           break;
9152
9153         case EXEC_BACKSPACE:
9154         case EXEC_ENDFILE:
9155         case EXEC_REWIND:
9156         case EXEC_FLUSH:
9157           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
9158             break;
9159
9160           resolve_branch (code->ext.filepos->err, code);
9161           break;
9162
9163         case EXEC_INQUIRE:
9164           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9165               break;
9166
9167           resolve_branch (code->ext.inquire->err, code);
9168           break;
9169
9170         case EXEC_IOLENGTH:
9171           gcc_assert (code->ext.inquire != NULL);
9172           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9173             break;
9174
9175           resolve_branch (code->ext.inquire->err, code);
9176           break;
9177
9178         case EXEC_WAIT:
9179           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
9180             break;
9181
9182           resolve_branch (code->ext.wait->err, code);
9183           resolve_branch (code->ext.wait->end, code);
9184           resolve_branch (code->ext.wait->eor, code);
9185           break;
9186
9187         case EXEC_READ:
9188         case EXEC_WRITE:
9189           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
9190             break;
9191
9192           resolve_branch (code->ext.dt->err, code);
9193           resolve_branch (code->ext.dt->end, code);
9194           resolve_branch (code->ext.dt->eor, code);
9195           break;
9196
9197         case EXEC_TRANSFER:
9198           resolve_transfer (code);
9199           break;
9200
9201         case EXEC_FORALL:
9202           resolve_forall_iterators (code->ext.forall_iterator);
9203
9204           if (code->expr1 != NULL
9205               && (code->expr1->ts.type != BT_LOGICAL || code->expr1->rank))
9206             gfc_error ("FORALL mask clause at %L requires a scalar LOGICAL "
9207                        "expression", &code->expr1->where);
9208           break;
9209
9210         case EXEC_OMP_ATOMIC:
9211         case EXEC_OMP_BARRIER:
9212         case EXEC_OMP_CRITICAL:
9213         case EXEC_OMP_FLUSH:
9214         case EXEC_OMP_DO:
9215         case EXEC_OMP_MASTER:
9216         case EXEC_OMP_ORDERED:
9217         case EXEC_OMP_SECTIONS:
9218         case EXEC_OMP_SINGLE:
9219         case EXEC_OMP_TASKWAIT:
9220         case EXEC_OMP_WORKSHARE:
9221           gfc_resolve_omp_directive (code, ns);
9222           break;
9223
9224         case EXEC_OMP_PARALLEL:
9225         case EXEC_OMP_PARALLEL_DO:
9226         case EXEC_OMP_PARALLEL_SECTIONS:
9227         case EXEC_OMP_PARALLEL_WORKSHARE:
9228         case EXEC_OMP_TASK:
9229           omp_workshare_save = omp_workshare_flag;
9230           omp_workshare_flag = 0;
9231           gfc_resolve_omp_directive (code, ns);
9232           omp_workshare_flag = omp_workshare_save;
9233           break;
9234
9235         default:
9236           gfc_internal_error ("resolve_code(): Bad statement code");
9237         }
9238     }
9239
9240   cs_base = frame.prev;
9241 }
9242
9243
9244 /* Resolve initial values and make sure they are compatible with
9245    the variable.  */
9246
9247 static void
9248 resolve_values (gfc_symbol *sym)
9249 {
9250   gfc_try t;
9251
9252   if (sym->value == NULL)
9253     return;
9254
9255   if (sym->value->expr_type == EXPR_STRUCTURE)
9256     t= resolve_structure_cons (sym->value, 1);
9257   else 
9258     t = gfc_resolve_expr (sym->value);
9259
9260   if (t == FAILURE)
9261     return;
9262
9263   gfc_check_assign_symbol (sym, sym->value);
9264 }
9265
9266
9267 /* Verify the binding labels for common blocks that are BIND(C).  The label
9268    for a BIND(C) common block must be identical in all scoping units in which
9269    the common block is declared.  Further, the binding label can not collide
9270    with any other global entity in the program.  */
9271
9272 static void
9273 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
9274 {
9275   if (comm_block_tree->n.common->is_bind_c == 1)
9276     {
9277       gfc_gsymbol *binding_label_gsym;
9278       gfc_gsymbol *comm_name_gsym;
9279
9280       /* See if a global symbol exists by the common block's name.  It may
9281          be NULL if the common block is use-associated.  */
9282       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
9283                                          comm_block_tree->n.common->name);
9284       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
9285         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
9286                    "with the global entity '%s' at %L",
9287                    comm_block_tree->n.common->binding_label,
9288                    comm_block_tree->n.common->name,
9289                    &(comm_block_tree->n.common->where),
9290                    comm_name_gsym->name, &(comm_name_gsym->where));
9291       else if (comm_name_gsym != NULL
9292                && strcmp (comm_name_gsym->name,
9293                           comm_block_tree->n.common->name) == 0)
9294         {
9295           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
9296              as expected.  */
9297           if (comm_name_gsym->binding_label == NULL)
9298             /* No binding label for common block stored yet; save this one.  */
9299             comm_name_gsym->binding_label =
9300               comm_block_tree->n.common->binding_label;
9301           else
9302             if (strcmp (comm_name_gsym->binding_label,
9303                         comm_block_tree->n.common->binding_label) != 0)
9304               {
9305                 /* Common block names match but binding labels do not.  */
9306                 gfc_error ("Binding label '%s' for common block '%s' at %L "
9307                            "does not match the binding label '%s' for common "
9308                            "block '%s' at %L",
9309                            comm_block_tree->n.common->binding_label,
9310                            comm_block_tree->n.common->name,
9311                            &(comm_block_tree->n.common->where),
9312                            comm_name_gsym->binding_label,
9313                            comm_name_gsym->name,
9314                            &(comm_name_gsym->where));
9315                 return;
9316               }
9317         }
9318
9319       /* There is no binding label (NAME="") so we have nothing further to
9320          check and nothing to add as a global symbol for the label.  */
9321       if (comm_block_tree->n.common->binding_label[0] == '\0' )
9322         return;
9323       
9324       binding_label_gsym =
9325         gfc_find_gsymbol (gfc_gsym_root,
9326                           comm_block_tree->n.common->binding_label);
9327       if (binding_label_gsym == NULL)
9328         {
9329           /* Need to make a global symbol for the binding label to prevent
9330              it from colliding with another.  */
9331           binding_label_gsym =
9332             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
9333           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
9334           binding_label_gsym->type = GSYM_COMMON;
9335         }
9336       else
9337         {
9338           /* If comm_name_gsym is NULL, the name common block is use
9339              associated and the name could be colliding.  */
9340           if (binding_label_gsym->type != GSYM_COMMON)
9341             gfc_error ("Binding label '%s' for common block '%s' at %L "
9342                        "collides with the global entity '%s' at %L",
9343                        comm_block_tree->n.common->binding_label,
9344                        comm_block_tree->n.common->name,
9345                        &(comm_block_tree->n.common->where),
9346                        binding_label_gsym->name,
9347                        &(binding_label_gsym->where));
9348           else if (comm_name_gsym != NULL
9349                    && (strcmp (binding_label_gsym->name,
9350                                comm_name_gsym->binding_label) != 0)
9351                    && (strcmp (binding_label_gsym->sym_name,
9352                                comm_name_gsym->name) != 0))
9353             gfc_error ("Binding label '%s' for common block '%s' at %L "
9354                        "collides with global entity '%s' at %L",
9355                        binding_label_gsym->name, binding_label_gsym->sym_name,
9356                        &(comm_block_tree->n.common->where),
9357                        comm_name_gsym->name, &(comm_name_gsym->where));
9358         }
9359     }
9360   
9361   return;
9362 }
9363
9364
9365 /* Verify any BIND(C) derived types in the namespace so we can report errors
9366    for them once, rather than for each variable declared of that type.  */
9367
9368 static void
9369 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
9370 {
9371   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
9372       && derived_sym->attr.is_bind_c == 1)
9373     verify_bind_c_derived_type (derived_sym);
9374   
9375   return;
9376 }
9377
9378
9379 /* Verify that any binding labels used in a given namespace do not collide 
9380    with the names or binding labels of any global symbols.  */
9381
9382 static void
9383 gfc_verify_binding_labels (gfc_symbol *sym)
9384 {
9385   int has_error = 0;
9386   
9387   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
9388       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
9389     {
9390       gfc_gsymbol *bind_c_sym;
9391
9392       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
9393       if (bind_c_sym != NULL 
9394           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
9395         {
9396           if (sym->attr.if_source == IFSRC_DECL 
9397               && (bind_c_sym->type != GSYM_SUBROUTINE 
9398                   && bind_c_sym->type != GSYM_FUNCTION) 
9399               && ((sym->attr.contained == 1 
9400                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
9401                   || (sym->attr.use_assoc == 1 
9402                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
9403             {
9404               /* Make sure global procedures don't collide with anything.  */
9405               gfc_error ("Binding label '%s' at %L collides with the global "
9406                          "entity '%s' at %L", sym->binding_label,
9407                          &(sym->declared_at), bind_c_sym->name,
9408                          &(bind_c_sym->where));
9409               has_error = 1;
9410             }
9411           else if (sym->attr.contained == 0 
9412                    && (sym->attr.if_source == IFSRC_IFBODY 
9413                        && sym->attr.flavor == FL_PROCEDURE) 
9414                    && (bind_c_sym->sym_name != NULL 
9415                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
9416             {
9417               /* Make sure procedures in interface bodies don't collide.  */
9418               gfc_error ("Binding label '%s' in interface body at %L collides "
9419                          "with the global entity '%s' at %L",
9420                          sym->binding_label,
9421                          &(sym->declared_at), bind_c_sym->name,
9422                          &(bind_c_sym->where));
9423               has_error = 1;
9424             }
9425           else if (sym->attr.contained == 0 
9426                    && sym->attr.if_source == IFSRC_UNKNOWN)
9427             if ((sym->attr.use_assoc && bind_c_sym->mod_name
9428                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
9429                 || sym->attr.use_assoc == 0)
9430               {
9431                 gfc_error ("Binding label '%s' at %L collides with global "
9432                            "entity '%s' at %L", sym->binding_label,
9433                            &(sym->declared_at), bind_c_sym->name,
9434                            &(bind_c_sym->where));
9435                 has_error = 1;
9436               }
9437
9438           if (has_error != 0)
9439             /* Clear the binding label to prevent checking multiple times.  */
9440             sym->binding_label[0] = '\0';
9441         }
9442       else if (bind_c_sym == NULL)
9443         {
9444           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
9445           bind_c_sym->where = sym->declared_at;
9446           bind_c_sym->sym_name = sym->name;
9447
9448           if (sym->attr.use_assoc == 1)
9449             bind_c_sym->mod_name = sym->module;
9450           else
9451             if (sym->ns->proc_name != NULL)
9452               bind_c_sym->mod_name = sym->ns->proc_name->name;
9453
9454           if (sym->attr.contained == 0)
9455             {
9456               if (sym->attr.subroutine)
9457                 bind_c_sym->type = GSYM_SUBROUTINE;
9458               else if (sym->attr.function)
9459                 bind_c_sym->type = GSYM_FUNCTION;
9460             }
9461         }
9462     }
9463   return;
9464 }
9465
9466
9467 /* Resolve an index expression.  */
9468
9469 static gfc_try
9470 resolve_index_expr (gfc_expr *e)
9471 {
9472   if (gfc_resolve_expr (e) == FAILURE)
9473     return FAILURE;
9474
9475   if (gfc_simplify_expr (e, 0) == FAILURE)
9476     return FAILURE;
9477
9478   if (gfc_specification_expr (e) == FAILURE)
9479     return FAILURE;
9480
9481   return SUCCESS;
9482 }
9483
9484
9485 /* Resolve a charlen structure.  */
9486
9487 static gfc_try
9488 resolve_charlen (gfc_charlen *cl)
9489 {
9490   int i, k;
9491
9492   if (cl->resolved)
9493     return SUCCESS;
9494
9495   cl->resolved = 1;
9496
9497   specification_expr = 1;
9498
9499   if (resolve_index_expr (cl->length) == FAILURE)
9500     {
9501       specification_expr = 0;
9502       return FAILURE;
9503     }
9504
9505   /* "If the character length parameter value evaluates to a negative
9506      value, the length of character entities declared is zero."  */
9507   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
9508     {
9509       if (gfc_option.warn_surprising)
9510         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
9511                          " the length has been set to zero",
9512                          &cl->length->where, i);
9513       gfc_replace_expr (cl->length,
9514                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
9515     }
9516
9517   /* Check that the character length is not too large.  */
9518   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
9519   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
9520       && cl->length->ts.type == BT_INTEGER
9521       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
9522     {
9523       gfc_error ("String length at %L is too large", &cl->length->where);
9524       return FAILURE;
9525     }
9526
9527   return SUCCESS;
9528 }
9529
9530
9531 /* Test for non-constant shape arrays.  */
9532
9533 static bool
9534 is_non_constant_shape_array (gfc_symbol *sym)
9535 {
9536   gfc_expr *e;
9537   int i;
9538   bool not_constant;
9539
9540   not_constant = false;
9541   if (sym->as != NULL)
9542     {
9543       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
9544          has not been simplified; parameter array references.  Do the
9545          simplification now.  */
9546       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
9547         {
9548           e = sym->as->lower[i];
9549           if (e && (resolve_index_expr (e) == FAILURE
9550                     || !gfc_is_constant_expr (e)))
9551             not_constant = true;
9552           e = sym->as->upper[i];
9553           if (e && (resolve_index_expr (e) == FAILURE
9554                     || !gfc_is_constant_expr (e)))
9555             not_constant = true;
9556         }
9557     }
9558   return not_constant;
9559 }
9560
9561 /* Given a symbol and an initialization expression, add code to initialize
9562    the symbol to the function entry.  */
9563 static void
9564 build_init_assign (gfc_symbol *sym, gfc_expr *init)
9565 {
9566   gfc_expr *lval;
9567   gfc_code *init_st;
9568   gfc_namespace *ns = sym->ns;
9569
9570   /* Search for the function namespace if this is a contained
9571      function without an explicit result.  */
9572   if (sym->attr.function && sym == sym->result
9573       && sym->name != sym->ns->proc_name->name)
9574     {
9575       ns = ns->contained;
9576       for (;ns; ns = ns->sibling)
9577         if (strcmp (ns->proc_name->name, sym->name) == 0)
9578           break;
9579     }
9580
9581   if (ns == NULL)
9582     {
9583       gfc_free_expr (init);
9584       return;
9585     }
9586
9587   /* Build an l-value expression for the result.  */
9588   lval = gfc_lval_expr_from_sym (sym);
9589
9590   /* Add the code at scope entry.  */
9591   init_st = gfc_get_code ();
9592   init_st->next = ns->code;
9593   ns->code = init_st;
9594
9595   /* Assign the default initializer to the l-value.  */
9596   init_st->loc = sym->declared_at;
9597   init_st->op = EXEC_INIT_ASSIGN;
9598   init_st->expr1 = lval;
9599   init_st->expr2 = init;
9600 }
9601
9602 /* Assign the default initializer to a derived type variable or result.  */
9603
9604 static void
9605 apply_default_init (gfc_symbol *sym)
9606 {
9607   gfc_expr *init = NULL;
9608
9609   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9610     return;
9611
9612   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
9613     init = gfc_default_initializer (&sym->ts);
9614
9615   if (init == NULL && sym->ts.type != BT_CLASS)
9616     return;
9617
9618   build_init_assign (sym, init);
9619   sym->attr.referenced = 1;
9620 }
9621
9622 /* Build an initializer for a local integer, real, complex, logical, or
9623    character variable, based on the command line flags finit-local-zero,
9624    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
9625    null if the symbol should not have a default initialization.  */
9626 static gfc_expr *
9627 build_default_init_expr (gfc_symbol *sym)
9628 {
9629   int char_len;
9630   gfc_expr *init_expr;
9631   int i;
9632
9633   /* These symbols should never have a default initialization.  */
9634   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
9635       || sym->attr.external
9636       || sym->attr.dummy
9637       || sym->attr.pointer
9638       || sym->attr.in_equivalence
9639       || sym->attr.in_common
9640       || sym->attr.data
9641       || sym->module
9642       || sym->attr.cray_pointee
9643       || sym->attr.cray_pointer)
9644     return NULL;
9645
9646   /* Now we'll try to build an initializer expression.  */
9647   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
9648                                      &sym->declared_at);
9649
9650   /* We will only initialize integers, reals, complex, logicals, and
9651      characters, and only if the corresponding command-line flags
9652      were set.  Otherwise, we free init_expr and return null.  */
9653   switch (sym->ts.type)
9654     {    
9655     case BT_INTEGER:
9656       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
9657         mpz_set_si (init_expr->value.integer, 
9658                          gfc_option.flag_init_integer_value);
9659       else
9660         {
9661           gfc_free_expr (init_expr);
9662           init_expr = NULL;
9663         }
9664       break;
9665
9666     case BT_REAL:
9667       switch (gfc_option.flag_init_real)
9668         {
9669         case GFC_INIT_REAL_SNAN:
9670           init_expr->is_snan = 1;
9671           /* Fall through.  */
9672         case GFC_INIT_REAL_NAN:
9673           mpfr_set_nan (init_expr->value.real);
9674           break;
9675
9676         case GFC_INIT_REAL_INF:
9677           mpfr_set_inf (init_expr->value.real, 1);
9678           break;
9679
9680         case GFC_INIT_REAL_NEG_INF:
9681           mpfr_set_inf (init_expr->value.real, -1);
9682           break;
9683
9684         case GFC_INIT_REAL_ZERO:
9685           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
9686           break;
9687
9688         default:
9689           gfc_free_expr (init_expr);
9690           init_expr = NULL;
9691           break;
9692         }
9693       break;
9694           
9695     case BT_COMPLEX:
9696       switch (gfc_option.flag_init_real)
9697         {
9698         case GFC_INIT_REAL_SNAN:
9699           init_expr->is_snan = 1;
9700           /* Fall through.  */
9701         case GFC_INIT_REAL_NAN:
9702           mpfr_set_nan (mpc_realref (init_expr->value.complex));
9703           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
9704           break;
9705
9706         case GFC_INIT_REAL_INF:
9707           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
9708           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
9709           break;
9710
9711         case GFC_INIT_REAL_NEG_INF:
9712           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
9713           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
9714           break;
9715
9716         case GFC_INIT_REAL_ZERO:
9717           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
9718           break;
9719
9720         default:
9721           gfc_free_expr (init_expr);
9722           init_expr = NULL;
9723           break;
9724         }
9725       break;
9726           
9727     case BT_LOGICAL:
9728       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
9729         init_expr->value.logical = 0;
9730       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
9731         init_expr->value.logical = 1;
9732       else
9733         {
9734           gfc_free_expr (init_expr);
9735           init_expr = NULL;
9736         }
9737       break;
9738           
9739     case BT_CHARACTER:
9740       /* For characters, the length must be constant in order to 
9741          create a default initializer.  */
9742       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
9743           && sym->ts.u.cl->length
9744           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9745         {
9746           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
9747           init_expr->value.character.length = char_len;
9748           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
9749           for (i = 0; i < char_len; i++)
9750             init_expr->value.character.string[i]
9751               = (unsigned char) gfc_option.flag_init_character_value;
9752         }
9753       else
9754         {
9755           gfc_free_expr (init_expr);
9756           init_expr = NULL;
9757         }
9758       break;
9759           
9760     default:
9761      gfc_free_expr (init_expr);
9762      init_expr = NULL;
9763     }
9764   return init_expr;
9765 }
9766
9767 /* Add an initialization expression to a local variable.  */
9768 static void
9769 apply_default_init_local (gfc_symbol *sym)
9770 {
9771   gfc_expr *init = NULL;
9772
9773   /* The symbol should be a variable or a function return value.  */
9774   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9775       || (sym->attr.function && sym->result != sym))
9776     return;
9777
9778   /* Try to build the initializer expression.  If we can't initialize
9779      this symbol, then init will be NULL.  */
9780   init = build_default_init_expr (sym);
9781   if (init == NULL)
9782     return;
9783
9784   /* For saved variables, we don't want to add an initializer at 
9785      function entry, so we just add a static initializer.  */
9786   if (sym->attr.save || sym->ns->save_all 
9787       || gfc_option.flag_max_stack_var_size == 0)
9788     {
9789       /* Don't clobber an existing initializer!  */
9790       gcc_assert (sym->value == NULL);
9791       sym->value = init;
9792       return;
9793     }
9794
9795   build_init_assign (sym, init);
9796 }
9797
9798
9799 /* Resolution of common features of flavors variable and procedure.  */
9800
9801 static gfc_try
9802 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
9803 {
9804   /* Constraints on deferred shape variable.  */
9805   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
9806     {
9807       if (sym->attr.allocatable)
9808         {
9809           if (sym->attr.dimension)
9810             {
9811               gfc_error ("Allocatable array '%s' at %L must have "
9812                          "a deferred shape", sym->name, &sym->declared_at);
9813               return FAILURE;
9814             }
9815           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
9816                                    "may not be ALLOCATABLE", sym->name,
9817                                    &sym->declared_at) == FAILURE)
9818             return FAILURE;
9819         }
9820
9821       if (sym->attr.pointer && sym->attr.dimension)
9822         {
9823           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
9824                      sym->name, &sym->declared_at);
9825           return FAILURE;
9826         }
9827     }
9828   else
9829     {
9830       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
9831           && !sym->attr.dummy && sym->ts.type != BT_CLASS && !sym->assoc)
9832         {
9833           gfc_error ("Array '%s' at %L cannot have a deferred shape",
9834                      sym->name, &sym->declared_at);
9835           return FAILURE;
9836          }
9837     }
9838
9839   /* Constraints on polymorphic variables.  */
9840   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
9841     {
9842       /* F03:C502.  */
9843       if (sym->attr.class_ok
9844           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
9845         {
9846           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
9847                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
9848                      &sym->declared_at);
9849           return FAILURE;
9850         }
9851
9852       /* F03:C509.  */
9853       /* Assume that use associated symbols were checked in the module ns.
9854          Class-variables that are associate-names are also something special
9855          and excepted from the test.  */
9856       if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
9857         {
9858           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
9859                      "or pointer", sym->name, &sym->declared_at);
9860           return FAILURE;
9861         }
9862     }
9863     
9864   return SUCCESS;
9865 }
9866
9867
9868 /* Additional checks for symbols with flavor variable and derived
9869    type.  To be called from resolve_fl_variable.  */
9870
9871 static gfc_try
9872 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
9873 {
9874   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
9875
9876   /* Check to see if a derived type is blocked from being host
9877      associated by the presence of another class I symbol in the same
9878      namespace.  14.6.1.3 of the standard and the discussion on
9879      comp.lang.fortran.  */
9880   if (sym->ns != sym->ts.u.derived->ns
9881       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
9882     {
9883       gfc_symbol *s;
9884       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
9885       if (s && s->attr.flavor != FL_DERIVED)
9886         {
9887           gfc_error ("The type '%s' cannot be host associated at %L "
9888                      "because it is blocked by an incompatible object "
9889                      "of the same name declared at %L",
9890                      sym->ts.u.derived->name, &sym->declared_at,
9891                      &s->declared_at);
9892           return FAILURE;
9893         }
9894     }
9895
9896   /* 4th constraint in section 11.3: "If an object of a type for which
9897      component-initialization is specified (R429) appears in the
9898      specification-part of a module and does not have the ALLOCATABLE
9899      or POINTER attribute, the object shall have the SAVE attribute."
9900
9901      The check for initializers is performed with
9902      gfc_has_default_initializer because gfc_default_initializer generates
9903      a hidden default for allocatable components.  */
9904   if (!(sym->value || no_init_flag) && sym->ns->proc_name
9905       && sym->ns->proc_name->attr.flavor == FL_MODULE
9906       && !sym->ns->save_all && !sym->attr.save
9907       && !sym->attr.pointer && !sym->attr.allocatable
9908       && gfc_has_default_initializer (sym->ts.u.derived)
9909       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
9910                          "module variable '%s' at %L, needed due to "
9911                          "the default initialization", sym->name,
9912                          &sym->declared_at) == FAILURE)
9913     return FAILURE;
9914
9915   /* Assign default initializer.  */
9916   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
9917       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
9918     {
9919       sym->value = gfc_default_initializer (&sym->ts);
9920     }
9921
9922   return SUCCESS;
9923 }
9924
9925
9926 /* Resolve symbols with flavor variable.  */
9927
9928 static gfc_try
9929 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
9930 {
9931   int no_init_flag, automatic_flag;
9932   gfc_expr *e;
9933   const char *auto_save_msg;
9934
9935   auto_save_msg = "Automatic object '%s' at %L cannot have the "
9936                   "SAVE attribute";
9937
9938   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
9939     return FAILURE;
9940
9941   /* Set this flag to check that variables are parameters of all entries.
9942      This check is effected by the call to gfc_resolve_expr through
9943      is_non_constant_shape_array.  */
9944   specification_expr = 1;
9945
9946   if (sym->ns->proc_name
9947       && (sym->ns->proc_name->attr.flavor == FL_MODULE
9948           || sym->ns->proc_name->attr.is_main_program)
9949       && !sym->attr.use_assoc
9950       && !sym->attr.allocatable
9951       && !sym->attr.pointer
9952       && is_non_constant_shape_array (sym))
9953     {
9954       /* The shape of a main program or module array needs to be
9955          constant.  */
9956       gfc_error ("The module or main program array '%s' at %L must "
9957                  "have constant shape", sym->name, &sym->declared_at);
9958       specification_expr = 0;
9959       return FAILURE;
9960     }
9961
9962   /* Constraints on deferred type parameter.  */
9963   if (sym->ts.deferred && !(sym->attr.pointer || sym->attr.allocatable))
9964     {
9965       gfc_error ("Entity '%s' at %L has a deferred type parameter and "
9966                  "requires either the pointer or allocatable attribute",
9967                      sym->name, &sym->declared_at);
9968       return FAILURE;
9969     }
9970
9971   if (sym->ts.type == BT_CHARACTER)
9972     {
9973       /* Make sure that character string variables with assumed length are
9974          dummy arguments.  */
9975       e = sym->ts.u.cl->length;
9976       if (e == NULL && !sym->attr.dummy && !sym->attr.result
9977           && !sym->ts.deferred)
9978         {
9979           gfc_error ("Entity with assumed character length at %L must be a "
9980                      "dummy argument or a PARAMETER", &sym->declared_at);
9981           return FAILURE;
9982         }
9983
9984       if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
9985         {
9986           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
9987           return FAILURE;
9988         }
9989
9990       if (!gfc_is_constant_expr (e)
9991           && !(e->expr_type == EXPR_VARIABLE
9992                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
9993           && sym->ns->proc_name
9994           && (sym->ns->proc_name->attr.flavor == FL_MODULE
9995               || sym->ns->proc_name->attr.is_main_program)
9996           && !sym->attr.use_assoc)
9997         {
9998           gfc_error ("'%s' at %L must have constant character length "
9999                      "in this context", sym->name, &sym->declared_at);
10000           return FAILURE;
10001         }
10002     }
10003
10004   if (sym->value == NULL && sym->attr.referenced)
10005     apply_default_init_local (sym); /* Try to apply a default initialization.  */
10006
10007   /* Determine if the symbol may not have an initializer.  */
10008   no_init_flag = automatic_flag = 0;
10009   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
10010       || sym->attr.intrinsic || sym->attr.result)
10011     no_init_flag = 1;
10012   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
10013            && is_non_constant_shape_array (sym))
10014     {
10015       no_init_flag = automatic_flag = 1;
10016
10017       /* Also, they must not have the SAVE attribute.
10018          SAVE_IMPLICIT is checked below.  */
10019       if (sym->attr.save == SAVE_EXPLICIT)
10020         {
10021           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10022           return FAILURE;
10023         }
10024     }
10025
10026   /* Ensure that any initializer is simplified.  */
10027   if (sym->value)
10028     gfc_simplify_expr (sym->value, 1);
10029
10030   /* Reject illegal initializers.  */
10031   if (!sym->mark && sym->value)
10032     {
10033       if (sym->attr.allocatable)
10034         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
10035                    sym->name, &sym->declared_at);
10036       else if (sym->attr.external)
10037         gfc_error ("External '%s' at %L cannot have an initializer",
10038                    sym->name, &sym->declared_at);
10039       else if (sym->attr.dummy
10040         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
10041         gfc_error ("Dummy '%s' at %L cannot have an initializer",
10042                    sym->name, &sym->declared_at);
10043       else if (sym->attr.intrinsic)
10044         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
10045                    sym->name, &sym->declared_at);
10046       else if (sym->attr.result)
10047         gfc_error ("Function result '%s' at %L cannot have an initializer",
10048                    sym->name, &sym->declared_at);
10049       else if (automatic_flag)
10050         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
10051                    sym->name, &sym->declared_at);
10052       else
10053         goto no_init_error;
10054       return FAILURE;
10055     }
10056
10057 no_init_error:
10058   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
10059     return resolve_fl_variable_derived (sym, no_init_flag);
10060
10061   return SUCCESS;
10062 }
10063
10064
10065 /* Resolve a procedure.  */
10066
10067 static gfc_try
10068 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
10069 {
10070   gfc_formal_arglist *arg;
10071
10072   if (sym->attr.function
10073       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10074     return FAILURE;
10075
10076   if (sym->ts.type == BT_CHARACTER)
10077     {
10078       gfc_charlen *cl = sym->ts.u.cl;
10079
10080       if (cl && cl->length && gfc_is_constant_expr (cl->length)
10081              && resolve_charlen (cl) == FAILURE)
10082         return FAILURE;
10083
10084       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
10085           && sym->attr.proc == PROC_ST_FUNCTION)
10086         {
10087           gfc_error ("Character-valued statement function '%s' at %L must "
10088                      "have constant length", sym->name, &sym->declared_at);
10089           return FAILURE;
10090         }
10091     }
10092
10093   /* Ensure that derived type for are not of a private type.  Internal
10094      module procedures are excluded by 2.2.3.3 - i.e., they are not
10095      externally accessible and can access all the objects accessible in
10096      the host.  */
10097   if (!(sym->ns->parent
10098         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
10099       && gfc_check_access(sym->attr.access, sym->ns->default_access))
10100     {
10101       gfc_interface *iface;
10102
10103       for (arg = sym->formal; arg; arg = arg->next)
10104         {
10105           if (arg->sym
10106               && arg->sym->ts.type == BT_DERIVED
10107               && !arg->sym->ts.u.derived->attr.use_assoc
10108               && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
10109                                     arg->sym->ts.u.derived->ns->default_access)
10110               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
10111                                  "PRIVATE type and cannot be a dummy argument"
10112                                  " of '%s', which is PUBLIC at %L",
10113                                  arg->sym->name, sym->name, &sym->declared_at)
10114                  == FAILURE)
10115             {
10116               /* Stop this message from recurring.  */
10117               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10118               return FAILURE;
10119             }
10120         }
10121
10122       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10123          PRIVATE to the containing module.  */
10124       for (iface = sym->generic; iface; iface = iface->next)
10125         {
10126           for (arg = iface->sym->formal; arg; arg = arg->next)
10127             {
10128               if (arg->sym
10129                   && arg->sym->ts.type == BT_DERIVED
10130                   && !arg->sym->ts.u.derived->attr.use_assoc
10131                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
10132                                         arg->sym->ts.u.derived->ns->default_access)
10133                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10134                                      "'%s' in PUBLIC interface '%s' at %L "
10135                                      "takes dummy arguments of '%s' which is "
10136                                      "PRIVATE", iface->sym->name, sym->name,
10137                                      &iface->sym->declared_at,
10138                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10139                 {
10140                   /* Stop this message from recurring.  */
10141                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10142                   return FAILURE;
10143                 }
10144              }
10145         }
10146
10147       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10148          PRIVATE to the containing module.  */
10149       for (iface = sym->generic; iface; iface = iface->next)
10150         {
10151           for (arg = iface->sym->formal; arg; arg = arg->next)
10152             {
10153               if (arg->sym
10154                   && arg->sym->ts.type == BT_DERIVED
10155                   && !arg->sym->ts.u.derived->attr.use_assoc
10156                   && !gfc_check_access (arg->sym->ts.u.derived->attr.access,
10157                                         arg->sym->ts.u.derived->ns->default_access)
10158                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10159                                      "'%s' in PUBLIC interface '%s' at %L "
10160                                      "takes dummy arguments of '%s' which is "
10161                                      "PRIVATE", iface->sym->name, sym->name,
10162                                      &iface->sym->declared_at,
10163                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10164                 {
10165                   /* Stop this message from recurring.  */
10166                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10167                   return FAILURE;
10168                 }
10169              }
10170         }
10171     }
10172
10173   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
10174       && !sym->attr.proc_pointer)
10175     {
10176       gfc_error ("Function '%s' at %L cannot have an initializer",
10177                  sym->name, &sym->declared_at);
10178       return FAILURE;
10179     }
10180
10181   /* An external symbol may not have an initializer because it is taken to be
10182      a procedure. Exception: Procedure Pointers.  */
10183   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
10184     {
10185       gfc_error ("External object '%s' at %L may not have an initializer",
10186                  sym->name, &sym->declared_at);
10187       return FAILURE;
10188     }
10189
10190   /* An elemental function is required to return a scalar 12.7.1  */
10191   if (sym->attr.elemental && sym->attr.function && sym->as)
10192     {
10193       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
10194                  "result", sym->name, &sym->declared_at);
10195       /* Reset so that the error only occurs once.  */
10196       sym->attr.elemental = 0;
10197       return FAILURE;
10198     }
10199
10200   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
10201      char-len-param shall not be array-valued, pointer-valued, recursive
10202      or pure.  ....snip... A character value of * may only be used in the
10203      following ways: (i) Dummy arg of procedure - dummy associates with
10204      actual length; (ii) To declare a named constant; or (iii) External
10205      function - but length must be declared in calling scoping unit.  */
10206   if (sym->attr.function
10207       && sym->ts.type == BT_CHARACTER
10208       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
10209     {
10210       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
10211           || (sym->attr.recursive) || (sym->attr.pure))
10212         {
10213           if (sym->as && sym->as->rank)
10214             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10215                        "array-valued", sym->name, &sym->declared_at);
10216
10217           if (sym->attr.pointer)
10218             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10219                        "pointer-valued", sym->name, &sym->declared_at);
10220
10221           if (sym->attr.pure)
10222             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10223                        "pure", sym->name, &sym->declared_at);
10224
10225           if (sym->attr.recursive)
10226             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10227                        "recursive", sym->name, &sym->declared_at);
10228
10229           return FAILURE;
10230         }
10231
10232       /* Appendix B.2 of the standard.  Contained functions give an
10233          error anyway.  Fixed-form is likely to be F77/legacy.  */
10234       if (!sym->attr.contained && gfc_current_form != FORM_FIXED)
10235         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
10236                         "CHARACTER(*) function '%s' at %L",
10237                         sym->name, &sym->declared_at);
10238     }
10239
10240   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
10241     {
10242       gfc_formal_arglist *curr_arg;
10243       int has_non_interop_arg = 0;
10244
10245       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10246                              sym->common_block) == FAILURE)
10247         {
10248           /* Clear these to prevent looking at them again if there was an
10249              error.  */
10250           sym->attr.is_bind_c = 0;
10251           sym->attr.is_c_interop = 0;
10252           sym->ts.is_c_interop = 0;
10253         }
10254       else
10255         {
10256           /* So far, no errors have been found.  */
10257           sym->attr.is_c_interop = 1;
10258           sym->ts.is_c_interop = 1;
10259         }
10260       
10261       curr_arg = sym->formal;
10262       while (curr_arg != NULL)
10263         {
10264           /* Skip implicitly typed dummy args here.  */
10265           if (curr_arg->sym->attr.implicit_type == 0)
10266             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
10267               /* If something is found to fail, record the fact so we
10268                  can mark the symbol for the procedure as not being
10269                  BIND(C) to try and prevent multiple errors being
10270                  reported.  */
10271               has_non_interop_arg = 1;
10272           
10273           curr_arg = curr_arg->next;
10274         }
10275
10276       /* See if any of the arguments were not interoperable and if so, clear
10277          the procedure symbol to prevent duplicate error messages.  */
10278       if (has_non_interop_arg != 0)
10279         {
10280           sym->attr.is_c_interop = 0;
10281           sym->ts.is_c_interop = 0;
10282           sym->attr.is_bind_c = 0;
10283         }
10284     }
10285   
10286   if (!sym->attr.proc_pointer)
10287     {
10288       if (sym->attr.save == SAVE_EXPLICIT)
10289         {
10290           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
10291                      "in '%s' at %L", sym->name, &sym->declared_at);
10292           return FAILURE;
10293         }
10294       if (sym->attr.intent)
10295         {
10296           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
10297                      "in '%s' at %L", sym->name, &sym->declared_at);
10298           return FAILURE;
10299         }
10300       if (sym->attr.subroutine && sym->attr.result)
10301         {
10302           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
10303                      "in '%s' at %L", sym->name, &sym->declared_at);
10304           return FAILURE;
10305         }
10306       if (sym->attr.external && sym->attr.function
10307           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
10308               || sym->attr.contained))
10309         {
10310           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
10311                      "in '%s' at %L", sym->name, &sym->declared_at);
10312           return FAILURE;
10313         }
10314       if (strcmp ("ppr@", sym->name) == 0)
10315         {
10316           gfc_error ("Procedure pointer result '%s' at %L "
10317                      "is missing the pointer attribute",
10318                      sym->ns->proc_name->name, &sym->declared_at);
10319           return FAILURE;
10320         }
10321     }
10322
10323   return SUCCESS;
10324 }
10325
10326
10327 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
10328    been defined and we now know their defined arguments, check that they fulfill
10329    the requirements of the standard for procedures used as finalizers.  */
10330
10331 static gfc_try
10332 gfc_resolve_finalizers (gfc_symbol* derived)
10333 {
10334   gfc_finalizer* list;
10335   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
10336   gfc_try result = SUCCESS;
10337   bool seen_scalar = false;
10338
10339   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
10340     return SUCCESS;
10341
10342   /* Walk over the list of finalizer-procedures, check them, and if any one
10343      does not fit in with the standard's definition, print an error and remove
10344      it from the list.  */
10345   prev_link = &derived->f2k_derived->finalizers;
10346   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
10347     {
10348       gfc_symbol* arg;
10349       gfc_finalizer* i;
10350       int my_rank;
10351
10352       /* Skip this finalizer if we already resolved it.  */
10353       if (list->proc_tree)
10354         {
10355           prev_link = &(list->next);
10356           continue;
10357         }
10358
10359       /* Check this exists and is a SUBROUTINE.  */
10360       if (!list->proc_sym->attr.subroutine)
10361         {
10362           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
10363                      list->proc_sym->name, &list->where);
10364           goto error;
10365         }
10366
10367       /* We should have exactly one argument.  */
10368       if (!list->proc_sym->formal || list->proc_sym->formal->next)
10369         {
10370           gfc_error ("FINAL procedure at %L must have exactly one argument",
10371                      &list->where);
10372           goto error;
10373         }
10374       arg = list->proc_sym->formal->sym;
10375
10376       /* This argument must be of our type.  */
10377       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
10378         {
10379           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
10380                      &arg->declared_at, derived->name);
10381           goto error;
10382         }
10383
10384       /* It must neither be a pointer nor allocatable nor optional.  */
10385       if (arg->attr.pointer)
10386         {
10387           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
10388                      &arg->declared_at);
10389           goto error;
10390         }
10391       if (arg->attr.allocatable)
10392         {
10393           gfc_error ("Argument of FINAL procedure at %L must not be"
10394                      " ALLOCATABLE", &arg->declared_at);
10395           goto error;
10396         }
10397       if (arg->attr.optional)
10398         {
10399           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
10400                      &arg->declared_at);
10401           goto error;
10402         }
10403
10404       /* It must not be INTENT(OUT).  */
10405       if (arg->attr.intent == INTENT_OUT)
10406         {
10407           gfc_error ("Argument of FINAL procedure at %L must not be"
10408                      " INTENT(OUT)", &arg->declared_at);
10409           goto error;
10410         }
10411
10412       /* Warn if the procedure is non-scalar and not assumed shape.  */
10413       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
10414           && arg->as->type != AS_ASSUMED_SHAPE)
10415         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
10416                      " shape argument", &arg->declared_at);
10417
10418       /* Check that it does not match in kind and rank with a FINAL procedure
10419          defined earlier.  To really loop over the *earlier* declarations,
10420          we need to walk the tail of the list as new ones were pushed at the
10421          front.  */
10422       /* TODO: Handle kind parameters once they are implemented.  */
10423       my_rank = (arg->as ? arg->as->rank : 0);
10424       for (i = list->next; i; i = i->next)
10425         {
10426           /* Argument list might be empty; that is an error signalled earlier,
10427              but we nevertheless continued resolving.  */
10428           if (i->proc_sym->formal)
10429             {
10430               gfc_symbol* i_arg = i->proc_sym->formal->sym;
10431               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
10432               if (i_rank == my_rank)
10433                 {
10434                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
10435                              " rank (%d) as '%s'",
10436                              list->proc_sym->name, &list->where, my_rank, 
10437                              i->proc_sym->name);
10438                   goto error;
10439                 }
10440             }
10441         }
10442
10443         /* Is this the/a scalar finalizer procedure?  */
10444         if (!arg->as || arg->as->rank == 0)
10445           seen_scalar = true;
10446
10447         /* Find the symtree for this procedure.  */
10448         gcc_assert (!list->proc_tree);
10449         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
10450
10451         prev_link = &list->next;
10452         continue;
10453
10454         /* Remove wrong nodes immediately from the list so we don't risk any
10455            troubles in the future when they might fail later expectations.  */
10456 error:
10457         result = FAILURE;
10458         i = list;
10459         *prev_link = list->next;
10460         gfc_free_finalizer (i);
10461     }
10462
10463   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
10464      were nodes in the list, must have been for arrays.  It is surely a good
10465      idea to have a scalar version there if there's something to finalize.  */
10466   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
10467     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
10468                  " defined at %L, suggest also scalar one",
10469                  derived->name, &derived->declared_at);
10470
10471   /* TODO:  Remove this error when finalization is finished.  */
10472   gfc_error ("Finalization at %L is not yet implemented",
10473              &derived->declared_at);
10474
10475   return result;
10476 }
10477
10478
10479 /* Check that it is ok for the typebound procedure proc to override the
10480    procedure old.  */
10481
10482 static gfc_try
10483 check_typebound_override (gfc_symtree* proc, gfc_symtree* old)
10484 {
10485   locus where;
10486   const gfc_symbol* proc_target;
10487   const gfc_symbol* old_target;
10488   unsigned proc_pass_arg, old_pass_arg, argpos;
10489   gfc_formal_arglist* proc_formal;
10490   gfc_formal_arglist* old_formal;
10491
10492   /* This procedure should only be called for non-GENERIC proc.  */
10493   gcc_assert (!proc->n.tb->is_generic);
10494
10495   /* If the overwritten procedure is GENERIC, this is an error.  */
10496   if (old->n.tb->is_generic)
10497     {
10498       gfc_error ("Can't overwrite GENERIC '%s' at %L",
10499                  old->name, &proc->n.tb->where);
10500       return FAILURE;
10501     }
10502
10503   where = proc->n.tb->where;
10504   proc_target = proc->n.tb->u.specific->n.sym;
10505   old_target = old->n.tb->u.specific->n.sym;
10506
10507   /* Check that overridden binding is not NON_OVERRIDABLE.  */
10508   if (old->n.tb->non_overridable)
10509     {
10510       gfc_error ("'%s' at %L overrides a procedure binding declared"
10511                  " NON_OVERRIDABLE", proc->name, &where);
10512       return FAILURE;
10513     }
10514
10515   /* It's an error to override a non-DEFERRED procedure with a DEFERRED one.  */
10516   if (!old->n.tb->deferred && proc->n.tb->deferred)
10517     {
10518       gfc_error ("'%s' at %L must not be DEFERRED as it overrides a"
10519                  " non-DEFERRED binding", proc->name, &where);
10520       return FAILURE;
10521     }
10522
10523   /* If the overridden binding is PURE, the overriding must be, too.  */
10524   if (old_target->attr.pure && !proc_target->attr.pure)
10525     {
10526       gfc_error ("'%s' at %L overrides a PURE procedure and must also be PURE",
10527                  proc->name, &where);
10528       return FAILURE;
10529     }
10530
10531   /* If the overridden binding is ELEMENTAL, the overriding must be, too.  If it
10532      is not, the overriding must not be either.  */
10533   if (old_target->attr.elemental && !proc_target->attr.elemental)
10534     {
10535       gfc_error ("'%s' at %L overrides an ELEMENTAL procedure and must also be"
10536                  " ELEMENTAL", proc->name, &where);
10537       return FAILURE;
10538     }
10539   if (!old_target->attr.elemental && proc_target->attr.elemental)
10540     {
10541       gfc_error ("'%s' at %L overrides a non-ELEMENTAL procedure and must not"
10542                  " be ELEMENTAL, either", proc->name, &where);
10543       return FAILURE;
10544     }
10545
10546   /* If the overridden binding is a SUBROUTINE, the overriding must also be a
10547      SUBROUTINE.  */
10548   if (old_target->attr.subroutine && !proc_target->attr.subroutine)
10549     {
10550       gfc_error ("'%s' at %L overrides a SUBROUTINE and must also be a"
10551                  " SUBROUTINE", proc->name, &where);
10552       return FAILURE;
10553     }
10554
10555   /* If the overridden binding is a FUNCTION, the overriding must also be a
10556      FUNCTION and have the same characteristics.  */
10557   if (old_target->attr.function)
10558     {
10559       if (!proc_target->attr.function)
10560         {
10561           gfc_error ("'%s' at %L overrides a FUNCTION and must also be a"
10562                      " FUNCTION", proc->name, &where);
10563           return FAILURE;
10564         }
10565
10566       /* FIXME:  Do more comprehensive checking (including, for instance, the
10567          rank and array-shape).  */
10568       gcc_assert (proc_target->result && old_target->result);
10569       if (!gfc_compare_types (&proc_target->result->ts,
10570                               &old_target->result->ts))
10571         {
10572           gfc_error ("'%s' at %L and the overridden FUNCTION should have"
10573                      " matching result types", proc->name, &where);
10574           return FAILURE;
10575         }
10576     }
10577
10578   /* If the overridden binding is PUBLIC, the overriding one must not be
10579      PRIVATE.  */
10580   if (old->n.tb->access == ACCESS_PUBLIC
10581       && proc->n.tb->access == ACCESS_PRIVATE)
10582     {
10583       gfc_error ("'%s' at %L overrides a PUBLIC procedure and must not be"
10584                  " PRIVATE", proc->name, &where);
10585       return FAILURE;
10586     }
10587
10588   /* Compare the formal argument lists of both procedures.  This is also abused
10589      to find the position of the passed-object dummy arguments of both
10590      bindings as at least the overridden one might not yet be resolved and we
10591      need those positions in the check below.  */
10592   proc_pass_arg = old_pass_arg = 0;
10593   if (!proc->n.tb->nopass && !proc->n.tb->pass_arg)
10594     proc_pass_arg = 1;
10595   if (!old->n.tb->nopass && !old->n.tb->pass_arg)
10596     old_pass_arg = 1;
10597   argpos = 1;
10598   for (proc_formal = proc_target->formal, old_formal = old_target->formal;
10599        proc_formal && old_formal;
10600        proc_formal = proc_formal->next, old_formal = old_formal->next)
10601     {
10602       if (proc->n.tb->pass_arg
10603           && !strcmp (proc->n.tb->pass_arg, proc_formal->sym->name))
10604         proc_pass_arg = argpos;
10605       if (old->n.tb->pass_arg
10606           && !strcmp (old->n.tb->pass_arg, old_formal->sym->name))
10607         old_pass_arg = argpos;
10608
10609       /* Check that the names correspond.  */
10610       if (strcmp (proc_formal->sym->name, old_formal->sym->name))
10611         {
10612           gfc_error ("Dummy argument '%s' of '%s' at %L should be named '%s' as"
10613                      " to match the corresponding argument of the overridden"
10614                      " procedure", proc_formal->sym->name, proc->name, &where,
10615                      old_formal->sym->name);
10616           return FAILURE;
10617         }
10618
10619       /* Check that the types correspond if neither is the passed-object
10620          argument.  */
10621       /* FIXME:  Do more comprehensive testing here.  */
10622       if (proc_pass_arg != argpos && old_pass_arg != argpos
10623           && !gfc_compare_types (&proc_formal->sym->ts, &old_formal->sym->ts))
10624         {
10625           gfc_error ("Types mismatch for dummy argument '%s' of '%s' %L "
10626                      "in respect to the overridden procedure",
10627                      proc_formal->sym->name, proc->name, &where);
10628           return FAILURE;
10629         }
10630
10631       ++argpos;
10632     }
10633   if (proc_formal || old_formal)
10634     {
10635       gfc_error ("'%s' at %L must have the same number of formal arguments as"
10636                  " the overridden procedure", proc->name, &where);
10637       return FAILURE;
10638     }
10639
10640   /* If the overridden binding is NOPASS, the overriding one must also be
10641      NOPASS.  */
10642   if (old->n.tb->nopass && !proc->n.tb->nopass)
10643     {
10644       gfc_error ("'%s' at %L overrides a NOPASS binding and must also be"
10645                  " NOPASS", proc->name, &where);
10646       return FAILURE;
10647     }
10648
10649   /* If the overridden binding is PASS(x), the overriding one must also be
10650      PASS and the passed-object dummy arguments must correspond.  */
10651   if (!old->n.tb->nopass)
10652     {
10653       if (proc->n.tb->nopass)
10654         {
10655           gfc_error ("'%s' at %L overrides a binding with PASS and must also be"
10656                      " PASS", proc->name, &where);
10657           return FAILURE;
10658         }
10659
10660       if (proc_pass_arg != old_pass_arg)
10661         {
10662           gfc_error ("Passed-object dummy argument of '%s' at %L must be at"
10663                      " the same position as the passed-object dummy argument of"
10664                      " the overridden procedure", proc->name, &where);
10665           return FAILURE;
10666         }
10667     }
10668
10669   return SUCCESS;
10670 }
10671
10672
10673 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10674
10675 static gfc_try
10676 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10677                              const char* generic_name, locus where)
10678 {
10679   gfc_symbol* sym1;
10680   gfc_symbol* sym2;
10681
10682   gcc_assert (t1->specific && t2->specific);
10683   gcc_assert (!t1->specific->is_generic);
10684   gcc_assert (!t2->specific->is_generic);
10685
10686   sym1 = t1->specific->u.specific->n.sym;
10687   sym2 = t2->specific->u.specific->n.sym;
10688
10689   if (sym1 == sym2)
10690     return SUCCESS;
10691
10692   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10693   if (sym1->attr.subroutine != sym2->attr.subroutine
10694       || sym1->attr.function != sym2->attr.function)
10695     {
10696       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10697                  " GENERIC '%s' at %L",
10698                  sym1->name, sym2->name, generic_name, &where);
10699       return FAILURE;
10700     }
10701
10702   /* Compare the interfaces.  */
10703   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10704     {
10705       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10706                  sym1->name, sym2->name, generic_name, &where);
10707       return FAILURE;
10708     }
10709
10710   return SUCCESS;
10711 }
10712
10713
10714 /* Worker function for resolving a generic procedure binding; this is used to
10715    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10716
10717    The difference between those cases is finding possible inherited bindings
10718    that are overridden, as one has to look for them in tb_sym_root,
10719    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10720    the super-type and set p->overridden correctly.  */
10721
10722 static gfc_try
10723 resolve_tb_generic_targets (gfc_symbol* super_type,
10724                             gfc_typebound_proc* p, const char* name)
10725 {
10726   gfc_tbp_generic* target;
10727   gfc_symtree* first_target;
10728   gfc_symtree* inherited;
10729
10730   gcc_assert (p && p->is_generic);
10731
10732   /* Try to find the specific bindings for the symtrees in our target-list.  */
10733   gcc_assert (p->u.generic);
10734   for (target = p->u.generic; target; target = target->next)
10735     if (!target->specific)
10736       {
10737         gfc_typebound_proc* overridden_tbp;
10738         gfc_tbp_generic* g;
10739         const char* target_name;
10740
10741         target_name = target->specific_st->name;
10742
10743         /* Defined for this type directly.  */
10744         if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
10745           {
10746             target->specific = target->specific_st->n.tb;
10747             goto specific_found;
10748           }
10749
10750         /* Look for an inherited specific binding.  */
10751         if (super_type)
10752           {
10753             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10754                                                  true, NULL);
10755
10756             if (inherited)
10757               {
10758                 gcc_assert (inherited->n.tb);
10759                 target->specific = inherited->n.tb;
10760                 goto specific_found;
10761               }
10762           }
10763
10764         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10765                    " at %L", target_name, name, &p->where);
10766         return FAILURE;
10767
10768         /* Once we've found the specific binding, check it is not ambiguous with
10769            other specifics already found or inherited for the same GENERIC.  */
10770 specific_found:
10771         gcc_assert (target->specific);
10772
10773         /* This must really be a specific binding!  */
10774         if (target->specific->is_generic)
10775           {
10776             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
10777                        " '%s' is GENERIC, too", name, &p->where, target_name);
10778             return FAILURE;
10779           }
10780
10781         /* Check those already resolved on this type directly.  */
10782         for (g = p->u.generic; g; g = g->next)
10783           if (g != target && g->specific
10784               && check_generic_tbp_ambiguity (target, g, name, p->where)
10785                   == FAILURE)
10786             return FAILURE;
10787
10788         /* Check for ambiguity with inherited specific targets.  */
10789         for (overridden_tbp = p->overridden; overridden_tbp;
10790              overridden_tbp = overridden_tbp->overridden)
10791           if (overridden_tbp->is_generic)
10792             {
10793               for (g = overridden_tbp->u.generic; g; g = g->next)
10794                 {
10795                   gcc_assert (g->specific);
10796                   if (check_generic_tbp_ambiguity (target, g,
10797                                                    name, p->where) == FAILURE)
10798                     return FAILURE;
10799                 }
10800             }
10801       }
10802
10803   /* If we attempt to "overwrite" a specific binding, this is an error.  */
10804   if (p->overridden && !p->overridden->is_generic)
10805     {
10806       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
10807                  " the same name", name, &p->where);
10808       return FAILURE;
10809     }
10810
10811   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
10812      all must have the same attributes here.  */
10813   first_target = p->u.generic->specific->u.specific;
10814   gcc_assert (first_target);
10815   p->subroutine = first_target->n.sym->attr.subroutine;
10816   p->function = first_target->n.sym->attr.function;
10817
10818   return SUCCESS;
10819 }
10820
10821
10822 /* Resolve a GENERIC procedure binding for a derived type.  */
10823
10824 static gfc_try
10825 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
10826 {
10827   gfc_symbol* super_type;
10828
10829   /* Find the overridden binding if any.  */
10830   st->n.tb->overridden = NULL;
10831   super_type = gfc_get_derived_super_type (derived);
10832   if (super_type)
10833     {
10834       gfc_symtree* overridden;
10835       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
10836                                             true, NULL);
10837
10838       if (overridden && overridden->n.tb)
10839         st->n.tb->overridden = overridden->n.tb;
10840     }
10841
10842   /* Resolve using worker function.  */
10843   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
10844 }
10845
10846
10847 /* Retrieve the target-procedure of an operator binding and do some checks in
10848    common for intrinsic and user-defined type-bound operators.  */
10849
10850 static gfc_symbol*
10851 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
10852 {
10853   gfc_symbol* target_proc;
10854
10855   gcc_assert (target->specific && !target->specific->is_generic);
10856   target_proc = target->specific->u.specific->n.sym;
10857   gcc_assert (target_proc);
10858
10859   /* All operator bindings must have a passed-object dummy argument.  */
10860   if (target->specific->nopass)
10861     {
10862       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
10863       return NULL;
10864     }
10865
10866   return target_proc;
10867 }
10868
10869
10870 /* Resolve a type-bound intrinsic operator.  */
10871
10872 static gfc_try
10873 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
10874                                 gfc_typebound_proc* p)
10875 {
10876   gfc_symbol* super_type;
10877   gfc_tbp_generic* target;
10878   
10879   /* If there's already an error here, do nothing (but don't fail again).  */
10880   if (p->error)
10881     return SUCCESS;
10882
10883   /* Operators should always be GENERIC bindings.  */
10884   gcc_assert (p->is_generic);
10885
10886   /* Look for an overridden binding.  */
10887   super_type = gfc_get_derived_super_type (derived);
10888   if (super_type && super_type->f2k_derived)
10889     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
10890                                                      op, true, NULL);
10891   else
10892     p->overridden = NULL;
10893
10894   /* Resolve general GENERIC properties using worker function.  */
10895   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
10896     goto error;
10897
10898   /* Check the targets to be procedures of correct interface.  */
10899   for (target = p->u.generic; target; target = target->next)
10900     {
10901       gfc_symbol* target_proc;
10902
10903       target_proc = get_checked_tb_operator_target (target, p->where);
10904       if (!target_proc)
10905         goto error;
10906
10907       if (!gfc_check_operator_interface (target_proc, op, p->where))
10908         goto error;
10909     }
10910
10911   return SUCCESS;
10912
10913 error:
10914   p->error = 1;
10915   return FAILURE;
10916 }
10917
10918
10919 /* Resolve a type-bound user operator (tree-walker callback).  */
10920
10921 static gfc_symbol* resolve_bindings_derived;
10922 static gfc_try resolve_bindings_result;
10923
10924 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
10925
10926 static void
10927 resolve_typebound_user_op (gfc_symtree* stree)
10928 {
10929   gfc_symbol* super_type;
10930   gfc_tbp_generic* target;
10931
10932   gcc_assert (stree && stree->n.tb);
10933
10934   if (stree->n.tb->error)
10935     return;
10936
10937   /* Operators should always be GENERIC bindings.  */
10938   gcc_assert (stree->n.tb->is_generic);
10939
10940   /* Find overridden procedure, if any.  */
10941   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10942   if (super_type && super_type->f2k_derived)
10943     {
10944       gfc_symtree* overridden;
10945       overridden = gfc_find_typebound_user_op (super_type, NULL,
10946                                                stree->name, true, NULL);
10947
10948       if (overridden && overridden->n.tb)
10949         stree->n.tb->overridden = overridden->n.tb;
10950     }
10951   else
10952     stree->n.tb->overridden = NULL;
10953
10954   /* Resolve basically using worker function.  */
10955   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
10956         == FAILURE)
10957     goto error;
10958
10959   /* Check the targets to be functions of correct interface.  */
10960   for (target = stree->n.tb->u.generic; target; target = target->next)
10961     {
10962       gfc_symbol* target_proc;
10963
10964       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
10965       if (!target_proc)
10966         goto error;
10967
10968       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
10969         goto error;
10970     }
10971
10972   return;
10973
10974 error:
10975   resolve_bindings_result = FAILURE;
10976   stree->n.tb->error = 1;
10977 }
10978
10979
10980 /* Resolve the type-bound procedures for a derived type.  */
10981
10982 static void
10983 resolve_typebound_procedure (gfc_symtree* stree)
10984 {
10985   gfc_symbol* proc;
10986   locus where;
10987   gfc_symbol* me_arg;
10988   gfc_symbol* super_type;
10989   gfc_component* comp;
10990
10991   gcc_assert (stree);
10992
10993   /* Undefined specific symbol from GENERIC target definition.  */
10994   if (!stree->n.tb)
10995     return;
10996
10997   if (stree->n.tb->error)
10998     return;
10999
11000   /* If this is a GENERIC binding, use that routine.  */
11001   if (stree->n.tb->is_generic)
11002     {
11003       if (resolve_typebound_generic (resolve_bindings_derived, stree)
11004             == FAILURE)
11005         goto error;
11006       return;
11007     }
11008
11009   /* Get the target-procedure to check it.  */
11010   gcc_assert (!stree->n.tb->is_generic);
11011   gcc_assert (stree->n.tb->u.specific);
11012   proc = stree->n.tb->u.specific->n.sym;
11013   where = stree->n.tb->where;
11014
11015   /* Default access should already be resolved from the parser.  */
11016   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
11017
11018   /* It should be a module procedure or an external procedure with explicit
11019      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
11020   if ((!proc->attr.subroutine && !proc->attr.function)
11021       || (proc->attr.proc != PROC_MODULE
11022           && proc->attr.if_source != IFSRC_IFBODY)
11023       || (proc->attr.abstract && !stree->n.tb->deferred))
11024     {
11025       gfc_error ("'%s' must be a module procedure or an external procedure with"
11026                  " an explicit interface at %L", proc->name, &where);
11027       goto error;
11028     }
11029   stree->n.tb->subroutine = proc->attr.subroutine;
11030   stree->n.tb->function = proc->attr.function;
11031
11032   /* Find the super-type of the current derived type.  We could do this once and
11033      store in a global if speed is needed, but as long as not I believe this is
11034      more readable and clearer.  */
11035   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11036
11037   /* If PASS, resolve and check arguments if not already resolved / loaded
11038      from a .mod file.  */
11039   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
11040     {
11041       if (stree->n.tb->pass_arg)
11042         {
11043           gfc_formal_arglist* i;
11044
11045           /* If an explicit passing argument name is given, walk the arg-list
11046              and look for it.  */
11047
11048           me_arg = NULL;
11049           stree->n.tb->pass_arg_num = 1;
11050           for (i = proc->formal; i; i = i->next)
11051             {
11052               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
11053                 {
11054                   me_arg = i->sym;
11055                   break;
11056                 }
11057               ++stree->n.tb->pass_arg_num;
11058             }
11059
11060           if (!me_arg)
11061             {
11062               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
11063                          " argument '%s'",
11064                          proc->name, stree->n.tb->pass_arg, &where,
11065                          stree->n.tb->pass_arg);
11066               goto error;
11067             }
11068         }
11069       else
11070         {
11071           /* Otherwise, take the first one; there should in fact be at least
11072              one.  */
11073           stree->n.tb->pass_arg_num = 1;
11074           if (!proc->formal)
11075             {
11076               gfc_error ("Procedure '%s' with PASS at %L must have at"
11077                          " least one argument", proc->name, &where);
11078               goto error;
11079             }
11080           me_arg = proc->formal->sym;
11081         }
11082
11083       /* Now check that the argument-type matches and the passed-object
11084          dummy argument is generally fine.  */
11085
11086       gcc_assert (me_arg);
11087
11088       if (me_arg->ts.type != BT_CLASS)
11089         {
11090           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11091                      " at %L", proc->name, &where);
11092           goto error;
11093         }
11094
11095       if (CLASS_DATA (me_arg)->ts.u.derived
11096           != resolve_bindings_derived)
11097         {
11098           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11099                      " the derived-type '%s'", me_arg->name, proc->name,
11100                      me_arg->name, &where, resolve_bindings_derived->name);
11101           goto error;
11102         }
11103   
11104       gcc_assert (me_arg->ts.type == BT_CLASS);
11105       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
11106         {
11107           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
11108                      " scalar", proc->name, &where);
11109           goto error;
11110         }
11111       if (CLASS_DATA (me_arg)->attr.allocatable)
11112         {
11113           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11114                      " be ALLOCATABLE", proc->name, &where);
11115           goto error;
11116         }
11117       if (CLASS_DATA (me_arg)->attr.class_pointer)
11118         {
11119           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11120                      " be POINTER", proc->name, &where);
11121           goto error;
11122         }
11123     }
11124
11125   /* If we are extending some type, check that we don't override a procedure
11126      flagged NON_OVERRIDABLE.  */
11127   stree->n.tb->overridden = NULL;
11128   if (super_type)
11129     {
11130       gfc_symtree* overridden;
11131       overridden = gfc_find_typebound_proc (super_type, NULL,
11132                                             stree->name, true, NULL);
11133
11134       if (overridden && overridden->n.tb)
11135         stree->n.tb->overridden = overridden->n.tb;
11136
11137       if (overridden && check_typebound_override (stree, overridden) == FAILURE)
11138         goto error;
11139     }
11140
11141   /* See if there's a name collision with a component directly in this type.  */
11142   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
11143     if (!strcmp (comp->name, stree->name))
11144       {
11145         gfc_error ("Procedure '%s' at %L has the same name as a component of"
11146                    " '%s'",
11147                    stree->name, &where, resolve_bindings_derived->name);
11148         goto error;
11149       }
11150
11151   /* Try to find a name collision with an inherited component.  */
11152   if (super_type && gfc_find_component (super_type, stree->name, true, true))
11153     {
11154       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
11155                  " component of '%s'",
11156                  stree->name, &where, resolve_bindings_derived->name);
11157       goto error;
11158     }
11159
11160   stree->n.tb->error = 0;
11161   return;
11162
11163 error:
11164   resolve_bindings_result = FAILURE;
11165   stree->n.tb->error = 1;
11166 }
11167
11168
11169 static gfc_try
11170 resolve_typebound_procedures (gfc_symbol* derived)
11171 {
11172   int op;
11173
11174   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
11175     return SUCCESS;
11176
11177   resolve_bindings_derived = derived;
11178   resolve_bindings_result = SUCCESS;
11179
11180   /* Make sure the vtab has been generated.  */
11181   gfc_find_derived_vtab (derived);
11182
11183   if (derived->f2k_derived->tb_sym_root)
11184     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
11185                           &resolve_typebound_procedure);
11186
11187   if (derived->f2k_derived->tb_uop_root)
11188     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
11189                           &resolve_typebound_user_op);
11190
11191   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
11192     {
11193       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
11194       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
11195                                                p) == FAILURE)
11196         resolve_bindings_result = FAILURE;
11197     }
11198
11199   return resolve_bindings_result;
11200 }
11201
11202
11203 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
11204    to give all identical derived types the same backend_decl.  */
11205 static void
11206 add_dt_to_dt_list (gfc_symbol *derived)
11207 {
11208   gfc_dt_list *dt_list;
11209
11210   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
11211     if (derived == dt_list->derived)
11212       return;
11213
11214   dt_list = gfc_get_dt_list ();
11215   dt_list->next = gfc_derived_types;
11216   dt_list->derived = derived;
11217   gfc_derived_types = dt_list;
11218 }
11219
11220
11221 /* Ensure that a derived-type is really not abstract, meaning that every
11222    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
11223
11224 static gfc_try
11225 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
11226 {
11227   if (!st)
11228     return SUCCESS;
11229
11230   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
11231     return FAILURE;
11232   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
11233     return FAILURE;
11234
11235   if (st->n.tb && st->n.tb->deferred)
11236     {
11237       gfc_symtree* overriding;
11238       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
11239       if (!overriding)
11240         return FAILURE;
11241       gcc_assert (overriding->n.tb);
11242       if (overriding->n.tb->deferred)
11243         {
11244           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
11245                      " '%s' is DEFERRED and not overridden",
11246                      sub->name, &sub->declared_at, st->name);
11247           return FAILURE;
11248         }
11249     }
11250
11251   return SUCCESS;
11252 }
11253
11254 static gfc_try
11255 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
11256 {
11257   /* The algorithm used here is to recursively travel up the ancestry of sub
11258      and for each ancestor-type, check all bindings.  If any of them is
11259      DEFERRED, look it up starting from sub and see if the found (overriding)
11260      binding is not DEFERRED.
11261      This is not the most efficient way to do this, but it should be ok and is
11262      clearer than something sophisticated.  */
11263
11264   gcc_assert (ancestor && !sub->attr.abstract);
11265   
11266   if (!ancestor->attr.abstract)
11267     return SUCCESS;
11268
11269   /* Walk bindings of this ancestor.  */
11270   if (ancestor->f2k_derived)
11271     {
11272       gfc_try t;
11273       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
11274       if (t == FAILURE)
11275         return FAILURE;
11276     }
11277
11278   /* Find next ancestor type and recurse on it.  */
11279   ancestor = gfc_get_derived_super_type (ancestor);
11280   if (ancestor)
11281     return ensure_not_abstract (sub, ancestor);
11282
11283   return SUCCESS;
11284 }
11285
11286
11287 /* Resolve the components of a derived type.  */
11288
11289 static gfc_try
11290 resolve_fl_derived (gfc_symbol *sym)
11291 {
11292   gfc_symbol* super_type;
11293   gfc_component *c;
11294
11295   super_type = gfc_get_derived_super_type (sym);
11296   
11297   if (sym->attr.is_class && sym->ts.u.derived == NULL)
11298     {
11299       /* Fix up incomplete CLASS symbols.  */
11300       gfc_component *data = gfc_find_component (sym, "_data", true, true);
11301       gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true);
11302       if (vptr->ts.u.derived == NULL)
11303         {
11304           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
11305           gcc_assert (vtab);
11306           vptr->ts.u.derived = vtab->ts.u.derived;
11307         }
11308     }
11309
11310   /* F2008, C432. */
11311   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
11312     {
11313       gfc_error ("As extending type '%s' at %L has a coarray component, "
11314                  "parent type '%s' shall also have one", sym->name,
11315                  &sym->declared_at, super_type->name);
11316       return FAILURE;
11317     }
11318
11319   /* Ensure the extended type gets resolved before we do.  */
11320   if (super_type && resolve_fl_derived (super_type) == FAILURE)
11321     return FAILURE;
11322
11323   /* An ABSTRACT type must be extensible.  */
11324   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
11325     {
11326       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
11327                  sym->name, &sym->declared_at);
11328       return FAILURE;
11329     }
11330
11331   for (c = sym->components; c != NULL; c = c->next)
11332     {
11333       /* F2008, C442.  */
11334       if (c->attr.codimension /* FIXME: c->as check due to PR 43412.  */
11335           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
11336         {
11337           gfc_error ("Coarray component '%s' at %L must be allocatable with "
11338                      "deferred shape", c->name, &c->loc);
11339           return FAILURE;
11340         }
11341
11342       /* F2008, C443.  */
11343       if (c->attr.codimension && c->ts.type == BT_DERIVED
11344           && c->ts.u.derived->ts.is_iso_c)
11345         {
11346           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11347                      "shall not be a coarray", c->name, &c->loc);
11348           return FAILURE;
11349         }
11350
11351       /* F2008, C444.  */
11352       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
11353           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
11354               || c->attr.allocatable))
11355         {
11356           gfc_error ("Component '%s' at %L with coarray component "
11357                      "shall be a nonpointer, nonallocatable scalar",
11358                      c->name, &c->loc);
11359           return FAILURE;
11360         }
11361
11362       /* F2008, C448.  */
11363       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
11364         {
11365           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
11366                      "is not an array pointer", c->name, &c->loc);
11367           return FAILURE;
11368         }
11369
11370       if (c->attr.proc_pointer && c->ts.interface)
11371         {
11372           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
11373             gfc_error ("Interface '%s', used by procedure pointer component "
11374                        "'%s' at %L, is declared in a later PROCEDURE statement",
11375                        c->ts.interface->name, c->name, &c->loc);
11376
11377           /* Get the attributes from the interface (now resolved).  */
11378           if (c->ts.interface->attr.if_source
11379               || c->ts.interface->attr.intrinsic)
11380             {
11381               gfc_symbol *ifc = c->ts.interface;
11382
11383               if (ifc->formal && !ifc->formal_ns)
11384                 resolve_symbol (ifc);
11385
11386               if (ifc->attr.intrinsic)
11387                 resolve_intrinsic (ifc, &ifc->declared_at);
11388
11389               if (ifc->result)
11390                 {
11391                   c->ts = ifc->result->ts;
11392                   c->attr.allocatable = ifc->result->attr.allocatable;
11393                   c->attr.pointer = ifc->result->attr.pointer;
11394                   c->attr.dimension = ifc->result->attr.dimension;
11395                   c->as = gfc_copy_array_spec (ifc->result->as);
11396                 }
11397               else
11398                 {   
11399                   c->ts = ifc->ts;
11400                   c->attr.allocatable = ifc->attr.allocatable;
11401                   c->attr.pointer = ifc->attr.pointer;
11402                   c->attr.dimension = ifc->attr.dimension;
11403                   c->as = gfc_copy_array_spec (ifc->as);
11404                 }
11405               c->ts.interface = ifc;
11406               c->attr.function = ifc->attr.function;
11407               c->attr.subroutine = ifc->attr.subroutine;
11408               gfc_copy_formal_args_ppc (c, ifc);
11409
11410               c->attr.pure = ifc->attr.pure;
11411               c->attr.elemental = ifc->attr.elemental;
11412               c->attr.recursive = ifc->attr.recursive;
11413               c->attr.always_explicit = ifc->attr.always_explicit;
11414               c->attr.ext_attr |= ifc->attr.ext_attr;
11415               /* Replace symbols in array spec.  */
11416               if (c->as)
11417                 {
11418                   int i;
11419                   for (i = 0; i < c->as->rank; i++)
11420                     {
11421                       gfc_expr_replace_comp (c->as->lower[i], c);
11422                       gfc_expr_replace_comp (c->as->upper[i], c);
11423                     }
11424                 }
11425               /* Copy char length.  */
11426               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11427                 {
11428                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11429                   gfc_expr_replace_comp (cl->length, c);
11430                   if (cl->length && !cl->resolved
11431                         && gfc_resolve_expr (cl->length) == FAILURE)
11432                     return FAILURE;
11433                   c->ts.u.cl = cl;
11434                 }
11435             }
11436           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
11437             {
11438               gfc_error ("Interface '%s' of procedure pointer component "
11439                          "'%s' at %L must be explicit", c->ts.interface->name,
11440                          c->name, &c->loc);
11441               return FAILURE;
11442             }
11443         }
11444       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
11445         {
11446           /* Since PPCs are not implicitly typed, a PPC without an explicit
11447              interface must be a subroutine.  */
11448           gfc_add_subroutine (&c->attr, c->name, &c->loc);
11449         }
11450
11451       /* Procedure pointer components: Check PASS arg.  */
11452       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
11453           && !sym->attr.vtype)
11454         {
11455           gfc_symbol* me_arg;
11456
11457           if (c->tb->pass_arg)
11458             {
11459               gfc_formal_arglist* i;
11460
11461               /* If an explicit passing argument name is given, walk the arg-list
11462                 and look for it.  */
11463
11464               me_arg = NULL;
11465               c->tb->pass_arg_num = 1;
11466               for (i = c->formal; i; i = i->next)
11467                 {
11468                   if (!strcmp (i->sym->name, c->tb->pass_arg))
11469                     {
11470                       me_arg = i->sym;
11471                       break;
11472                     }
11473                   c->tb->pass_arg_num++;
11474                 }
11475
11476               if (!me_arg)
11477                 {
11478                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
11479                              "at %L has no argument '%s'", c->name,
11480                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
11481                   c->tb->error = 1;
11482                   return FAILURE;
11483                 }
11484             }
11485           else
11486             {
11487               /* Otherwise, take the first one; there should in fact be at least
11488                 one.  */
11489               c->tb->pass_arg_num = 1;
11490               if (!c->formal)
11491                 {
11492                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
11493                              "must have at least one argument",
11494                              c->name, &c->loc);
11495                   c->tb->error = 1;
11496                   return FAILURE;
11497                 }
11498               me_arg = c->formal->sym;
11499             }
11500
11501           /* Now check that the argument-type matches.  */
11502           gcc_assert (me_arg);
11503           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
11504               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
11505               || (me_arg->ts.type == BT_CLASS
11506                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
11507             {
11508               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11509                          " the derived type '%s'", me_arg->name, c->name,
11510                          me_arg->name, &c->loc, sym->name);
11511               c->tb->error = 1;
11512               return FAILURE;
11513             }
11514
11515           /* Check for C453.  */
11516           if (me_arg->attr.dimension)
11517             {
11518               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11519                          "must be scalar", me_arg->name, c->name, me_arg->name,
11520                          &c->loc);
11521               c->tb->error = 1;
11522               return FAILURE;
11523             }
11524
11525           if (me_arg->attr.pointer)
11526             {
11527               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11528                          "may not have the POINTER attribute", me_arg->name,
11529                          c->name, me_arg->name, &c->loc);
11530               c->tb->error = 1;
11531               return FAILURE;
11532             }
11533
11534           if (me_arg->attr.allocatable)
11535             {
11536               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11537                          "may not be ALLOCATABLE", me_arg->name, c->name,
11538                          me_arg->name, &c->loc);
11539               c->tb->error = 1;
11540               return FAILURE;
11541             }
11542
11543           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11544             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11545                        " at %L", c->name, &c->loc);
11546
11547         }
11548
11549       /* Check type-spec if this is not the parent-type component.  */
11550       if ((!sym->attr.extension || c != sym->components) && !sym->attr.vtype
11551           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11552         return FAILURE;
11553
11554       /* If this type is an extension, set the accessibility of the parent
11555          component.  */
11556       if (super_type && c == sym->components
11557           && strcmp (super_type->name, c->name) == 0)
11558         c->attr.access = super_type->attr.access;
11559       
11560       /* If this type is an extension, see if this component has the same name
11561          as an inherited type-bound procedure.  */
11562       if (super_type && !sym->attr.is_class
11563           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11564         {
11565           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11566                      " inherited type-bound procedure",
11567                      c->name, sym->name, &c->loc);
11568           return FAILURE;
11569         }
11570
11571       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer)
11572         {
11573          if (c->ts.u.cl->length == NULL
11574              || (resolve_charlen (c->ts.u.cl) == FAILURE)
11575              || !gfc_is_constant_expr (c->ts.u.cl->length))
11576            {
11577              gfc_error ("Character length of component '%s' needs to "
11578                         "be a constant specification expression at %L",
11579                         c->name,
11580                         c->ts.u.cl->length ? &c->ts.u.cl->length->where : &c->loc);
11581              return FAILURE;
11582            }
11583         }
11584
11585       if (c->ts.type == BT_DERIVED
11586           && sym->component_access != ACCESS_PRIVATE
11587           && gfc_check_access (sym->attr.access, sym->ns->default_access)
11588           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11589           && !c->ts.u.derived->attr.use_assoc
11590           && !gfc_check_access (c->ts.u.derived->attr.access,
11591                                 c->ts.u.derived->ns->default_access)
11592           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11593                              "is a PRIVATE type and cannot be a component of "
11594                              "'%s', which is PUBLIC at %L", c->name,
11595                              sym->name, &sym->declared_at) == FAILURE)
11596         return FAILURE;
11597
11598       if ((sym->attr.sequence || sym->attr.is_bind_c) && c->ts.type == BT_CLASS)
11599         {
11600           gfc_error ("Polymorphic component %s at %L in SEQUENCE or BIND(C) "
11601                      "type %s", c->name, &c->loc, sym->name);
11602           return FAILURE;
11603         }
11604
11605       if (sym->attr.sequence)
11606         {
11607           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
11608             {
11609               gfc_error ("Component %s of SEQUENCE type declared at %L does "
11610                          "not have the SEQUENCE attribute",
11611                          c->ts.u.derived->name, &sym->declared_at);
11612               return FAILURE;
11613             }
11614         }
11615
11616       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && !sym->attr.vtype
11617           && c->attr.pointer && c->ts.u.derived->components == NULL
11618           && !c->ts.u.derived->attr.zero_comp)
11619         {
11620           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11621                      "that has not been declared", c->name, sym->name,
11622                      &c->loc);
11623           return FAILURE;
11624         }
11625
11626       if (c->ts.type == BT_CLASS && CLASS_DATA (c)->attr.class_pointer
11627           && CLASS_DATA (c)->ts.u.derived->components == NULL
11628           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
11629         {
11630           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11631                      "that has not been declared", c->name, sym->name,
11632                      &c->loc);
11633           return FAILURE;
11634         }
11635
11636       /* C437.  */
11637       if (c->ts.type == BT_CLASS
11638           && !(CLASS_DATA (c)->attr.class_pointer
11639                || CLASS_DATA (c)->attr.allocatable))
11640         {
11641           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
11642                      "or pointer", c->name, &c->loc);
11643           return FAILURE;
11644         }
11645
11646       /* Ensure that all the derived type components are put on the
11647          derived type list; even in formal namespaces, where derived type
11648          pointer components might not have been declared.  */
11649       if (c->ts.type == BT_DERIVED
11650             && c->ts.u.derived
11651             && c->ts.u.derived->components
11652             && c->attr.pointer
11653             && sym != c->ts.u.derived)
11654         add_dt_to_dt_list (c->ts.u.derived);
11655
11656       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
11657                                            || c->attr.proc_pointer
11658                                            || c->attr.allocatable)) == FAILURE)
11659         return FAILURE;
11660     }
11661
11662   /* Resolve the type-bound procedures.  */
11663   if (resolve_typebound_procedures (sym) == FAILURE)
11664     return FAILURE;
11665
11666   /* Resolve the finalizer procedures.  */
11667   if (gfc_resolve_finalizers (sym) == FAILURE)
11668     return FAILURE;
11669
11670   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11671      all DEFERRED bindings are overridden.  */
11672   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11673       && !sym->attr.is_class
11674       && ensure_not_abstract (sym, super_type) == FAILURE)
11675     return FAILURE;
11676
11677   /* Add derived type to the derived type list.  */
11678   add_dt_to_dt_list (sym);
11679
11680   return SUCCESS;
11681 }
11682
11683
11684 static gfc_try
11685 resolve_fl_namelist (gfc_symbol *sym)
11686 {
11687   gfc_namelist *nl;
11688   gfc_symbol *nlsym;
11689
11690   for (nl = sym->namelist; nl; nl = nl->next)
11691     {
11692       /* Reject namelist arrays of assumed shape.  */
11693       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
11694           && gfc_notify_std (GFC_STD_F2003, "NAMELIST array object '%s' "
11695                              "must not have assumed shape in namelist "
11696                              "'%s' at %L", nl->sym->name, sym->name,
11697                              &sym->declared_at) == FAILURE)
11698             return FAILURE;
11699
11700       /* Reject namelist arrays that are not constant shape.  */
11701       if (is_non_constant_shape_array (nl->sym))
11702         {
11703           gfc_error ("NAMELIST array object '%s' must have constant "
11704                      "shape in namelist '%s' at %L", nl->sym->name,
11705                      sym->name, &sym->declared_at);
11706           return FAILURE;
11707         }
11708
11709       /* Namelist objects cannot have allocatable or pointer components.  */
11710       if (nl->sym->ts.type != BT_DERIVED)
11711         continue;
11712
11713       if (nl->sym->ts.u.derived->attr.alloc_comp)
11714         {
11715           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11716                      "have ALLOCATABLE components",
11717                      nl->sym->name, sym->name, &sym->declared_at);
11718           return FAILURE;
11719         }
11720
11721       if (nl->sym->ts.u.derived->attr.pointer_comp)
11722         {
11723           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L cannot "
11724                      "have POINTER components", 
11725                      nl->sym->name, sym->name, &sym->declared_at);
11726           return FAILURE;
11727         }
11728     }
11729
11730   /* Reject PRIVATE objects in a PUBLIC namelist.  */
11731   if (gfc_check_access(sym->attr.access, sym->ns->default_access))
11732     {
11733       for (nl = sym->namelist; nl; nl = nl->next)
11734         {
11735           if (!nl->sym->attr.use_assoc
11736               && !is_sym_host_assoc (nl->sym, sym->ns)
11737               && !gfc_check_access(nl->sym->attr.access,
11738                                 nl->sym->ns->default_access))
11739             {
11740               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
11741                          "cannot be member of PUBLIC namelist '%s' at %L",
11742                          nl->sym->name, sym->name, &sym->declared_at);
11743               return FAILURE;
11744             }
11745
11746           /* Types with private components that came here by USE-association.  */
11747           if (nl->sym->ts.type == BT_DERIVED
11748               && derived_inaccessible (nl->sym->ts.u.derived))
11749             {
11750               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
11751                          "components and cannot be member of namelist '%s' at %L",
11752                          nl->sym->name, sym->name, &sym->declared_at);
11753               return FAILURE;
11754             }
11755
11756           /* Types with private components that are defined in the same module.  */
11757           if (nl->sym->ts.type == BT_DERIVED
11758               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
11759               && !gfc_check_access (nl->sym->ts.u.derived->attr.private_comp
11760                                         ? ACCESS_PRIVATE : ACCESS_UNKNOWN,
11761                                         nl->sym->ns->default_access))
11762             {
11763               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
11764                          "cannot be a member of PUBLIC namelist '%s' at %L",
11765                          nl->sym->name, sym->name, &sym->declared_at);
11766               return FAILURE;
11767             }
11768         }
11769     }
11770
11771
11772   /* 14.1.2 A module or internal procedure represent local entities
11773      of the same type as a namelist member and so are not allowed.  */
11774   for (nl = sym->namelist; nl; nl = nl->next)
11775     {
11776       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
11777         continue;
11778
11779       if (nl->sym->attr.function && nl->sym == nl->sym->result)
11780         if ((nl->sym == sym->ns->proc_name)
11781                ||
11782             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
11783           continue;
11784
11785       nlsym = NULL;
11786       if (nl->sym && nl->sym->name)
11787         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
11788       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
11789         {
11790           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
11791                      "attribute in '%s' at %L", nlsym->name,
11792                      &sym->declared_at);
11793           return FAILURE;
11794         }
11795     }
11796
11797   return SUCCESS;
11798 }
11799
11800
11801 static gfc_try
11802 resolve_fl_parameter (gfc_symbol *sym)
11803 {
11804   /* A parameter array's shape needs to be constant.  */
11805   if (sym->as != NULL 
11806       && (sym->as->type == AS_DEFERRED
11807           || is_non_constant_shape_array (sym)))
11808     {
11809       gfc_error ("Parameter array '%s' at %L cannot be automatic "
11810                  "or of deferred shape", sym->name, &sym->declared_at);
11811       return FAILURE;
11812     }
11813
11814   /* Make sure a parameter that has been implicitly typed still
11815      matches the implicit type, since PARAMETER statements can precede
11816      IMPLICIT statements.  */
11817   if (sym->attr.implicit_type
11818       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
11819                                                              sym->ns)))
11820     {
11821       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
11822                  "later IMPLICIT type", sym->name, &sym->declared_at);
11823       return FAILURE;
11824     }
11825
11826   /* Make sure the types of derived parameters are consistent.  This
11827      type checking is deferred until resolution because the type may
11828      refer to a derived type from the host.  */
11829   if (sym->ts.type == BT_DERIVED
11830       && !gfc_compare_types (&sym->ts, &sym->value->ts))
11831     {
11832       gfc_error ("Incompatible derived type in PARAMETER at %L",
11833                  &sym->value->where);
11834       return FAILURE;
11835     }
11836   return SUCCESS;
11837 }
11838
11839
11840 /* Do anything necessary to resolve a symbol.  Right now, we just
11841    assume that an otherwise unknown symbol is a variable.  This sort
11842    of thing commonly happens for symbols in module.  */
11843
11844 static void
11845 resolve_symbol (gfc_symbol *sym)
11846 {
11847   int check_constant, mp_flag;
11848   gfc_symtree *symtree;
11849   gfc_symtree *this_symtree;
11850   gfc_namespace *ns;
11851   gfc_component *c;
11852
11853   /* Avoid double resolution of function result symbols.  */
11854   if ((sym->result || sym->attr.result) && !sym->attr.dummy
11855       && (sym->ns != gfc_current_ns))
11856     return;
11857   
11858   if (sym->attr.flavor == FL_UNKNOWN)
11859     {
11860
11861     /* If we find that a flavorless symbol is an interface in one of the
11862        parent namespaces, find its symtree in this namespace, free the
11863        symbol and set the symtree to point to the interface symbol.  */
11864       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
11865         {
11866           symtree = gfc_find_symtree (ns->sym_root, sym->name);
11867           if (symtree && (symtree->n.sym->generic ||
11868                           (symtree->n.sym->attr.flavor == FL_PROCEDURE
11869                            && sym->ns->construct_entities)))
11870             {
11871               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
11872                                                sym->name);
11873               gfc_release_symbol (sym);
11874               symtree->n.sym->refs++;
11875               this_symtree->n.sym = symtree->n.sym;
11876               return;
11877             }
11878         }
11879
11880       /* Otherwise give it a flavor according to such attributes as
11881          it has.  */
11882       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
11883         sym->attr.flavor = FL_VARIABLE;
11884       else
11885         {
11886           sym->attr.flavor = FL_PROCEDURE;
11887           if (sym->attr.dimension)
11888             sym->attr.function = 1;
11889         }
11890     }
11891
11892   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
11893     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
11894
11895   if (sym->attr.procedure && sym->ts.interface
11896       && sym->attr.if_source != IFSRC_DECL
11897       && resolve_procedure_interface (sym) == FAILURE)
11898     return;
11899
11900   if (sym->attr.is_protected && !sym->attr.proc_pointer
11901       && (sym->attr.procedure || sym->attr.external))
11902     {
11903       if (sym->attr.external)
11904         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
11905                    "at %L", &sym->declared_at);
11906       else
11907         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
11908                    "at %L", &sym->declared_at);
11909
11910       return;
11911     }
11912
11913
11914   /* F2008, C530. */
11915   if (sym->attr.contiguous
11916       && (!sym->attr.dimension || (sym->as->type != AS_ASSUMED_SHAPE
11917                                    && !sym->attr.pointer)))
11918     {
11919       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
11920                   "array pointer or an assumed-shape array", sym->name,
11921                   &sym->declared_at);
11922       return;
11923     }
11924
11925   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
11926     return;
11927
11928   /* Symbols that are module procedures with results (functions) have
11929      the types and array specification copied for type checking in
11930      procedures that call them, as well as for saving to a module
11931      file.  These symbols can't stand the scrutiny that their results
11932      can.  */
11933   mp_flag = (sym->result != NULL && sym->result != sym);
11934
11935   /* Make sure that the intrinsic is consistent with its internal 
11936      representation. This needs to be done before assigning a default 
11937      type to avoid spurious warnings.  */
11938   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
11939       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
11940     return;
11941
11942   /* Resolve associate names.  */
11943   if (sym->assoc)
11944     resolve_assoc_var (sym, true);
11945
11946   /* Assign default type to symbols that need one and don't have one.  */
11947   if (sym->ts.type == BT_UNKNOWN)
11948     {
11949       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
11950         gfc_set_default_type (sym, 1, NULL);
11951
11952       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
11953           && !sym->attr.function && !sym->attr.subroutine
11954           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
11955         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
11956
11957       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
11958         {
11959           /* The specific case of an external procedure should emit an error
11960              in the case that there is no implicit type.  */
11961           if (!mp_flag)
11962             gfc_set_default_type (sym, sym->attr.external, NULL);
11963           else
11964             {
11965               /* Result may be in another namespace.  */
11966               resolve_symbol (sym->result);
11967
11968               if (!sym->result->attr.proc_pointer)
11969                 {
11970                   sym->ts = sym->result->ts;
11971                   sym->as = gfc_copy_array_spec (sym->result->as);
11972                   sym->attr.dimension = sym->result->attr.dimension;
11973                   sym->attr.pointer = sym->result->attr.pointer;
11974                   sym->attr.allocatable = sym->result->attr.allocatable;
11975                   sym->attr.contiguous = sym->result->attr.contiguous;
11976                 }
11977             }
11978         }
11979     }
11980
11981   /* Assumed size arrays and assumed shape arrays must be dummy
11982      arguments.  Array-spec's of implied-shape should have been resolved to
11983      AS_EXPLICIT already.  */
11984
11985   if (sym->as)
11986     {
11987       gcc_assert (sym->as->type != AS_IMPLIED_SHAPE);
11988       if (((sym->as->type == AS_ASSUMED_SIZE && !sym->as->cp_was_assumed)
11989            || sym->as->type == AS_ASSUMED_SHAPE)
11990           && sym->attr.dummy == 0)
11991         {
11992           if (sym->as->type == AS_ASSUMED_SIZE)
11993             gfc_error ("Assumed size array at %L must be a dummy argument",
11994                        &sym->declared_at);
11995           else
11996             gfc_error ("Assumed shape array at %L must be a dummy argument",
11997                        &sym->declared_at);
11998           return;
11999         }
12000     }
12001
12002   /* Make sure symbols with known intent or optional are really dummy
12003      variable.  Because of ENTRY statement, this has to be deferred
12004      until resolution time.  */
12005
12006   if (!sym->attr.dummy
12007       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
12008     {
12009       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
12010       return;
12011     }
12012
12013   if (sym->attr.value && !sym->attr.dummy)
12014     {
12015       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
12016                  "it is not a dummy argument", sym->name, &sym->declared_at);
12017       return;
12018     }
12019
12020   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
12021     {
12022       gfc_charlen *cl = sym->ts.u.cl;
12023       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
12024         {
12025           gfc_error ("Character dummy variable '%s' at %L with VALUE "
12026                      "attribute must have constant length",
12027                      sym->name, &sym->declared_at);
12028           return;
12029         }
12030
12031       if (sym->ts.is_c_interop
12032           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
12033         {
12034           gfc_error ("C interoperable character dummy variable '%s' at %L "
12035                      "with VALUE attribute must have length one",
12036                      sym->name, &sym->declared_at);
12037           return;
12038         }
12039     }
12040
12041   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
12042      do this for something that was implicitly typed because that is handled
12043      in gfc_set_default_type.  Handle dummy arguments and procedure
12044      definitions separately.  Also, anything that is use associated is not
12045      handled here but instead is handled in the module it is declared in.
12046      Finally, derived type definitions are allowed to be BIND(C) since that
12047      only implies that they're interoperable, and they are checked fully for
12048      interoperability when a variable is declared of that type.  */
12049   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
12050       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
12051       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
12052     {
12053       gfc_try t = SUCCESS;
12054       
12055       /* First, make sure the variable is declared at the
12056          module-level scope (J3/04-007, Section 15.3).  */
12057       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
12058           sym->attr.in_common == 0)
12059         {
12060           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
12061                      "is neither a COMMON block nor declared at the "
12062                      "module level scope", sym->name, &(sym->declared_at));
12063           t = FAILURE;
12064         }
12065       else if (sym->common_head != NULL)
12066         {
12067           t = verify_com_block_vars_c_interop (sym->common_head);
12068         }
12069       else
12070         {
12071           /* If type() declaration, we need to verify that the components
12072              of the given type are all C interoperable, etc.  */
12073           if (sym->ts.type == BT_DERIVED &&
12074               sym->ts.u.derived->attr.is_c_interop != 1)
12075             {
12076               /* Make sure the user marked the derived type as BIND(C).  If
12077                  not, call the verify routine.  This could print an error
12078                  for the derived type more than once if multiple variables
12079                  of that type are declared.  */
12080               if (sym->ts.u.derived->attr.is_bind_c != 1)
12081                 verify_bind_c_derived_type (sym->ts.u.derived);
12082               t = FAILURE;
12083             }
12084           
12085           /* Verify the variable itself as C interoperable if it
12086              is BIND(C).  It is not possible for this to succeed if
12087              the verify_bind_c_derived_type failed, so don't have to handle
12088              any error returned by verify_bind_c_derived_type.  */
12089           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
12090                                  sym->common_block);
12091         }
12092
12093       if (t == FAILURE)
12094         {
12095           /* clear the is_bind_c flag to prevent reporting errors more than
12096              once if something failed.  */
12097           sym->attr.is_bind_c = 0;
12098           return;
12099         }
12100     }
12101
12102   /* If a derived type symbol has reached this point, without its
12103      type being declared, we have an error.  Notice that most
12104      conditions that produce undefined derived types have already
12105      been dealt with.  However, the likes of:
12106      implicit type(t) (t) ..... call foo (t) will get us here if
12107      the type is not declared in the scope of the implicit
12108      statement. Change the type to BT_UNKNOWN, both because it is so
12109      and to prevent an ICE.  */
12110   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
12111       && !sym->ts.u.derived->attr.zero_comp)
12112     {
12113       gfc_error ("The derived type '%s' at %L is of type '%s', "
12114                  "which has not been defined", sym->name,
12115                   &sym->declared_at, sym->ts.u.derived->name);
12116       sym->ts.type = BT_UNKNOWN;
12117       return;
12118     }
12119
12120   /* Make sure that the derived type has been resolved and that the
12121      derived type is visible in the symbol's namespace, if it is a
12122      module function and is not PRIVATE.  */
12123   if (sym->ts.type == BT_DERIVED
12124         && sym->ts.u.derived->attr.use_assoc
12125         && sym->ns->proc_name
12126         && sym->ns->proc_name->attr.flavor == FL_MODULE)
12127     {
12128       gfc_symbol *ds;
12129
12130       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
12131         return;
12132
12133       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
12134       if (!ds && sym->attr.function
12135             && gfc_check_access (sym->attr.access, sym->ns->default_access))
12136         {
12137           symtree = gfc_new_symtree (&sym->ns->sym_root,
12138                                      sym->ts.u.derived->name);
12139           symtree->n.sym = sym->ts.u.derived;
12140           sym->ts.u.derived->refs++;
12141         }
12142     }
12143
12144   /* Unless the derived-type declaration is use associated, Fortran 95
12145      does not allow public entries of private derived types.
12146      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
12147      161 in 95-006r3.  */
12148   if (sym->ts.type == BT_DERIVED
12149       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
12150       && !sym->ts.u.derived->attr.use_assoc
12151       && gfc_check_access (sym->attr.access, sym->ns->default_access)
12152       && !gfc_check_access (sym->ts.u.derived->attr.access,
12153                             sym->ts.u.derived->ns->default_access)
12154       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
12155                          "of PRIVATE derived type '%s'",
12156                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
12157                          : "variable", sym->name, &sym->declared_at,
12158                          sym->ts.u.derived->name) == FAILURE)
12159     return;
12160
12161   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
12162      default initialization is defined (5.1.2.4.4).  */
12163   if (sym->ts.type == BT_DERIVED
12164       && sym->attr.dummy
12165       && sym->attr.intent == INTENT_OUT
12166       && sym->as
12167       && sym->as->type == AS_ASSUMED_SIZE)
12168     {
12169       for (c = sym->ts.u.derived->components; c; c = c->next)
12170         {
12171           if (c->initializer)
12172             {
12173               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
12174                          "ASSUMED SIZE and so cannot have a default initializer",
12175                          sym->name, &sym->declared_at);
12176               return;
12177             }
12178         }
12179     }
12180
12181   /* F2008, C526.  */
12182   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12183        || sym->attr.codimension)
12184       && sym->attr.result)
12185     gfc_error ("Function result '%s' at %L shall not be a coarray or have "
12186                "a coarray component", sym->name, &sym->declared_at);
12187
12188   /* F2008, C524.  */
12189   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
12190       && sym->ts.u.derived->ts.is_iso_c)
12191     gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12192                "shall not be a coarray", sym->name, &sym->declared_at);
12193
12194   /* F2008, C525.  */
12195   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp
12196       && (sym->attr.codimension || sym->attr.pointer || sym->attr.dimension
12197           || sym->attr.allocatable))
12198     gfc_error ("Variable '%s' at %L with coarray component "
12199                "shall be a nonpointer, nonallocatable scalar",
12200                sym->name, &sym->declared_at);
12201
12202   /* F2008, C526.  The function-result case was handled above.  */
12203   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12204        || sym->attr.codimension)
12205       && !(sym->attr.allocatable || sym->attr.dummy || sym->attr.save
12206            || sym->ns->proc_name->attr.flavor == FL_MODULE
12207            || sym->ns->proc_name->attr.is_main_program
12208            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
12209     gfc_error ("Variable '%s' at %L is a coarray or has a coarray "
12210                "component and is not ALLOCATABLE, SAVE nor a "
12211                "dummy argument", sym->name, &sym->declared_at);
12212   /* F2008, C528.  */  /* FIXME: sym->as check due to PR 43412.  */
12213   else if (sym->attr.codimension && !sym->attr.allocatable
12214       && sym->as && sym->as->cotype == AS_DEFERRED)
12215     gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
12216                 "deferred shape", sym->name, &sym->declared_at);
12217   else if (sym->attr.codimension && sym->attr.allocatable
12218       && (sym->as->type != AS_DEFERRED || sym->as->cotype != AS_DEFERRED))
12219     gfc_error ("Allocatable coarray variable '%s' at %L must have "
12220                "deferred shape", sym->name, &sym->declared_at);
12221
12222
12223   /* F2008, C541.  */
12224   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12225        || (sym->attr.codimension && sym->attr.allocatable))
12226       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
12227     gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
12228                "allocatable coarray or have coarray components",
12229                sym->name, &sym->declared_at);
12230
12231   if (sym->attr.codimension && sym->attr.dummy
12232       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
12233     gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
12234                "procedure '%s'", sym->name, &sym->declared_at,
12235                sym->ns->proc_name->name);
12236
12237   switch (sym->attr.flavor)
12238     {
12239     case FL_VARIABLE:
12240       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
12241         return;
12242       break;
12243
12244     case FL_PROCEDURE:
12245       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
12246         return;
12247       break;
12248
12249     case FL_NAMELIST:
12250       if (resolve_fl_namelist (sym) == FAILURE)
12251         return;
12252       break;
12253
12254     case FL_PARAMETER:
12255       if (resolve_fl_parameter (sym) == FAILURE)
12256         return;
12257       break;
12258
12259     default:
12260       break;
12261     }
12262
12263   /* Resolve array specifier. Check as well some constraints
12264      on COMMON blocks.  */
12265
12266   check_constant = sym->attr.in_common && !sym->attr.pointer;
12267
12268   /* Set the formal_arg_flag so that check_conflict will not throw
12269      an error for host associated variables in the specification
12270      expression for an array_valued function.  */
12271   if (sym->attr.function && sym->as)
12272     formal_arg_flag = 1;
12273
12274   gfc_resolve_array_spec (sym->as, check_constant);
12275
12276   formal_arg_flag = 0;
12277
12278   /* Resolve formal namespaces.  */
12279   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
12280       && !sym->attr.contained && !sym->attr.intrinsic)
12281     gfc_resolve (sym->formal_ns);
12282
12283   /* Make sure the formal namespace is present.  */
12284   if (sym->formal && !sym->formal_ns)
12285     {
12286       gfc_formal_arglist *formal = sym->formal;
12287       while (formal && !formal->sym)
12288         formal = formal->next;
12289
12290       if (formal)
12291         {
12292           sym->formal_ns = formal->sym->ns;
12293           sym->formal_ns->refs++;
12294         }
12295     }
12296
12297   /* Check threadprivate restrictions.  */
12298   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
12299       && (!sym->attr.in_common
12300           && sym->module == NULL
12301           && (sym->ns->proc_name == NULL
12302               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
12303     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
12304
12305   /* If we have come this far we can apply default-initializers, as
12306      described in 14.7.5, to those variables that have not already
12307      been assigned one.  */
12308   if (sym->ts.type == BT_DERIVED
12309       && sym->ns == gfc_current_ns
12310       && !sym->value
12311       && !sym->attr.allocatable
12312       && !sym->attr.alloc_comp)
12313     {
12314       symbol_attribute *a = &sym->attr;
12315
12316       if ((!a->save && !a->dummy && !a->pointer
12317            && !a->in_common && !a->use_assoc
12318            && (a->referenced || a->result)
12319            && !(a->function && sym != sym->result))
12320           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
12321         apply_default_init (sym);
12322     }
12323
12324   if (sym->ts.type == BT_CLASS && sym->ns == gfc_current_ns
12325       && sym->attr.dummy && sym->attr.intent == INTENT_OUT
12326       && !CLASS_DATA (sym)->attr.class_pointer
12327       && !CLASS_DATA (sym)->attr.allocatable)
12328     apply_default_init (sym);
12329
12330   /* If this symbol has a type-spec, check it.  */
12331   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
12332       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
12333     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
12334           == FAILURE)
12335       return;
12336 }
12337
12338
12339 /************* Resolve DATA statements *************/
12340
12341 static struct
12342 {
12343   gfc_data_value *vnode;
12344   mpz_t left;
12345 }
12346 values;
12347
12348
12349 /* Advance the values structure to point to the next value in the data list.  */
12350
12351 static gfc_try
12352 next_data_value (void)
12353 {
12354   while (mpz_cmp_ui (values.left, 0) == 0)
12355     {
12356
12357       if (values.vnode->next == NULL)
12358         return FAILURE;
12359
12360       values.vnode = values.vnode->next;
12361       mpz_set (values.left, values.vnode->repeat);
12362     }
12363
12364   return SUCCESS;
12365 }
12366
12367
12368 static gfc_try
12369 check_data_variable (gfc_data_variable *var, locus *where)
12370 {
12371   gfc_expr *e;
12372   mpz_t size;
12373   mpz_t offset;
12374   gfc_try t;
12375   ar_type mark = AR_UNKNOWN;
12376   int i;
12377   mpz_t section_index[GFC_MAX_DIMENSIONS];
12378   gfc_ref *ref;
12379   gfc_array_ref *ar;
12380   gfc_symbol *sym;
12381   int has_pointer;
12382
12383   if (gfc_resolve_expr (var->expr) == FAILURE)
12384     return FAILURE;
12385
12386   ar = NULL;
12387   mpz_init_set_si (offset, 0);
12388   e = var->expr;
12389
12390   if (e->expr_type != EXPR_VARIABLE)
12391     gfc_internal_error ("check_data_variable(): Bad expression");
12392
12393   sym = e->symtree->n.sym;
12394
12395   if (sym->ns->is_block_data && !sym->attr.in_common)
12396     {
12397       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
12398                  sym->name, &sym->declared_at);
12399     }
12400
12401   if (e->ref == NULL && sym->as)
12402     {
12403       gfc_error ("DATA array '%s' at %L must be specified in a previous"
12404                  " declaration", sym->name, where);
12405       return FAILURE;
12406     }
12407
12408   has_pointer = sym->attr.pointer;
12409
12410   for (ref = e->ref; ref; ref = ref->next)
12411     {
12412       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
12413         has_pointer = 1;
12414
12415       if (ref->type == REF_ARRAY && ref->u.ar.codimen)
12416         {
12417           gfc_error ("DATA element '%s' at %L cannot have a coindex",
12418                      sym->name, where);
12419           return FAILURE;
12420         }
12421
12422       if (has_pointer
12423             && ref->type == REF_ARRAY
12424             && ref->u.ar.type != AR_FULL)
12425           {
12426             gfc_error ("DATA element '%s' at %L is a pointer and so must "
12427                         "be a full array", sym->name, where);
12428             return FAILURE;
12429           }
12430     }
12431
12432   if (e->rank == 0 || has_pointer)
12433     {
12434       mpz_init_set_ui (size, 1);
12435       ref = NULL;
12436     }
12437   else
12438     {
12439       ref = e->ref;
12440
12441       /* Find the array section reference.  */
12442       for (ref = e->ref; ref; ref = ref->next)
12443         {
12444           if (ref->type != REF_ARRAY)
12445             continue;
12446           if (ref->u.ar.type == AR_ELEMENT)
12447             continue;
12448           break;
12449         }
12450       gcc_assert (ref);
12451
12452       /* Set marks according to the reference pattern.  */
12453       switch (ref->u.ar.type)
12454         {
12455         case AR_FULL:
12456           mark = AR_FULL;
12457           break;
12458
12459         case AR_SECTION:
12460           ar = &ref->u.ar;
12461           /* Get the start position of array section.  */
12462           gfc_get_section_index (ar, section_index, &offset);
12463           mark = AR_SECTION;
12464           break;
12465
12466         default:
12467           gcc_unreachable ();
12468         }
12469
12470       if (gfc_array_size (e, &size) == FAILURE)
12471         {
12472           gfc_error ("Nonconstant array section at %L in DATA statement",
12473                      &e->where);
12474           mpz_clear (offset);
12475           return FAILURE;
12476         }
12477     }
12478
12479   t = SUCCESS;
12480
12481   while (mpz_cmp_ui (size, 0) > 0)
12482     {
12483       if (next_data_value () == FAILURE)
12484         {
12485           gfc_error ("DATA statement at %L has more variables than values",
12486                      where);
12487           t = FAILURE;
12488           break;
12489         }
12490
12491       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
12492       if (t == FAILURE)
12493         break;
12494
12495       /* If we have more than one element left in the repeat count,
12496          and we have more than one element left in the target variable,
12497          then create a range assignment.  */
12498       /* FIXME: Only done for full arrays for now, since array sections
12499          seem tricky.  */
12500       if (mark == AR_FULL && ref && ref->next == NULL
12501           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
12502         {
12503           mpz_t range;
12504
12505           if (mpz_cmp (size, values.left) >= 0)
12506             {
12507               mpz_init_set (range, values.left);
12508               mpz_sub (size, size, values.left);
12509               mpz_set_ui (values.left, 0);
12510             }
12511           else
12512             {
12513               mpz_init_set (range, size);
12514               mpz_sub (values.left, values.left, size);
12515               mpz_set_ui (size, 0);
12516             }
12517
12518           t = gfc_assign_data_value_range (var->expr, values.vnode->expr,
12519                                            offset, range);
12520
12521           mpz_add (offset, offset, range);
12522           mpz_clear (range);
12523
12524           if (t == FAILURE)
12525             break;
12526         }
12527
12528       /* Assign initial value to symbol.  */
12529       else
12530         {
12531           mpz_sub_ui (values.left, values.left, 1);
12532           mpz_sub_ui (size, size, 1);
12533
12534           t = gfc_assign_data_value (var->expr, values.vnode->expr, offset);
12535           if (t == FAILURE)
12536             break;
12537
12538           if (mark == AR_FULL)
12539             mpz_add_ui (offset, offset, 1);
12540
12541           /* Modify the array section indexes and recalculate the offset
12542              for next element.  */
12543           else if (mark == AR_SECTION)
12544             gfc_advance_section (section_index, ar, &offset);
12545         }
12546     }
12547
12548   if (mark == AR_SECTION)
12549     {
12550       for (i = 0; i < ar->dimen; i++)
12551         mpz_clear (section_index[i]);
12552     }
12553
12554   mpz_clear (size);
12555   mpz_clear (offset);
12556
12557   return t;
12558 }
12559
12560
12561 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
12562
12563 /* Iterate over a list of elements in a DATA statement.  */
12564
12565 static gfc_try
12566 traverse_data_list (gfc_data_variable *var, locus *where)
12567 {
12568   mpz_t trip;
12569   iterator_stack frame;
12570   gfc_expr *e, *start, *end, *step;
12571   gfc_try retval = SUCCESS;
12572
12573   mpz_init (frame.value);
12574   mpz_init (trip);
12575
12576   start = gfc_copy_expr (var->iter.start);
12577   end = gfc_copy_expr (var->iter.end);
12578   step = gfc_copy_expr (var->iter.step);
12579
12580   if (gfc_simplify_expr (start, 1) == FAILURE
12581       || start->expr_type != EXPR_CONSTANT)
12582     {
12583       gfc_error ("start of implied-do loop at %L could not be "
12584                  "simplified to a constant value", &start->where);
12585       retval = FAILURE;
12586       goto cleanup;
12587     }
12588   if (gfc_simplify_expr (end, 1) == FAILURE
12589       || end->expr_type != EXPR_CONSTANT)
12590     {
12591       gfc_error ("end of implied-do loop at %L could not be "
12592                  "simplified to a constant value", &start->where);
12593       retval = FAILURE;
12594       goto cleanup;
12595     }
12596   if (gfc_simplify_expr (step, 1) == FAILURE
12597       || step->expr_type != EXPR_CONSTANT)
12598     {
12599       gfc_error ("step of implied-do loop at %L could not be "
12600                  "simplified to a constant value", &start->where);
12601       retval = FAILURE;
12602       goto cleanup;
12603     }
12604
12605   mpz_set (trip, end->value.integer);
12606   mpz_sub (trip, trip, start->value.integer);
12607   mpz_add (trip, trip, step->value.integer);
12608
12609   mpz_div (trip, trip, step->value.integer);
12610
12611   mpz_set (frame.value, start->value.integer);
12612
12613   frame.prev = iter_stack;
12614   frame.variable = var->iter.var->symtree;
12615   iter_stack = &frame;
12616
12617   while (mpz_cmp_ui (trip, 0) > 0)
12618     {
12619       if (traverse_data_var (var->list, where) == FAILURE)
12620         {
12621           retval = FAILURE;
12622           goto cleanup;
12623         }
12624
12625       e = gfc_copy_expr (var->expr);
12626       if (gfc_simplify_expr (e, 1) == FAILURE)
12627         {
12628           gfc_free_expr (e);
12629           retval = FAILURE;
12630           goto cleanup;
12631         }
12632
12633       mpz_add (frame.value, frame.value, step->value.integer);
12634
12635       mpz_sub_ui (trip, trip, 1);
12636     }
12637
12638 cleanup:
12639   mpz_clear (frame.value);
12640   mpz_clear (trip);
12641
12642   gfc_free_expr (start);
12643   gfc_free_expr (end);
12644   gfc_free_expr (step);
12645
12646   iter_stack = frame.prev;
12647   return retval;
12648 }
12649
12650
12651 /* Type resolve variables in the variable list of a DATA statement.  */
12652
12653 static gfc_try
12654 traverse_data_var (gfc_data_variable *var, locus *where)
12655 {
12656   gfc_try t;
12657
12658   for (; var; var = var->next)
12659     {
12660       if (var->expr == NULL)
12661         t = traverse_data_list (var, where);
12662       else
12663         t = check_data_variable (var, where);
12664
12665       if (t == FAILURE)
12666         return FAILURE;
12667     }
12668
12669   return SUCCESS;
12670 }
12671
12672
12673 /* Resolve the expressions and iterators associated with a data statement.
12674    This is separate from the assignment checking because data lists should
12675    only be resolved once.  */
12676
12677 static gfc_try
12678 resolve_data_variables (gfc_data_variable *d)
12679 {
12680   for (; d; d = d->next)
12681     {
12682       if (d->list == NULL)
12683         {
12684           if (gfc_resolve_expr (d->expr) == FAILURE)
12685             return FAILURE;
12686         }
12687       else
12688         {
12689           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
12690             return FAILURE;
12691
12692           if (resolve_data_variables (d->list) == FAILURE)
12693             return FAILURE;
12694         }
12695     }
12696
12697   return SUCCESS;
12698 }
12699
12700
12701 /* Resolve a single DATA statement.  We implement this by storing a pointer to
12702    the value list into static variables, and then recursively traversing the
12703    variables list, expanding iterators and such.  */
12704
12705 static void
12706 resolve_data (gfc_data *d)
12707 {
12708
12709   if (resolve_data_variables (d->var) == FAILURE)
12710     return;
12711
12712   values.vnode = d->value;
12713   if (d->value == NULL)
12714     mpz_set_ui (values.left, 0);
12715   else
12716     mpz_set (values.left, d->value->repeat);
12717
12718   if (traverse_data_var (d->var, &d->where) == FAILURE)
12719     return;
12720
12721   /* At this point, we better not have any values left.  */
12722
12723   if (next_data_value () == SUCCESS)
12724     gfc_error ("DATA statement at %L has more values than variables",
12725                &d->where);
12726 }
12727
12728
12729 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
12730    accessed by host or use association, is a dummy argument to a pure function,
12731    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
12732    is storage associated with any such variable, shall not be used in the
12733    following contexts: (clients of this function).  */
12734
12735 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
12736    procedure.  Returns zero if assignment is OK, nonzero if there is a
12737    problem.  */
12738 int
12739 gfc_impure_variable (gfc_symbol *sym)
12740 {
12741   gfc_symbol *proc;
12742   gfc_namespace *ns;
12743
12744   if (sym->attr.use_assoc || sym->attr.in_common)
12745     return 1;
12746
12747   /* Check if the symbol's ns is inside the pure procedure.  */
12748   for (ns = gfc_current_ns; ns; ns = ns->parent)
12749     {
12750       if (ns == sym->ns)
12751         break;
12752       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
12753         return 1;
12754     }
12755
12756   proc = sym->ns->proc_name;
12757   if (sym->attr.dummy && gfc_pure (proc)
12758         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
12759                 ||
12760              proc->attr.function))
12761     return 1;
12762
12763   /* TODO: Sort out what can be storage associated, if anything, and include
12764      it here.  In principle equivalences should be scanned but it does not
12765      seem to be possible to storage associate an impure variable this way.  */
12766   return 0;
12767 }
12768
12769
12770 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
12771    current namespace is inside a pure procedure.  */
12772
12773 int
12774 gfc_pure (gfc_symbol *sym)
12775 {
12776   symbol_attribute attr;
12777   gfc_namespace *ns;
12778
12779   if (sym == NULL)
12780     {
12781       /* Check if the current namespace or one of its parents
12782         belongs to a pure procedure.  */
12783       for (ns = gfc_current_ns; ns; ns = ns->parent)
12784         {
12785           sym = ns->proc_name;
12786           if (sym == NULL)
12787             return 0;
12788           attr = sym->attr;
12789           if (attr.flavor == FL_PROCEDURE && attr.pure)
12790             return 1;
12791         }
12792       return 0;
12793     }
12794
12795   attr = sym->attr;
12796
12797   return attr.flavor == FL_PROCEDURE && attr.pure;
12798 }
12799
12800
12801 /* Test whether a symbol is implicitly pure or not.  For a NULL pointer,
12802    checks if the current namespace is implicitly pure.  Note that this
12803    function returns false for a PURE procedure.  */
12804
12805 int
12806 gfc_implicit_pure (gfc_symbol *sym)
12807 {
12808   symbol_attribute attr;
12809
12810   if (sym == NULL)
12811     {
12812       /* Check if the current namespace is implicit_pure.  */
12813       sym = gfc_current_ns->proc_name;
12814       if (sym == NULL)
12815         return 0;
12816       attr = sym->attr;
12817       if (attr.flavor == FL_PROCEDURE
12818             && attr.implicit_pure && !attr.pure)
12819         return 1;
12820       return 0;
12821     }
12822
12823   attr = sym->attr;
12824
12825   return attr.flavor == FL_PROCEDURE && attr.implicit_pure && !attr.pure;
12826 }
12827
12828
12829 /* Test whether the current procedure is elemental or not.  */
12830
12831 int
12832 gfc_elemental (gfc_symbol *sym)
12833 {
12834   symbol_attribute attr;
12835
12836   if (sym == NULL)
12837     sym = gfc_current_ns->proc_name;
12838   if (sym == NULL)
12839     return 0;
12840   attr = sym->attr;
12841
12842   return attr.flavor == FL_PROCEDURE && attr.elemental;
12843 }
12844
12845
12846 /* Warn about unused labels.  */
12847
12848 static void
12849 warn_unused_fortran_label (gfc_st_label *label)
12850 {
12851   if (label == NULL)
12852     return;
12853
12854   warn_unused_fortran_label (label->left);
12855
12856   if (label->defined == ST_LABEL_UNKNOWN)
12857     return;
12858
12859   switch (label->referenced)
12860     {
12861     case ST_LABEL_UNKNOWN:
12862       gfc_warning ("Label %d at %L defined but not used", label->value,
12863                    &label->where);
12864       break;
12865
12866     case ST_LABEL_BAD_TARGET:
12867       gfc_warning ("Label %d at %L defined but cannot be used",
12868                    label->value, &label->where);
12869       break;
12870
12871     default:
12872       break;
12873     }
12874
12875   warn_unused_fortran_label (label->right);
12876 }
12877
12878
12879 /* Returns the sequence type of a symbol or sequence.  */
12880
12881 static seq_type
12882 sequence_type (gfc_typespec ts)
12883 {
12884   seq_type result;
12885   gfc_component *c;
12886
12887   switch (ts.type)
12888   {
12889     case BT_DERIVED:
12890
12891       if (ts.u.derived->components == NULL)
12892         return SEQ_NONDEFAULT;
12893
12894       result = sequence_type (ts.u.derived->components->ts);
12895       for (c = ts.u.derived->components->next; c; c = c->next)
12896         if (sequence_type (c->ts) != result)
12897           return SEQ_MIXED;
12898
12899       return result;
12900
12901     case BT_CHARACTER:
12902       if (ts.kind != gfc_default_character_kind)
12903           return SEQ_NONDEFAULT;
12904
12905       return SEQ_CHARACTER;
12906
12907     case BT_INTEGER:
12908       if (ts.kind != gfc_default_integer_kind)
12909           return SEQ_NONDEFAULT;
12910
12911       return SEQ_NUMERIC;
12912
12913     case BT_REAL:
12914       if (!(ts.kind == gfc_default_real_kind
12915             || ts.kind == gfc_default_double_kind))
12916           return SEQ_NONDEFAULT;
12917
12918       return SEQ_NUMERIC;
12919
12920     case BT_COMPLEX:
12921       if (ts.kind != gfc_default_complex_kind)
12922           return SEQ_NONDEFAULT;
12923
12924       return SEQ_NUMERIC;
12925
12926     case BT_LOGICAL:
12927       if (ts.kind != gfc_default_logical_kind)
12928           return SEQ_NONDEFAULT;
12929
12930       return SEQ_NUMERIC;
12931
12932     default:
12933       return SEQ_NONDEFAULT;
12934   }
12935 }
12936
12937
12938 /* Resolve derived type EQUIVALENCE object.  */
12939
12940 static gfc_try
12941 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
12942 {
12943   gfc_component *c = derived->components;
12944
12945   if (!derived)
12946     return SUCCESS;
12947
12948   /* Shall not be an object of nonsequence derived type.  */
12949   if (!derived->attr.sequence)
12950     {
12951       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
12952                  "attribute to be an EQUIVALENCE object", sym->name,
12953                  &e->where);
12954       return FAILURE;
12955     }
12956
12957   /* Shall not have allocatable components.  */
12958   if (derived->attr.alloc_comp)
12959     {
12960       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
12961                  "components to be an EQUIVALENCE object",sym->name,
12962                  &e->where);
12963       return FAILURE;
12964     }
12965
12966   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
12967     {
12968       gfc_error ("Derived type variable '%s' at %L with default "
12969                  "initialization cannot be in EQUIVALENCE with a variable "
12970                  "in COMMON", sym->name, &e->where);
12971       return FAILURE;
12972     }
12973
12974   for (; c ; c = c->next)
12975     {
12976       if (c->ts.type == BT_DERIVED
12977           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
12978         return FAILURE;
12979
12980       /* Shall not be an object of sequence derived type containing a pointer
12981          in the structure.  */
12982       if (c->attr.pointer)
12983         {
12984           gfc_error ("Derived type variable '%s' at %L with pointer "
12985                      "component(s) cannot be an EQUIVALENCE object",
12986                      sym->name, &e->where);
12987           return FAILURE;
12988         }
12989     }
12990   return SUCCESS;
12991 }
12992
12993
12994 /* Resolve equivalence object. 
12995    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
12996    an allocatable array, an object of nonsequence derived type, an object of
12997    sequence derived type containing a pointer at any level of component
12998    selection, an automatic object, a function name, an entry name, a result
12999    name, a named constant, a structure component, or a subobject of any of
13000    the preceding objects.  A substring shall not have length zero.  A
13001    derived type shall not have components with default initialization nor
13002    shall two objects of an equivalence group be initialized.
13003    Either all or none of the objects shall have an protected attribute.
13004    The simple constraints are done in symbol.c(check_conflict) and the rest
13005    are implemented here.  */
13006
13007 static void
13008 resolve_equivalence (gfc_equiv *eq)
13009 {
13010   gfc_symbol *sym;
13011   gfc_symbol *first_sym;
13012   gfc_expr *e;
13013   gfc_ref *r;
13014   locus *last_where = NULL;
13015   seq_type eq_type, last_eq_type;
13016   gfc_typespec *last_ts;
13017   int object, cnt_protected;
13018   const char *msg;
13019
13020   last_ts = &eq->expr->symtree->n.sym->ts;
13021
13022   first_sym = eq->expr->symtree->n.sym;
13023
13024   cnt_protected = 0;
13025
13026   for (object = 1; eq; eq = eq->eq, object++)
13027     {
13028       e = eq->expr;
13029
13030       e->ts = e->symtree->n.sym->ts;
13031       /* match_varspec might not know yet if it is seeing
13032          array reference or substring reference, as it doesn't
13033          know the types.  */
13034       if (e->ref && e->ref->type == REF_ARRAY)
13035         {
13036           gfc_ref *ref = e->ref;
13037           sym = e->symtree->n.sym;
13038
13039           if (sym->attr.dimension)
13040             {
13041               ref->u.ar.as = sym->as;
13042               ref = ref->next;
13043             }
13044
13045           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
13046           if (e->ts.type == BT_CHARACTER
13047               && ref
13048               && ref->type == REF_ARRAY
13049               && ref->u.ar.dimen == 1
13050               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
13051               && ref->u.ar.stride[0] == NULL)
13052             {
13053               gfc_expr *start = ref->u.ar.start[0];
13054               gfc_expr *end = ref->u.ar.end[0];
13055               void *mem = NULL;
13056
13057               /* Optimize away the (:) reference.  */
13058               if (start == NULL && end == NULL)
13059                 {
13060                   if (e->ref == ref)
13061                     e->ref = ref->next;
13062                   else
13063                     e->ref->next = ref->next;
13064                   mem = ref;
13065                 }
13066               else
13067                 {
13068                   ref->type = REF_SUBSTRING;
13069                   if (start == NULL)
13070                     start = gfc_get_int_expr (gfc_default_integer_kind,
13071                                               NULL, 1);
13072                   ref->u.ss.start = start;
13073                   if (end == NULL && e->ts.u.cl)
13074                     end = gfc_copy_expr (e->ts.u.cl->length);
13075                   ref->u.ss.end = end;
13076                   ref->u.ss.length = e->ts.u.cl;
13077                   e->ts.u.cl = NULL;
13078                 }
13079               ref = ref->next;
13080               gfc_free (mem);
13081             }
13082
13083           /* Any further ref is an error.  */
13084           if (ref)
13085             {
13086               gcc_assert (ref->type == REF_ARRAY);
13087               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
13088                          &ref->u.ar.where);
13089               continue;
13090             }
13091         }
13092
13093       if (gfc_resolve_expr (e) == FAILURE)
13094         continue;
13095
13096       sym = e->symtree->n.sym;
13097
13098       if (sym->attr.is_protected)
13099         cnt_protected++;
13100       if (cnt_protected > 0 && cnt_protected != object)
13101         {
13102               gfc_error ("Either all or none of the objects in the "
13103                          "EQUIVALENCE set at %L shall have the "
13104                          "PROTECTED attribute",
13105                          &e->where);
13106               break;
13107         }
13108
13109       /* Shall not equivalence common block variables in a PURE procedure.  */
13110       if (sym->ns->proc_name
13111           && sym->ns->proc_name->attr.pure
13112           && sym->attr.in_common)
13113         {
13114           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
13115                      "object in the pure procedure '%s'",
13116                      sym->name, &e->where, sym->ns->proc_name->name);
13117           break;
13118         }
13119
13120       /* Shall not be a named constant.  */
13121       if (e->expr_type == EXPR_CONSTANT)
13122         {
13123           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
13124                      "object", sym->name, &e->where);
13125           continue;
13126         }
13127
13128       if (e->ts.type == BT_DERIVED
13129           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
13130         continue;
13131
13132       /* Check that the types correspond correctly:
13133          Note 5.28:
13134          A numeric sequence structure may be equivalenced to another sequence
13135          structure, an object of default integer type, default real type, double
13136          precision real type, default logical type such that components of the
13137          structure ultimately only become associated to objects of the same
13138          kind. A character sequence structure may be equivalenced to an object
13139          of default character kind or another character sequence structure.
13140          Other objects may be equivalenced only to objects of the same type and
13141          kind parameters.  */
13142
13143       /* Identical types are unconditionally OK.  */
13144       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
13145         goto identical_types;
13146
13147       last_eq_type = sequence_type (*last_ts);
13148       eq_type = sequence_type (sym->ts);
13149
13150       /* Since the pair of objects is not of the same type, mixed or
13151          non-default sequences can be rejected.  */
13152
13153       msg = "Sequence %s with mixed components in EQUIVALENCE "
13154             "statement at %L with different type objects";
13155       if ((object ==2
13156            && last_eq_type == SEQ_MIXED
13157            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
13158               == FAILURE)
13159           || (eq_type == SEQ_MIXED
13160               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13161                                  &e->where) == FAILURE))
13162         continue;
13163
13164       msg = "Non-default type object or sequence %s in EQUIVALENCE "
13165             "statement at %L with objects of different type";
13166       if ((object ==2
13167            && last_eq_type == SEQ_NONDEFAULT
13168            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
13169                               last_where) == FAILURE)
13170           || (eq_type == SEQ_NONDEFAULT
13171               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13172                                  &e->where) == FAILURE))
13173         continue;
13174
13175       msg ="Non-CHARACTER object '%s' in default CHARACTER "
13176            "EQUIVALENCE statement at %L";
13177       if (last_eq_type == SEQ_CHARACTER
13178           && eq_type != SEQ_CHARACTER
13179           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13180                              &e->where) == FAILURE)
13181                 continue;
13182
13183       msg ="Non-NUMERIC object '%s' in default NUMERIC "
13184            "EQUIVALENCE statement at %L";
13185       if (last_eq_type == SEQ_NUMERIC
13186           && eq_type != SEQ_NUMERIC
13187           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13188                              &e->where) == FAILURE)
13189                 continue;
13190
13191   identical_types:
13192       last_ts =&sym->ts;
13193       last_where = &e->where;
13194
13195       if (!e->ref)
13196         continue;
13197
13198       /* Shall not be an automatic array.  */
13199       if (e->ref->type == REF_ARRAY
13200           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
13201         {
13202           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
13203                      "an EQUIVALENCE object", sym->name, &e->where);
13204           continue;
13205         }
13206
13207       r = e->ref;
13208       while (r)
13209         {
13210           /* Shall not be a structure component.  */
13211           if (r->type == REF_COMPONENT)
13212             {
13213               gfc_error ("Structure component '%s' at %L cannot be an "
13214                          "EQUIVALENCE object",
13215                          r->u.c.component->name, &e->where);
13216               break;
13217             }
13218
13219           /* A substring shall not have length zero.  */
13220           if (r->type == REF_SUBSTRING)
13221             {
13222               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
13223                 {
13224                   gfc_error ("Substring at %L has length zero",
13225                              &r->u.ss.start->where);
13226                   break;
13227                 }
13228             }
13229           r = r->next;
13230         }
13231     }
13232 }
13233
13234
13235 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
13236
13237 static void
13238 resolve_fntype (gfc_namespace *ns)
13239 {
13240   gfc_entry_list *el;
13241   gfc_symbol *sym;
13242
13243   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
13244     return;
13245
13246   /* If there are any entries, ns->proc_name is the entry master
13247      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
13248   if (ns->entries)
13249     sym = ns->entries->sym;
13250   else
13251     sym = ns->proc_name;
13252   if (sym->result == sym
13253       && sym->ts.type == BT_UNKNOWN
13254       && gfc_set_default_type (sym, 0, NULL) == FAILURE
13255       && !sym->attr.untyped)
13256     {
13257       gfc_error ("Function '%s' at %L has no IMPLICIT type",
13258                  sym->name, &sym->declared_at);
13259       sym->attr.untyped = 1;
13260     }
13261
13262   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
13263       && !sym->attr.contained
13264       && !gfc_check_access (sym->ts.u.derived->attr.access,
13265                             sym->ts.u.derived->ns->default_access)
13266       && gfc_check_access (sym->attr.access, sym->ns->default_access))
13267     {
13268       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
13269                       "%L of PRIVATE type '%s'", sym->name,
13270                       &sym->declared_at, sym->ts.u.derived->name);
13271     }
13272
13273     if (ns->entries)
13274     for (el = ns->entries->next; el; el = el->next)
13275       {
13276         if (el->sym->result == el->sym
13277             && el->sym->ts.type == BT_UNKNOWN
13278             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
13279             && !el->sym->attr.untyped)
13280           {
13281             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
13282                        el->sym->name, &el->sym->declared_at);
13283             el->sym->attr.untyped = 1;
13284           }
13285       }
13286 }
13287
13288
13289 /* 12.3.2.1.1 Defined operators.  */
13290
13291 static gfc_try
13292 check_uop_procedure (gfc_symbol *sym, locus where)
13293 {
13294   gfc_formal_arglist *formal;
13295
13296   if (!sym->attr.function)
13297     {
13298       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
13299                  sym->name, &where);
13300       return FAILURE;
13301     }
13302
13303   if (sym->ts.type == BT_CHARACTER
13304       && !(sym->ts.u.cl && sym->ts.u.cl->length)
13305       && !(sym->result && sym->result->ts.u.cl
13306            && sym->result->ts.u.cl->length))
13307     {
13308       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
13309                  "character length", sym->name, &where);
13310       return FAILURE;
13311     }
13312
13313   formal = sym->formal;
13314   if (!formal || !formal->sym)
13315     {
13316       gfc_error ("User operator procedure '%s' at %L must have at least "
13317                  "one argument", sym->name, &where);
13318       return FAILURE;
13319     }
13320
13321   if (formal->sym->attr.intent != INTENT_IN)
13322     {
13323       gfc_error ("First argument of operator interface at %L must be "
13324                  "INTENT(IN)", &where);
13325       return FAILURE;
13326     }
13327
13328   if (formal->sym->attr.optional)
13329     {
13330       gfc_error ("First argument of operator interface at %L cannot be "
13331                  "optional", &where);
13332       return FAILURE;
13333     }
13334
13335   formal = formal->next;
13336   if (!formal || !formal->sym)
13337     return SUCCESS;
13338
13339   if (formal->sym->attr.intent != INTENT_IN)
13340     {
13341       gfc_error ("Second argument of operator interface at %L must be "
13342                  "INTENT(IN)", &where);
13343       return FAILURE;
13344     }
13345
13346   if (formal->sym->attr.optional)
13347     {
13348       gfc_error ("Second argument of operator interface at %L cannot be "
13349                  "optional", &where);
13350       return FAILURE;
13351     }
13352
13353   if (formal->next)
13354     {
13355       gfc_error ("Operator interface at %L must have, at most, two "
13356                  "arguments", &where);
13357       return FAILURE;
13358     }
13359
13360   return SUCCESS;
13361 }
13362
13363 static void
13364 gfc_resolve_uops (gfc_symtree *symtree)
13365 {
13366   gfc_interface *itr;
13367
13368   if (symtree == NULL)
13369     return;
13370
13371   gfc_resolve_uops (symtree->left);
13372   gfc_resolve_uops (symtree->right);
13373
13374   for (itr = symtree->n.uop->op; itr; itr = itr->next)
13375     check_uop_procedure (itr->sym, itr->sym->declared_at);
13376 }
13377
13378
13379 /* Examine all of the expressions associated with a program unit,
13380    assign types to all intermediate expressions, make sure that all
13381    assignments are to compatible types and figure out which names
13382    refer to which functions or subroutines.  It doesn't check code
13383    block, which is handled by resolve_code.  */
13384
13385 static void
13386 resolve_types (gfc_namespace *ns)
13387 {
13388   gfc_namespace *n;
13389   gfc_charlen *cl;
13390   gfc_data *d;
13391   gfc_equiv *eq;
13392   gfc_namespace* old_ns = gfc_current_ns;
13393
13394   /* Check that all IMPLICIT types are ok.  */
13395   if (!ns->seen_implicit_none)
13396     {
13397       unsigned letter;
13398       for (letter = 0; letter != GFC_LETTERS; ++letter)
13399         if (ns->set_flag[letter]
13400             && resolve_typespec_used (&ns->default_type[letter],
13401                                       &ns->implicit_loc[letter],
13402                                       NULL) == FAILURE)
13403           return;
13404     }
13405
13406   gfc_current_ns = ns;
13407
13408   resolve_entries (ns);
13409
13410   resolve_common_vars (ns->blank_common.head, false);
13411   resolve_common_blocks (ns->common_root);
13412
13413   resolve_contained_functions (ns);
13414
13415   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
13416
13417   for (cl = ns->cl_list; cl; cl = cl->next)
13418     resolve_charlen (cl);
13419
13420   gfc_traverse_ns (ns, resolve_symbol);
13421
13422   resolve_fntype (ns);
13423
13424   for (n = ns->contained; n; n = n->sibling)
13425     {
13426       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
13427         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
13428                    "also be PURE", n->proc_name->name,
13429                    &n->proc_name->declared_at);
13430
13431       resolve_types (n);
13432     }
13433
13434   forall_flag = 0;
13435   gfc_check_interfaces (ns);
13436
13437   gfc_traverse_ns (ns, resolve_values);
13438
13439   if (ns->save_all)
13440     gfc_save_all (ns);
13441
13442   iter_stack = NULL;
13443   for (d = ns->data; d; d = d->next)
13444     resolve_data (d);
13445
13446   iter_stack = NULL;
13447   gfc_traverse_ns (ns, gfc_formalize_init_value);
13448
13449   gfc_traverse_ns (ns, gfc_verify_binding_labels);
13450
13451   if (ns->common_root != NULL)
13452     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
13453
13454   for (eq = ns->equiv; eq; eq = eq->next)
13455     resolve_equivalence (eq);
13456
13457   /* Warn about unused labels.  */
13458   if (warn_unused_label)
13459     warn_unused_fortran_label (ns->st_labels);
13460
13461   gfc_resolve_uops (ns->uop_root);
13462
13463   gfc_current_ns = old_ns;
13464 }
13465
13466
13467 /* Call resolve_code recursively.  */
13468
13469 static void
13470 resolve_codes (gfc_namespace *ns)
13471 {
13472   gfc_namespace *n;
13473   bitmap_obstack old_obstack;
13474
13475   if (ns->resolved == 1)
13476     return;
13477
13478   for (n = ns->contained; n; n = n->sibling)
13479     resolve_codes (n);
13480
13481   gfc_current_ns = ns;
13482
13483   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
13484   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
13485     cs_base = NULL;
13486
13487   /* Set to an out of range value.  */
13488   current_entry_id = -1;
13489
13490   old_obstack = labels_obstack;
13491   bitmap_obstack_initialize (&labels_obstack);
13492
13493   resolve_code (ns->code, ns);
13494
13495   bitmap_obstack_release (&labels_obstack);
13496   labels_obstack = old_obstack;
13497 }
13498
13499
13500 /* This function is called after a complete program unit has been compiled.
13501    Its purpose is to examine all of the expressions associated with a program
13502    unit, assign types to all intermediate expressions, make sure that all
13503    assignments are to compatible types and figure out which names refer to
13504    which functions or subroutines.  */
13505
13506 void
13507 gfc_resolve (gfc_namespace *ns)
13508 {
13509   gfc_namespace *old_ns;
13510   code_stack *old_cs_base;
13511
13512   if (ns->resolved)
13513     return;
13514
13515   ns->resolved = -1;
13516   old_ns = gfc_current_ns;
13517   old_cs_base = cs_base;
13518
13519   resolve_types (ns);
13520   resolve_codes (ns);
13521
13522   gfc_current_ns = old_ns;
13523   cs_base = old_cs_base;
13524   ns->resolved = 1;
13525
13526   gfc_run_passes (ns);
13527 }