OSDN Git Service

2011-08-16 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / fortran / resolve.c
1 /* Perform type resolution on the various structures.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009,
3    2010, 2011
4    Free Software Foundation, Inc.
5    Contributed by Andy Vaught
6
7 This file is part of GCC.
8
9 GCC is free software; you can redistribute it and/or modify it under
10 the terms of the GNU General Public License as published by the Free
11 Software Foundation; either version 3, or (at your option) any later
12 version.
13
14 GCC is distributed in the hope that it will be useful, but WITHOUT ANY
15 WARRANTY; without even the implied warranty of MERCHANTABILITY or
16 FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
17 for more details.
18
19 You should have received a copy of the GNU General Public License
20 along with GCC; see the file COPYING3.  If not see
21 <http://www.gnu.org/licenses/>.  */
22
23 #include "config.h"
24 #include "system.h"
25 #include "flags.h"
26 #include "gfortran.h"
27 #include "obstack.h"
28 #include "bitmap.h"
29 #include "arith.h"  /* For gfc_compare_expr().  */
30 #include "dependency.h"
31 #include "data.h"
32 #include "target-memory.h" /* for gfc_simplify_transfer */
33 #include "constructor.h"
34
35 /* Types used in equivalence statements.  */
36
37 typedef enum seq_type
38 {
39   SEQ_NONDEFAULT, SEQ_NUMERIC, SEQ_CHARACTER, SEQ_MIXED
40 }
41 seq_type;
42
43 /* Stack to keep track of the nesting of blocks as we move through the
44    code.  See resolve_branch() and resolve_code().  */
45
46 typedef struct code_stack
47 {
48   struct gfc_code *head, *current;
49   struct code_stack *prev;
50
51   /* This bitmap keeps track of the targets valid for a branch from
52      inside this block except for END {IF|SELECT}s of enclosing
53      blocks.  */
54   bitmap reachable_labels;
55 }
56 code_stack;
57
58 static code_stack *cs_base = NULL;
59
60
61 /* Nonzero if we're inside a FORALL block.  */
62
63 static int forall_flag;
64
65 /* Nonzero if we're inside a OpenMP WORKSHARE or PARALLEL WORKSHARE block.  */
66
67 static int omp_workshare_flag;
68
69 /* Nonzero if we are processing a formal arglist. The corresponding function
70    resets the flag each time that it is read.  */
71 static int formal_arg_flag = 0;
72
73 /* True if we are resolving a specification expression.  */
74 static int specification_expr = 0;
75
76 /* The id of the last entry seen.  */
77 static int current_entry_id;
78
79 /* We use bitmaps to determine if a branch target is valid.  */
80 static bitmap_obstack labels_obstack;
81
82 /* True when simplifying a EXPR_VARIABLE argument to an inquiry function.  */
83 static bool inquiry_argument = false;
84
85 int
86 gfc_is_formal_arg (void)
87 {
88   return formal_arg_flag;
89 }
90
91 /* Is the symbol host associated?  */
92 static bool
93 is_sym_host_assoc (gfc_symbol *sym, gfc_namespace *ns)
94 {
95   for (ns = ns->parent; ns; ns = ns->parent)
96     {      
97       if (sym->ns == ns)
98         return true;
99     }
100
101   return false;
102 }
103
104 /* Ensure a typespec used is valid; for instance, TYPE(t) is invalid if t is
105    an ABSTRACT derived-type.  If where is not NULL, an error message with that
106    locus is printed, optionally using name.  */
107
108 static gfc_try
109 resolve_typespec_used (gfc_typespec* ts, locus* where, const char* name)
110 {
111   if (ts->type == BT_DERIVED && ts->u.derived->attr.abstract)
112     {
113       if (where)
114         {
115           if (name)
116             gfc_error ("'%s' at %L is of the ABSTRACT type '%s'",
117                        name, where, ts->u.derived->name);
118           else
119             gfc_error ("ABSTRACT type '%s' used at %L",
120                        ts->u.derived->name, where);
121         }
122
123       return FAILURE;
124     }
125
126   return SUCCESS;
127 }
128
129
130 static void resolve_symbol (gfc_symbol *sym);
131 static gfc_try resolve_intrinsic (gfc_symbol *sym, locus *loc);
132
133
134 /* Resolve the interface for a PROCEDURE declaration or procedure pointer.  */
135
136 static gfc_try
137 resolve_procedure_interface (gfc_symbol *sym)
138 {
139   if (sym->ts.interface == sym)
140     {
141       gfc_error ("PROCEDURE '%s' at %L may not be used as its own interface",
142                  sym->name, &sym->declared_at);
143       return FAILURE;
144     }
145   if (sym->ts.interface->attr.procedure)
146     {
147       gfc_error ("Interface '%s', used by procedure '%s' at %L, is declared "
148                  "in a later PROCEDURE statement", sym->ts.interface->name,
149                  sym->name, &sym->declared_at);
150       return FAILURE;
151     }
152
153   /* Get the attributes from the interface (now resolved).  */
154   if (sym->ts.interface->attr.if_source || sym->ts.interface->attr.intrinsic)
155     {
156       gfc_symbol *ifc = sym->ts.interface;
157       resolve_symbol (ifc);
158
159       if (ifc->attr.intrinsic)
160         resolve_intrinsic (ifc, &ifc->declared_at);
161
162       if (ifc->result)
163         {
164           sym->ts = ifc->result->ts;
165           sym->result = sym;
166         }
167       else   
168         sym->ts = ifc->ts;
169       sym->ts.interface = ifc;
170       sym->attr.function = ifc->attr.function;
171       sym->attr.subroutine = ifc->attr.subroutine;
172       gfc_copy_formal_args (sym, ifc);
173
174       sym->attr.allocatable = ifc->attr.allocatable;
175       sym->attr.pointer = ifc->attr.pointer;
176       sym->attr.pure = ifc->attr.pure;
177       sym->attr.elemental = ifc->attr.elemental;
178       sym->attr.dimension = ifc->attr.dimension;
179       sym->attr.contiguous = ifc->attr.contiguous;
180       sym->attr.recursive = ifc->attr.recursive;
181       sym->attr.always_explicit = ifc->attr.always_explicit;
182       sym->attr.ext_attr |= ifc->attr.ext_attr;
183       sym->attr.is_bind_c = ifc->attr.is_bind_c;
184       /* Copy array spec.  */
185       sym->as = gfc_copy_array_spec (ifc->as);
186       if (sym->as)
187         {
188           int i;
189           for (i = 0; i < sym->as->rank; i++)
190             {
191               gfc_expr_replace_symbols (sym->as->lower[i], sym);
192               gfc_expr_replace_symbols (sym->as->upper[i], sym);
193             }
194         }
195       /* Copy char length.  */
196       if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
197         {
198           sym->ts.u.cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
199           gfc_expr_replace_symbols (sym->ts.u.cl->length, sym);
200           if (sym->ts.u.cl->length && !sym->ts.u.cl->resolved
201               && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
202             return FAILURE;
203         }
204     }
205   else if (sym->ts.interface->name[0] != '\0')
206     {
207       gfc_error ("Interface '%s' of procedure '%s' at %L must be explicit",
208                  sym->ts.interface->name, sym->name, &sym->declared_at);
209       return FAILURE;
210     }
211
212   return SUCCESS;
213 }
214
215
216 /* Resolve types of formal argument lists.  These have to be done early so that
217    the formal argument lists of module procedures can be copied to the
218    containing module before the individual procedures are resolved
219    individually.  We also resolve argument lists of procedures in interface
220    blocks because they are self-contained scoping units.
221
222    Since a dummy argument cannot be a non-dummy procedure, the only
223    resort left for untyped names are the IMPLICIT types.  */
224
225 static void
226 resolve_formal_arglist (gfc_symbol *proc)
227 {
228   gfc_formal_arglist *f;
229   gfc_symbol *sym;
230   int i;
231
232   if (proc->result != NULL)
233     sym = proc->result;
234   else
235     sym = proc;
236
237   if (gfc_elemental (proc)
238       || sym->attr.pointer || sym->attr.allocatable
239       || (sym->as && sym->as->rank > 0))
240     {
241       proc->attr.always_explicit = 1;
242       sym->attr.always_explicit = 1;
243     }
244
245   formal_arg_flag = 1;
246
247   for (f = proc->formal; f; f = f->next)
248     {
249       sym = f->sym;
250
251       if (sym == NULL)
252         {
253           /* Alternate return placeholder.  */
254           if (gfc_elemental (proc))
255             gfc_error ("Alternate return specifier in elemental subroutine "
256                        "'%s' at %L is not allowed", proc->name,
257                        &proc->declared_at);
258           if (proc->attr.function)
259             gfc_error ("Alternate return specifier in function "
260                        "'%s' at %L is not allowed", proc->name,
261                        &proc->declared_at);
262           continue;
263         }
264       else if (sym->attr.procedure && sym->ts.interface
265                && sym->attr.if_source != IFSRC_DECL)
266         resolve_procedure_interface (sym);
267
268       if (sym->attr.if_source != IFSRC_UNKNOWN)
269         resolve_formal_arglist (sym);
270
271       if (sym->attr.subroutine || sym->attr.external || sym->attr.intrinsic)
272         {
273           if (gfc_pure (proc) && !gfc_pure (sym))
274             {
275               gfc_error ("Dummy procedure '%s' of PURE procedure at %L must "
276                          "also be PURE", sym->name, &sym->declared_at);
277               continue;
278             }
279
280           if (proc->attr.implicit_pure && !gfc_pure(sym))
281             proc->attr.implicit_pure = 0;
282
283           if (gfc_elemental (proc))
284             {
285               gfc_error ("Dummy procedure at %L not allowed in ELEMENTAL "
286                          "procedure", &sym->declared_at);
287               continue;
288             }
289
290           if (sym->attr.function
291                 && sym->ts.type == BT_UNKNOWN
292                 && sym->attr.intrinsic)
293             {
294               gfc_intrinsic_sym *isym;
295               isym = gfc_find_function (sym->name);
296               if (isym == NULL || !isym->specific)
297                 {
298                   gfc_error ("Unable to find a specific INTRINSIC procedure "
299                              "for the reference '%s' at %L", sym->name,
300                              &sym->declared_at);
301                 }
302               sym->ts = isym->ts;
303             }
304
305           continue;
306         }
307
308       if (sym->ts.type == BT_UNKNOWN && !proc->attr.intrinsic
309           && (!sym->attr.function || sym->result == sym))
310         gfc_set_default_type (sym, 1, sym->ns);
311
312       gfc_resolve_array_spec (sym->as, 0);
313
314       /* We can't tell if an array with dimension (:) is assumed or deferred
315          shape until we know if it has the pointer or allocatable attributes.
316       */
317       if (sym->as && sym->as->rank > 0 && sym->as->type == AS_DEFERRED
318           && !(sym->attr.pointer || sym->attr.allocatable)
319           && sym->attr.flavor != FL_PROCEDURE)
320         {
321           sym->as->type = AS_ASSUMED_SHAPE;
322           for (i = 0; i < sym->as->rank; i++)
323             sym->as->lower[i] = gfc_get_int_expr (gfc_default_integer_kind,
324                                                   NULL, 1);
325         }
326
327       if ((sym->as && sym->as->rank > 0 && sym->as->type == AS_ASSUMED_SHAPE)
328           || sym->attr.pointer || sym->attr.allocatable || sym->attr.target
329           || sym->attr.optional)
330         {
331           proc->attr.always_explicit = 1;
332           if (proc->result)
333             proc->result->attr.always_explicit = 1;
334         }
335
336       /* If the flavor is unknown at this point, it has to be a variable.
337          A procedure specification would have already set the type.  */
338
339       if (sym->attr.flavor == FL_UNKNOWN)
340         gfc_add_flavor (&sym->attr, FL_VARIABLE, sym->name, &sym->declared_at);
341
342       if (gfc_pure (proc) && !sym->attr.pointer
343           && sym->attr.flavor != FL_PROCEDURE)
344         {
345           if (proc->attr.function && sym->attr.intent != INTENT_IN)
346             {
347               if (sym->attr.value)
348                 gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s' "
349                                 "of pure function '%s' at %L with VALUE "
350                                 "attribute but without INTENT(IN)", sym->name,
351                                 proc->name, &sym->declared_at);
352               else
353                 gfc_error ("Argument '%s' of pure function '%s' at %L must be "
354                            "INTENT(IN) or VALUE", sym->name, proc->name,
355                            &sym->declared_at);
356             }
357
358           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
359             {
360               if (sym->attr.value)
361                 gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Argument '%s' "
362                                 "of pure subroutine '%s' at %L with VALUE "
363                                 "attribute but without INTENT", sym->name,
364                                 proc->name, &sym->declared_at);
365               else
366                 gfc_error ("Argument '%s' of pure subroutine '%s' at %L must "
367                        "have its INTENT specified or have the VALUE "
368                        "attribute", sym->name, proc->name, &sym->declared_at);
369             }
370         }
371
372       if (proc->attr.implicit_pure && !sym->attr.pointer
373           && sym->attr.flavor != FL_PROCEDURE)
374         {
375           if (proc->attr.function && sym->attr.intent != INTENT_IN)
376             proc->attr.implicit_pure = 0;
377
378           if (proc->attr.subroutine && sym->attr.intent == INTENT_UNKNOWN)
379             proc->attr.implicit_pure = 0;
380         }
381
382       if (gfc_elemental (proc))
383         {
384           /* F2008, C1289.  */
385           if (sym->attr.codimension)
386             {
387               gfc_error ("Coarray dummy argument '%s' at %L to elemental "
388                          "procedure", sym->name, &sym->declared_at);
389               continue;
390             }
391
392           if (sym->as != NULL)
393             {
394               gfc_error ("Argument '%s' of elemental procedure at %L must "
395                          "be scalar", sym->name, &sym->declared_at);
396               continue;
397             }
398
399           if (sym->attr.allocatable)
400             {
401               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
402                          "have the ALLOCATABLE attribute", sym->name,
403                          &sym->declared_at);
404               continue;
405             }
406
407           if (sym->attr.pointer)
408             {
409               gfc_error ("Argument '%s' of elemental procedure at %L cannot "
410                          "have the POINTER attribute", sym->name,
411                          &sym->declared_at);
412               continue;
413             }
414
415           if (sym->attr.flavor == FL_PROCEDURE)
416             {
417               gfc_error ("Dummy procedure '%s' not allowed in elemental "
418                          "procedure '%s' at %L", sym->name, proc->name,
419                          &sym->declared_at);
420               continue;
421             }
422
423           if (sym->attr.intent == INTENT_UNKNOWN)
424             {
425               gfc_error ("Argument '%s' of elemental procedure '%s' at %L must "
426                          "have its INTENT specified", sym->name, proc->name,
427                          &sym->declared_at);
428               continue;
429             }
430         }
431
432       /* Each dummy shall be specified to be scalar.  */
433       if (proc->attr.proc == PROC_ST_FUNCTION)
434         {
435           if (sym->as != NULL)
436             {
437               gfc_error ("Argument '%s' of statement function at %L must "
438                          "be scalar", sym->name, &sym->declared_at);
439               continue;
440             }
441
442           if (sym->ts.type == BT_CHARACTER)
443             {
444               gfc_charlen *cl = sym->ts.u.cl;
445               if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
446                 {
447                   gfc_error ("Character-valued argument '%s' of statement "
448                              "function at %L must have constant length",
449                              sym->name, &sym->declared_at);
450                   continue;
451                 }
452             }
453         }
454     }
455   formal_arg_flag = 0;
456 }
457
458
459 /* Work function called when searching for symbols that have argument lists
460    associated with them.  */
461
462 static void
463 find_arglists (gfc_symbol *sym)
464 {
465   if (sym->attr.if_source == IFSRC_UNKNOWN || sym->ns != gfc_current_ns)
466     return;
467
468   resolve_formal_arglist (sym);
469 }
470
471
472 /* Given a namespace, resolve all formal argument lists within the namespace.
473  */
474
475 static void
476 resolve_formal_arglists (gfc_namespace *ns)
477 {
478   if (ns == NULL)
479     return;
480
481   gfc_traverse_ns (ns, find_arglists);
482 }
483
484
485 static void
486 resolve_contained_fntype (gfc_symbol *sym, gfc_namespace *ns)
487 {
488   gfc_try t;
489
490   /* If this namespace is not a function or an entry master function,
491      ignore it.  */
492   if (! sym || !(sym->attr.function || sym->attr.flavor == FL_VARIABLE)
493       || sym->attr.entry_master)
494     return;
495
496   /* Try to find out of what the return type is.  */
497   if (sym->result->ts.type == BT_UNKNOWN && sym->result->ts.interface == NULL)
498     {
499       t = gfc_set_default_type (sym->result, 0, ns);
500
501       if (t == FAILURE && !sym->result->attr.untyped)
502         {
503           if (sym->result == sym)
504             gfc_error ("Contained function '%s' at %L has no IMPLICIT type",
505                        sym->name, &sym->declared_at);
506           else if (!sym->result->attr.proc_pointer)
507             gfc_error ("Result '%s' of contained function '%s' at %L has "
508                        "no IMPLICIT type", sym->result->name, sym->name,
509                        &sym->result->declared_at);
510           sym->result->attr.untyped = 1;
511         }
512     }
513
514   /* Fortran 95 Draft Standard, page 51, Section 5.1.1.5, on the Character 
515      type, lists the only ways a character length value of * can be used:
516      dummy arguments of procedures, named constants, and function results
517      in external functions.  Internal function results and results of module
518      procedures are not on this list, ergo, not permitted.  */
519
520   if (sym->result->ts.type == BT_CHARACTER)
521     {
522       gfc_charlen *cl = sym->result->ts.u.cl;
523       if ((!cl || !cl->length) && !sym->result->ts.deferred)
524         {
525           /* See if this is a module-procedure and adapt error message
526              accordingly.  */
527           bool module_proc;
528           gcc_assert (ns->parent && ns->parent->proc_name);
529           module_proc = (ns->parent->proc_name->attr.flavor == FL_MODULE);
530
531           gfc_error ("Character-valued %s '%s' at %L must not be"
532                      " assumed length",
533                      module_proc ? _("module procedure")
534                                  : _("internal function"),
535                      sym->name, &sym->declared_at);
536         }
537     }
538 }
539
540
541 /* Add NEW_ARGS to the formal argument list of PROC, taking care not to
542    introduce duplicates.  */
543
544 static void
545 merge_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
546 {
547   gfc_formal_arglist *f, *new_arglist;
548   gfc_symbol *new_sym;
549
550   for (; new_args != NULL; new_args = new_args->next)
551     {
552       new_sym = new_args->sym;
553       /* See if this arg is already in the formal argument list.  */
554       for (f = proc->formal; f; f = f->next)
555         {
556           if (new_sym == f->sym)
557             break;
558         }
559
560       if (f)
561         continue;
562
563       /* Add a new argument.  Argument order is not important.  */
564       new_arglist = gfc_get_formal_arglist ();
565       new_arglist->sym = new_sym;
566       new_arglist->next = proc->formal;
567       proc->formal  = new_arglist;
568     }
569 }
570
571
572 /* Flag the arguments that are not present in all entries.  */
573
574 static void
575 check_argument_lists (gfc_symbol *proc, gfc_formal_arglist *new_args)
576 {
577   gfc_formal_arglist *f, *head;
578   head = new_args;
579
580   for (f = proc->formal; f; f = f->next)
581     {
582       if (f->sym == NULL)
583         continue;
584
585       for (new_args = head; new_args; new_args = new_args->next)
586         {
587           if (new_args->sym == f->sym)
588             break;
589         }
590
591       if (new_args)
592         continue;
593
594       f->sym->attr.not_always_present = 1;
595     }
596 }
597
598
599 /* Resolve alternate entry points.  If a symbol has multiple entry points we
600    create a new master symbol for the main routine, and turn the existing
601    symbol into an entry point.  */
602
603 static void
604 resolve_entries (gfc_namespace *ns)
605 {
606   gfc_namespace *old_ns;
607   gfc_code *c;
608   gfc_symbol *proc;
609   gfc_entry_list *el;
610   char name[GFC_MAX_SYMBOL_LEN + 1];
611   static int master_count = 0;
612
613   if (ns->proc_name == NULL)
614     return;
615
616   /* No need to do anything if this procedure doesn't have alternate entry
617      points.  */
618   if (!ns->entries)
619     return;
620
621   /* We may already have resolved alternate entry points.  */
622   if (ns->proc_name->attr.entry_master)
623     return;
624
625   /* If this isn't a procedure something has gone horribly wrong.  */
626   gcc_assert (ns->proc_name->attr.flavor == FL_PROCEDURE);
627
628   /* Remember the current namespace.  */
629   old_ns = gfc_current_ns;
630
631   gfc_current_ns = ns;
632
633   /* Add the main entry point to the list of entry points.  */
634   el = gfc_get_entry_list ();
635   el->sym = ns->proc_name;
636   el->id = 0;
637   el->next = ns->entries;
638   ns->entries = el;
639   ns->proc_name->attr.entry = 1;
640
641   /* If it is a module function, it needs to be in the right namespace
642      so that gfc_get_fake_result_decl can gather up the results. The
643      need for this arose in get_proc_name, where these beasts were
644      left in their own namespace, to keep prior references linked to
645      the entry declaration.*/
646   if (ns->proc_name->attr.function
647       && ns->parent && ns->parent->proc_name->attr.flavor == FL_MODULE)
648     el->sym->ns = ns;
649
650   /* Do the same for entries where the master is not a module
651      procedure.  These are retained in the module namespace because
652      of the module procedure declaration.  */
653   for (el = el->next; el; el = el->next)
654     if (el->sym->ns->proc_name->attr.flavor == FL_MODULE
655           && el->sym->attr.mod_proc)
656       el->sym->ns = ns;
657   el = ns->entries;
658
659   /* Add an entry statement for it.  */
660   c = gfc_get_code ();
661   c->op = EXEC_ENTRY;
662   c->ext.entry = el;
663   c->next = ns->code;
664   ns->code = c;
665
666   /* Create a new symbol for the master function.  */
667   /* Give the internal function a unique name (within this file).
668      Also include the function name so the user has some hope of figuring
669      out what is going on.  */
670   snprintf (name, GFC_MAX_SYMBOL_LEN, "master.%d.%s",
671             master_count++, ns->proc_name->name);
672   gfc_get_ha_symbol (name, &proc);
673   gcc_assert (proc != NULL);
674
675   gfc_add_procedure (&proc->attr, PROC_INTERNAL, proc->name, NULL);
676   if (ns->proc_name->attr.subroutine)
677     gfc_add_subroutine (&proc->attr, proc->name, NULL);
678   else
679     {
680       gfc_symbol *sym;
681       gfc_typespec *ts, *fts;
682       gfc_array_spec *as, *fas;
683       gfc_add_function (&proc->attr, proc->name, NULL);
684       proc->result = proc;
685       fas = ns->entries->sym->as;
686       fas = fas ? fas : ns->entries->sym->result->as;
687       fts = &ns->entries->sym->result->ts;
688       if (fts->type == BT_UNKNOWN)
689         fts = gfc_get_default_type (ns->entries->sym->result->name, NULL);
690       for (el = ns->entries->next; el; el = el->next)
691         {
692           ts = &el->sym->result->ts;
693           as = el->sym->as;
694           as = as ? as : el->sym->result->as;
695           if (ts->type == BT_UNKNOWN)
696             ts = gfc_get_default_type (el->sym->result->name, NULL);
697
698           if (! gfc_compare_types (ts, fts)
699               || (el->sym->result->attr.dimension
700                   != ns->entries->sym->result->attr.dimension)
701               || (el->sym->result->attr.pointer
702                   != ns->entries->sym->result->attr.pointer))
703             break;
704           else if (as && fas && ns->entries->sym->result != el->sym->result
705                       && gfc_compare_array_spec (as, fas) == 0)
706             gfc_error ("Function %s at %L has entries with mismatched "
707                        "array specifications", ns->entries->sym->name,
708                        &ns->entries->sym->declared_at);
709           /* The characteristics need to match and thus both need to have
710              the same string length, i.e. both len=*, or both len=4.
711              Having both len=<variable> is also possible, but difficult to
712              check at compile time.  */
713           else if (ts->type == BT_CHARACTER && ts->u.cl && fts->u.cl
714                    && (((ts->u.cl->length && !fts->u.cl->length)
715                         ||(!ts->u.cl->length && fts->u.cl->length))
716                        || (ts->u.cl->length
717                            && ts->u.cl->length->expr_type
718                               != fts->u.cl->length->expr_type)
719                        || (ts->u.cl->length
720                            && ts->u.cl->length->expr_type == EXPR_CONSTANT
721                            && mpz_cmp (ts->u.cl->length->value.integer,
722                                        fts->u.cl->length->value.integer) != 0)))
723             gfc_notify_std (GFC_STD_GNU, "Extension: Function %s at %L with "
724                             "entries returning variables of different "
725                             "string lengths", ns->entries->sym->name,
726                             &ns->entries->sym->declared_at);
727         }
728
729       if (el == NULL)
730         {
731           sym = ns->entries->sym->result;
732           /* All result types the same.  */
733           proc->ts = *fts;
734           if (sym->attr.dimension)
735             gfc_set_array_spec (proc, gfc_copy_array_spec (sym->as), NULL);
736           if (sym->attr.pointer)
737             gfc_add_pointer (&proc->attr, NULL);
738         }
739       else
740         {
741           /* Otherwise the result will be passed through a union by
742              reference.  */
743           proc->attr.mixed_entry_master = 1;
744           for (el = ns->entries; el; el = el->next)
745             {
746               sym = el->sym->result;
747               if (sym->attr.dimension)
748                 {
749                   if (el == ns->entries)
750                     gfc_error ("FUNCTION result %s can't be an array in "
751                                "FUNCTION %s at %L", sym->name,
752                                ns->entries->sym->name, &sym->declared_at);
753                   else
754                     gfc_error ("ENTRY result %s can't be an array in "
755                                "FUNCTION %s at %L", sym->name,
756                                ns->entries->sym->name, &sym->declared_at);
757                 }
758               else if (sym->attr.pointer)
759                 {
760                   if (el == ns->entries)
761                     gfc_error ("FUNCTION result %s can't be a POINTER in "
762                                "FUNCTION %s at %L", sym->name,
763                                ns->entries->sym->name, &sym->declared_at);
764                   else
765                     gfc_error ("ENTRY result %s can't be a POINTER in "
766                                "FUNCTION %s at %L", sym->name,
767                                ns->entries->sym->name, &sym->declared_at);
768                 }
769               else
770                 {
771                   ts = &sym->ts;
772                   if (ts->type == BT_UNKNOWN)
773                     ts = gfc_get_default_type (sym->name, NULL);
774                   switch (ts->type)
775                     {
776                     case BT_INTEGER:
777                       if (ts->kind == gfc_default_integer_kind)
778                         sym = NULL;
779                       break;
780                     case BT_REAL:
781                       if (ts->kind == gfc_default_real_kind
782                           || ts->kind == gfc_default_double_kind)
783                         sym = NULL;
784                       break;
785                     case BT_COMPLEX:
786                       if (ts->kind == gfc_default_complex_kind)
787                         sym = NULL;
788                       break;
789                     case BT_LOGICAL:
790                       if (ts->kind == gfc_default_logical_kind)
791                         sym = NULL;
792                       break;
793                     case BT_UNKNOWN:
794                       /* We will issue error elsewhere.  */
795                       sym = NULL;
796                       break;
797                     default:
798                       break;
799                     }
800                   if (sym)
801                     {
802                       if (el == ns->entries)
803                         gfc_error ("FUNCTION result %s can't be of type %s "
804                                    "in FUNCTION %s at %L", sym->name,
805                                    gfc_typename (ts), ns->entries->sym->name,
806                                    &sym->declared_at);
807                       else
808                         gfc_error ("ENTRY result %s can't be of type %s "
809                                    "in FUNCTION %s at %L", sym->name,
810                                    gfc_typename (ts), ns->entries->sym->name,
811                                    &sym->declared_at);
812                     }
813                 }
814             }
815         }
816     }
817   proc->attr.access = ACCESS_PRIVATE;
818   proc->attr.entry_master = 1;
819
820   /* Merge all the entry point arguments.  */
821   for (el = ns->entries; el; el = el->next)
822     merge_argument_lists (proc, el->sym->formal);
823
824   /* Check the master formal arguments for any that are not
825      present in all entry points.  */
826   for (el = ns->entries; el; el = el->next)
827     check_argument_lists (proc, el->sym->formal);
828
829   /* Use the master function for the function body.  */
830   ns->proc_name = proc;
831
832   /* Finalize the new symbols.  */
833   gfc_commit_symbols ();
834
835   /* Restore the original namespace.  */
836   gfc_current_ns = old_ns;
837 }
838
839
840 /* Resolve common variables.  */
841 static void
842 resolve_common_vars (gfc_symbol *sym, bool named_common)
843 {
844   gfc_symbol *csym = sym;
845
846   for (; csym; csym = csym->common_next)
847     {
848       if (csym->value || csym->attr.data)
849         {
850           if (!csym->ns->is_block_data)
851             gfc_notify_std (GFC_STD_GNU, "Variable '%s' at %L is in COMMON "
852                             "but only in BLOCK DATA initialization is "
853                             "allowed", csym->name, &csym->declared_at);
854           else if (!named_common)
855             gfc_notify_std (GFC_STD_GNU, "Initialized variable '%s' at %L is "
856                             "in a blank COMMON but initialization is only "
857                             "allowed in named common blocks", csym->name,
858                             &csym->declared_at);
859         }
860
861       if (csym->ts.type != BT_DERIVED)
862         continue;
863
864       if (!(csym->ts.u.derived->attr.sequence
865             || csym->ts.u.derived->attr.is_bind_c))
866         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
867                        "has neither the SEQUENCE nor the BIND(C) "
868                        "attribute", csym->name, &csym->declared_at);
869       if (csym->ts.u.derived->attr.alloc_comp)
870         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
871                        "has an ultimate component that is "
872                        "allocatable", csym->name, &csym->declared_at);
873       if (gfc_has_default_initializer (csym->ts.u.derived))
874         gfc_error_now ("Derived type variable '%s' in COMMON at %L "
875                        "may not have default initializer", csym->name,
876                        &csym->declared_at);
877
878       if (csym->attr.flavor == FL_UNKNOWN && !csym->attr.proc_pointer)
879         gfc_add_flavor (&csym->attr, FL_VARIABLE, csym->name, &csym->declared_at);
880     }
881 }
882
883 /* Resolve common blocks.  */
884 static void
885 resolve_common_blocks (gfc_symtree *common_root)
886 {
887   gfc_symbol *sym;
888
889   if (common_root == NULL)
890     return;
891
892   if (common_root->left)
893     resolve_common_blocks (common_root->left);
894   if (common_root->right)
895     resolve_common_blocks (common_root->right);
896
897   resolve_common_vars (common_root->n.common->head, true);
898
899   gfc_find_symbol (common_root->name, gfc_current_ns, 0, &sym);
900   if (sym == NULL)
901     return;
902
903   if (sym->attr.flavor == FL_PARAMETER)
904     gfc_error ("COMMON block '%s' at %L is used as PARAMETER at %L",
905                sym->name, &common_root->n.common->where, &sym->declared_at);
906
907   if (sym->attr.intrinsic)
908     gfc_error ("COMMON block '%s' at %L is also an intrinsic procedure",
909                sym->name, &common_root->n.common->where);
910   else if (sym->attr.result
911            || gfc_is_function_return_value (sym, gfc_current_ns))
912     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
913                     "that is also a function result", sym->name,
914                     &common_root->n.common->where);
915   else if (sym->attr.flavor == FL_PROCEDURE && sym->attr.proc != PROC_INTERNAL
916            && sym->attr.proc != PROC_ST_FUNCTION)
917     gfc_notify_std (GFC_STD_F2003, "Fortran 2003: COMMON block '%s' at %L "
918                     "that is also a global procedure", sym->name,
919                     &common_root->n.common->where);
920 }
921
922
923 /* Resolve contained function types.  Because contained functions can call one
924    another, they have to be worked out before any of the contained procedures
925    can be resolved.
926
927    The good news is that if a function doesn't already have a type, the only
928    way it can get one is through an IMPLICIT type or a RESULT variable, because
929    by definition contained functions are contained namespace they're contained
930    in, not in a sibling or parent namespace.  */
931
932 static void
933 resolve_contained_functions (gfc_namespace *ns)
934 {
935   gfc_namespace *child;
936   gfc_entry_list *el;
937
938   resolve_formal_arglists (ns);
939
940   for (child = ns->contained; child; child = child->sibling)
941     {
942       /* Resolve alternate entry points first.  */
943       resolve_entries (child);
944
945       /* Then check function return types.  */
946       resolve_contained_fntype (child->proc_name, child);
947       for (el = child->entries; el; el = el->next)
948         resolve_contained_fntype (el->sym, child);
949     }
950 }
951
952
953 static gfc_try resolve_fl_derived0 (gfc_symbol *sym);
954
955
956 /* Resolve all of the elements of a structure constructor and make sure that
957    the types are correct. The 'init' flag indicates that the given
958    constructor is an initializer.  */
959
960 static gfc_try
961 resolve_structure_cons (gfc_expr *expr, int init)
962 {
963   gfc_constructor *cons;
964   gfc_component *comp;
965   gfc_try t;
966   symbol_attribute a;
967
968   t = SUCCESS;
969
970   if (expr->ts.type == BT_DERIVED)
971     resolve_fl_derived0 (expr->ts.u.derived);
972
973   cons = gfc_constructor_first (expr->value.constructor);
974   /* A constructor may have references if it is the result of substituting a
975      parameter variable.  In this case we just pull out the component we
976      want.  */
977   if (expr->ref)
978     comp = expr->ref->u.c.sym->components;
979   else
980     comp = expr->ts.u.derived->components;
981
982   /* See if the user is trying to invoke a structure constructor for one of
983      the iso_c_binding derived types.  */
984   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
985       && expr->ts.u.derived->ts.is_iso_c && cons
986       && (cons->expr == NULL || cons->expr->expr_type != EXPR_NULL))
987     {
988       gfc_error ("Components of structure constructor '%s' at %L are PRIVATE",
989                  expr->ts.u.derived->name, &(expr->where));
990       return FAILURE;
991     }
992
993   /* Return if structure constructor is c_null_(fun)prt.  */
994   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
995       && expr->ts.u.derived->ts.is_iso_c && cons
996       && cons->expr && cons->expr->expr_type == EXPR_NULL)
997     return SUCCESS;
998
999   for (; comp && cons; comp = comp->next, cons = gfc_constructor_next (cons))
1000     {
1001       int rank;
1002
1003       if (!cons->expr)
1004         continue;
1005
1006       if (gfc_resolve_expr (cons->expr) == FAILURE)
1007         {
1008           t = FAILURE;
1009           continue;
1010         }
1011
1012       rank = comp->as ? comp->as->rank : 0;
1013       if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank
1014           && (comp->attr.allocatable || cons->expr->rank))
1015         {
1016           gfc_error ("The rank of the element in the derived type "
1017                      "constructor at %L does not match that of the "
1018                      "component (%d/%d)", &cons->expr->where,
1019                      cons->expr->rank, rank);
1020           t = FAILURE;
1021         }
1022
1023       /* If we don't have the right type, try to convert it.  */
1024
1025       if (!comp->attr.proc_pointer &&
1026           !gfc_compare_types (&cons->expr->ts, &comp->ts))
1027         {
1028           t = FAILURE;
1029           if (strcmp (comp->name, "_extends") == 0)
1030             {
1031               /* Can afford to be brutal with the _extends initializer.
1032                  The derived type can get lost because it is PRIVATE
1033                  but it is not usage constrained by the standard.  */
1034               cons->expr->ts = comp->ts;
1035               t = SUCCESS;
1036             }
1037           else if (comp->attr.pointer && cons->expr->ts.type != BT_UNKNOWN)
1038             gfc_error ("The element in the derived type constructor at %L, "
1039                        "for pointer component '%s', is %s but should be %s",
1040                        &cons->expr->where, comp->name,
1041                        gfc_basic_typename (cons->expr->ts.type),
1042                        gfc_basic_typename (comp->ts.type));
1043           else
1044             t = gfc_convert_type (cons->expr, &comp->ts, 1);
1045         }
1046
1047       /* For strings, the length of the constructor should be the same as
1048          the one of the structure, ensure this if the lengths are known at
1049          compile time and when we are dealing with PARAMETER or structure
1050          constructors.  */
1051       if (cons->expr->ts.type == BT_CHARACTER && comp->ts.u.cl
1052           && comp->ts.u.cl->length
1053           && comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
1054           && cons->expr->ts.u.cl && cons->expr->ts.u.cl->length
1055           && cons->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
1056           && mpz_cmp (cons->expr->ts.u.cl->length->value.integer,
1057                       comp->ts.u.cl->length->value.integer) != 0)
1058         {
1059           if (cons->expr->expr_type == EXPR_VARIABLE
1060               && cons->expr->symtree->n.sym->attr.flavor == FL_PARAMETER)
1061             {
1062               /* Wrap the parameter in an array constructor (EXPR_ARRAY)
1063                  to make use of the gfc_resolve_character_array_constructor
1064                  machinery.  The expression is later simplified away to
1065                  an array of string literals.  */
1066               gfc_expr *para = cons->expr;
1067               cons->expr = gfc_get_expr ();
1068               cons->expr->ts = para->ts;
1069               cons->expr->where = para->where;
1070               cons->expr->expr_type = EXPR_ARRAY;
1071               cons->expr->rank = para->rank;
1072               cons->expr->shape = gfc_copy_shape (para->shape, para->rank);
1073               gfc_constructor_append_expr (&cons->expr->value.constructor,
1074                                            para, &cons->expr->where);
1075             }
1076           if (cons->expr->expr_type == EXPR_ARRAY)
1077             {
1078               gfc_constructor *p;
1079               p = gfc_constructor_first (cons->expr->value.constructor);
1080               if (cons->expr->ts.u.cl != p->expr->ts.u.cl)
1081                 {
1082                   gfc_charlen *cl, *cl2;
1083
1084                   cl2 = NULL;
1085                   for (cl = gfc_current_ns->cl_list; cl; cl = cl->next)
1086                     {
1087                       if (cl == cons->expr->ts.u.cl)
1088                         break;
1089                       cl2 = cl;
1090                     }
1091
1092                   gcc_assert (cl);
1093
1094                   if (cl2)
1095                     cl2->next = cl->next;
1096
1097                   gfc_free_expr (cl->length);
1098                   free (cl);
1099                 }
1100
1101               cons->expr->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
1102               cons->expr->ts.u.cl->length_from_typespec = true;
1103               cons->expr->ts.u.cl->length = gfc_copy_expr (comp->ts.u.cl->length);
1104               gfc_resolve_character_array_constructor (cons->expr);
1105             }
1106         }
1107
1108       if (cons->expr->expr_type == EXPR_NULL
1109           && !(comp->attr.pointer || comp->attr.allocatable
1110                || comp->attr.proc_pointer
1111                || (comp->ts.type == BT_CLASS
1112                    && (CLASS_DATA (comp)->attr.class_pointer
1113                        || CLASS_DATA (comp)->attr.allocatable))))
1114         {
1115           t = FAILURE;
1116           gfc_error ("The NULL in the derived type constructor at %L is "
1117                      "being applied to component '%s', which is neither "
1118                      "a POINTER nor ALLOCATABLE", &cons->expr->where,
1119                      comp->name);
1120         }
1121
1122       if (!comp->attr.pointer || comp->attr.proc_pointer
1123           || cons->expr->expr_type == EXPR_NULL)
1124         continue;
1125
1126       a = gfc_expr_attr (cons->expr);
1127
1128       if (!a.pointer && !a.target)
1129         {
1130           t = FAILURE;
1131           gfc_error ("The element in the derived type constructor at %L, "
1132                      "for pointer component '%s' should be a POINTER or "
1133                      "a TARGET", &cons->expr->where, comp->name);
1134         }
1135
1136       if (init)
1137         {
1138           /* F08:C461. Additional checks for pointer initialization.  */
1139           if (a.allocatable)
1140             {
1141               t = FAILURE;
1142               gfc_error ("Pointer initialization target at %L "
1143                          "must not be ALLOCATABLE ", &cons->expr->where);
1144             }
1145           if (!a.save)
1146             {
1147               t = FAILURE;
1148               gfc_error ("Pointer initialization target at %L "
1149                          "must have the SAVE attribute", &cons->expr->where);
1150             }
1151         }
1152
1153       /* F2003, C1272 (3).  */
1154       if (gfc_pure (NULL) && cons->expr->expr_type == EXPR_VARIABLE
1155           && (gfc_impure_variable (cons->expr->symtree->n.sym)
1156               || gfc_is_coindexed (cons->expr)))
1157         {
1158           t = FAILURE;
1159           gfc_error ("Invalid expression in the derived type constructor for "
1160                      "pointer component '%s' at %L in PURE procedure",
1161                      comp->name, &cons->expr->where);
1162         }
1163
1164       if (gfc_implicit_pure (NULL)
1165             && cons->expr->expr_type == EXPR_VARIABLE
1166             && (gfc_impure_variable (cons->expr->symtree->n.sym)
1167                 || gfc_is_coindexed (cons->expr)))
1168         gfc_current_ns->proc_name->attr.implicit_pure = 0;
1169
1170     }
1171
1172   return t;
1173 }
1174
1175
1176 /****************** Expression name resolution ******************/
1177
1178 /* Returns 0 if a symbol was not declared with a type or
1179    attribute declaration statement, nonzero otherwise.  */
1180
1181 static int
1182 was_declared (gfc_symbol *sym)
1183 {
1184   symbol_attribute a;
1185
1186   a = sym->attr;
1187
1188   if (!a.implicit_type && sym->ts.type != BT_UNKNOWN)
1189     return 1;
1190
1191   if (a.allocatable || a.dimension || a.dummy || a.external || a.intrinsic
1192       || a.optional || a.pointer || a.save || a.target || a.volatile_
1193       || a.value || a.access != ACCESS_UNKNOWN || a.intent != INTENT_UNKNOWN
1194       || a.asynchronous || a.codimension)
1195     return 1;
1196
1197   return 0;
1198 }
1199
1200
1201 /* Determine if a symbol is generic or not.  */
1202
1203 static int
1204 generic_sym (gfc_symbol *sym)
1205 {
1206   gfc_symbol *s;
1207
1208   if (sym->attr.generic ||
1209       (sym->attr.intrinsic && gfc_generic_intrinsic (sym->name)))
1210     return 1;
1211
1212   if (was_declared (sym) || sym->ns->parent == NULL)
1213     return 0;
1214
1215   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1216   
1217   if (s != NULL)
1218     {
1219       if (s == sym)
1220         return 0;
1221       else
1222         return generic_sym (s);
1223     }
1224
1225   return 0;
1226 }
1227
1228
1229 /* Determine if a symbol is specific or not.  */
1230
1231 static int
1232 specific_sym (gfc_symbol *sym)
1233 {
1234   gfc_symbol *s;
1235
1236   if (sym->attr.if_source == IFSRC_IFBODY
1237       || sym->attr.proc == PROC_MODULE
1238       || sym->attr.proc == PROC_INTERNAL
1239       || sym->attr.proc == PROC_ST_FUNCTION
1240       || (sym->attr.intrinsic && gfc_specific_intrinsic (sym->name))
1241       || sym->attr.external)
1242     return 1;
1243
1244   if (was_declared (sym) || sym->ns->parent == NULL)
1245     return 0;
1246
1247   gfc_find_symbol (sym->name, sym->ns->parent, 1, &s);
1248
1249   return (s == NULL) ? 0 : specific_sym (s);
1250 }
1251
1252
1253 /* Figure out if the procedure is specific, generic or unknown.  */
1254
1255 typedef enum
1256 { PTYPE_GENERIC = 1, PTYPE_SPECIFIC, PTYPE_UNKNOWN }
1257 proc_type;
1258
1259 static proc_type
1260 procedure_kind (gfc_symbol *sym)
1261 {
1262   if (generic_sym (sym))
1263     return PTYPE_GENERIC;
1264
1265   if (specific_sym (sym))
1266     return PTYPE_SPECIFIC;
1267
1268   return PTYPE_UNKNOWN;
1269 }
1270
1271 /* Check references to assumed size arrays.  The flag need_full_assumed_size
1272    is nonzero when matching actual arguments.  */
1273
1274 static int need_full_assumed_size = 0;
1275
1276 static bool
1277 check_assumed_size_reference (gfc_symbol *sym, gfc_expr *e)
1278 {
1279   if (need_full_assumed_size || !(sym->as && sym->as->type == AS_ASSUMED_SIZE))
1280       return false;
1281
1282   /* FIXME: The comparison "e->ref->u.ar.type == AR_FULL" is wrong.
1283      What should it be?  */
1284   if ((e->ref->u.ar.end[e->ref->u.ar.as->rank - 1] == NULL)
1285           && (e->ref->u.ar.as->type == AS_ASSUMED_SIZE)
1286                && (e->ref->u.ar.type == AR_FULL))
1287     {
1288       gfc_error ("The upper bound in the last dimension must "
1289                  "appear in the reference to the assumed size "
1290                  "array '%s' at %L", sym->name, &e->where);
1291       return true;
1292     }
1293   return false;
1294 }
1295
1296
1297 /* Look for bad assumed size array references in argument expressions
1298   of elemental and array valued intrinsic procedures.  Since this is
1299   called from procedure resolution functions, it only recurses at
1300   operators.  */
1301
1302 static bool
1303 resolve_assumed_size_actual (gfc_expr *e)
1304 {
1305   if (e == NULL)
1306    return false;
1307
1308   switch (e->expr_type)
1309     {
1310     case EXPR_VARIABLE:
1311       if (e->symtree && check_assumed_size_reference (e->symtree->n.sym, e))
1312         return true;
1313       break;
1314
1315     case EXPR_OP:
1316       if (resolve_assumed_size_actual (e->value.op.op1)
1317           || resolve_assumed_size_actual (e->value.op.op2))
1318         return true;
1319       break;
1320
1321     default:
1322       break;
1323     }
1324   return false;
1325 }
1326
1327
1328 /* Check a generic procedure, passed as an actual argument, to see if
1329    there is a matching specific name.  If none, it is an error, and if
1330    more than one, the reference is ambiguous.  */
1331 static int
1332 count_specific_procs (gfc_expr *e)
1333 {
1334   int n;
1335   gfc_interface *p;
1336   gfc_symbol *sym;
1337         
1338   n = 0;
1339   sym = e->symtree->n.sym;
1340
1341   for (p = sym->generic; p; p = p->next)
1342     if (strcmp (sym->name, p->sym->name) == 0)
1343       {
1344         e->symtree = gfc_find_symtree (p->sym->ns->sym_root,
1345                                        sym->name);
1346         n++;
1347       }
1348
1349   if (n > 1)
1350     gfc_error ("'%s' at %L is ambiguous", e->symtree->n.sym->name,
1351                &e->where);
1352
1353   if (n == 0)
1354     gfc_error ("GENERIC procedure '%s' is not allowed as an actual "
1355                "argument at %L", sym->name, &e->where);
1356
1357   return n;
1358 }
1359
1360
1361 /* See if a call to sym could possibly be a not allowed RECURSION because of
1362    a missing RECURIVE declaration.  This means that either sym is the current
1363    context itself, or sym is the parent of a contained procedure calling its
1364    non-RECURSIVE containing procedure.
1365    This also works if sym is an ENTRY.  */
1366
1367 static bool
1368 is_illegal_recursion (gfc_symbol* sym, gfc_namespace* context)
1369 {
1370   gfc_symbol* proc_sym;
1371   gfc_symbol* context_proc;
1372   gfc_namespace* real_context;
1373
1374   if (sym->attr.flavor == FL_PROGRAM)
1375     return false;
1376
1377   gcc_assert (sym->attr.flavor == FL_PROCEDURE);
1378
1379   /* If we've got an ENTRY, find real procedure.  */
1380   if (sym->attr.entry && sym->ns->entries)
1381     proc_sym = sym->ns->entries->sym;
1382   else
1383     proc_sym = sym;
1384
1385   /* If sym is RECURSIVE, all is well of course.  */
1386   if (proc_sym->attr.recursive || gfc_option.flag_recursive)
1387     return false;
1388
1389   /* Find the context procedure's "real" symbol if it has entries.
1390      We look for a procedure symbol, so recurse on the parents if we don't
1391      find one (like in case of a BLOCK construct).  */
1392   for (real_context = context; ; real_context = real_context->parent)
1393     {
1394       /* We should find something, eventually!  */
1395       gcc_assert (real_context);
1396
1397       context_proc = (real_context->entries ? real_context->entries->sym
1398                                             : real_context->proc_name);
1399
1400       /* In some special cases, there may not be a proc_name, like for this
1401          invalid code:
1402          real(bad_kind()) function foo () ...
1403          when checking the call to bad_kind ().
1404          In these cases, we simply return here and assume that the
1405          call is ok.  */
1406       if (!context_proc)
1407         return false;
1408
1409       if (context_proc->attr.flavor != FL_LABEL)
1410         break;
1411     }
1412
1413   /* A call from sym's body to itself is recursion, of course.  */
1414   if (context_proc == proc_sym)
1415     return true;
1416
1417   /* The same is true if context is a contained procedure and sym the
1418      containing one.  */
1419   if (context_proc->attr.contained)
1420     {
1421       gfc_symbol* parent_proc;
1422
1423       gcc_assert (context->parent);
1424       parent_proc = (context->parent->entries ? context->parent->entries->sym
1425                                               : context->parent->proc_name);
1426
1427       if (parent_proc == proc_sym)
1428         return true;
1429     }
1430
1431   return false;
1432 }
1433
1434
1435 /* Resolve an intrinsic procedure: Set its function/subroutine attribute,
1436    its typespec and formal argument list.  */
1437
1438 static gfc_try
1439 resolve_intrinsic (gfc_symbol *sym, locus *loc)
1440 {
1441   gfc_intrinsic_sym* isym = NULL;
1442   const char* symstd;
1443
1444   if (sym->formal)
1445     return SUCCESS;
1446
1447   /* Already resolved.  */
1448   if (sym->from_intmod && sym->ts.type != BT_UNKNOWN)
1449     return SUCCESS;
1450
1451   /* We already know this one is an intrinsic, so we don't call
1452      gfc_is_intrinsic for full checking but rather use gfc_find_function and
1453      gfc_find_subroutine directly to check whether it is a function or
1454      subroutine.  */
1455
1456   if (sym->intmod_sym_id)
1457     isym = gfc_intrinsic_function_by_id ((gfc_isym_id) sym->intmod_sym_id);
1458   else
1459     isym = gfc_find_function (sym->name);
1460
1461   if (isym)
1462     {
1463       if (sym->ts.type != BT_UNKNOWN && gfc_option.warn_surprising
1464           && !sym->attr.implicit_type)
1465         gfc_warning ("Type specified for intrinsic function '%s' at %L is"
1466                       " ignored", sym->name, &sym->declared_at);
1467
1468       if (!sym->attr.function &&
1469           gfc_add_function (&sym->attr, sym->name, loc) == FAILURE)
1470         return FAILURE;
1471
1472       sym->ts = isym->ts;
1473     }
1474   else if ((isym = gfc_find_subroutine (sym->name)))
1475     {
1476       if (sym->ts.type != BT_UNKNOWN && !sym->attr.implicit_type)
1477         {
1478           gfc_error ("Intrinsic subroutine '%s' at %L shall not have a type"
1479                       " specifier", sym->name, &sym->declared_at);
1480           return FAILURE;
1481         }
1482
1483       if (!sym->attr.subroutine &&
1484           gfc_add_subroutine (&sym->attr, sym->name, loc) == FAILURE)
1485         return FAILURE;
1486     }
1487   else
1488     {
1489       gfc_error ("'%s' declared INTRINSIC at %L does not exist", sym->name,
1490                  &sym->declared_at);
1491       return FAILURE;
1492     }
1493
1494   gfc_copy_formal_args_intr (sym, isym);
1495
1496   /* Check it is actually available in the standard settings.  */
1497   if (gfc_check_intrinsic_standard (isym, &symstd, false, sym->declared_at)
1498       == FAILURE)
1499     {
1500       gfc_error ("The intrinsic '%s' declared INTRINSIC at %L is not"
1501                  " available in the current standard settings but %s.  Use"
1502                  " an appropriate -std=* option or enable -fall-intrinsics"
1503                  " in order to use it.",
1504                  sym->name, &sym->declared_at, symstd);
1505       return FAILURE;
1506     }
1507
1508   return SUCCESS;
1509 }
1510
1511
1512 /* Resolve a procedure expression, like passing it to a called procedure or as
1513    RHS for a procedure pointer assignment.  */
1514
1515 static gfc_try
1516 resolve_procedure_expression (gfc_expr* expr)
1517 {
1518   gfc_symbol* sym;
1519
1520   if (expr->expr_type != EXPR_VARIABLE)
1521     return SUCCESS;
1522   gcc_assert (expr->symtree);
1523
1524   sym = expr->symtree->n.sym;
1525
1526   if (sym->attr.intrinsic)
1527     resolve_intrinsic (sym, &expr->where);
1528
1529   if (sym->attr.flavor != FL_PROCEDURE
1530       || (sym->attr.function && sym->result == sym))
1531     return SUCCESS;
1532
1533   /* A non-RECURSIVE procedure that is used as procedure expression within its
1534      own body is in danger of being called recursively.  */
1535   if (is_illegal_recursion (sym, gfc_current_ns))
1536     gfc_warning ("Non-RECURSIVE procedure '%s' at %L is possibly calling"
1537                  " itself recursively.  Declare it RECURSIVE or use"
1538                  " -frecursive", sym->name, &expr->where);
1539   
1540   return SUCCESS;
1541 }
1542
1543
1544 /* Resolve an actual argument list.  Most of the time, this is just
1545    resolving the expressions in the list.
1546    The exception is that we sometimes have to decide whether arguments
1547    that look like procedure arguments are really simple variable
1548    references.  */
1549
1550 static gfc_try
1551 resolve_actual_arglist (gfc_actual_arglist *arg, procedure_type ptype,
1552                         bool no_formal_args)
1553 {
1554   gfc_symbol *sym;
1555   gfc_symtree *parent_st;
1556   gfc_expr *e;
1557   int save_need_full_assumed_size;
1558
1559   for (; arg; arg = arg->next)
1560     {
1561       e = arg->expr;
1562       if (e == NULL)
1563         {
1564           /* Check the label is a valid branching target.  */
1565           if (arg->label)
1566             {
1567               if (arg->label->defined == ST_LABEL_UNKNOWN)
1568                 {
1569                   gfc_error ("Label %d referenced at %L is never defined",
1570                              arg->label->value, &arg->label->where);
1571                   return FAILURE;
1572                 }
1573             }
1574           continue;
1575         }
1576
1577       if (e->expr_type == EXPR_VARIABLE
1578             && e->symtree->n.sym->attr.generic
1579             && no_formal_args
1580             && count_specific_procs (e) != 1)
1581         return FAILURE;
1582
1583       if (e->ts.type != BT_PROCEDURE)
1584         {
1585           save_need_full_assumed_size = need_full_assumed_size;
1586           if (e->expr_type != EXPR_VARIABLE)
1587             need_full_assumed_size = 0;
1588           if (gfc_resolve_expr (e) != SUCCESS)
1589             return FAILURE;
1590           need_full_assumed_size = save_need_full_assumed_size;
1591           goto argument_list;
1592         }
1593
1594       /* See if the expression node should really be a variable reference.  */
1595
1596       sym = e->symtree->n.sym;
1597
1598       if (sym->attr.flavor == FL_PROCEDURE
1599           || sym->attr.intrinsic
1600           || sym->attr.external)
1601         {
1602           int actual_ok;
1603
1604           /* If a procedure is not already determined to be something else
1605              check if it is intrinsic.  */
1606           if (!sym->attr.intrinsic
1607               && !(sym->attr.external || sym->attr.use_assoc
1608                    || sym->attr.if_source == IFSRC_IFBODY)
1609               && gfc_is_intrinsic (sym, sym->attr.subroutine, e->where))
1610             sym->attr.intrinsic = 1;
1611
1612           if (sym->attr.proc == PROC_ST_FUNCTION)
1613             {
1614               gfc_error ("Statement function '%s' at %L is not allowed as an "
1615                          "actual argument", sym->name, &e->where);
1616             }
1617
1618           actual_ok = gfc_intrinsic_actual_ok (sym->name,
1619                                                sym->attr.subroutine);
1620           if (sym->attr.intrinsic && actual_ok == 0)
1621             {
1622               gfc_error ("Intrinsic '%s' at %L is not allowed as an "
1623                          "actual argument", sym->name, &e->where);
1624             }
1625
1626           if (sym->attr.contained && !sym->attr.use_assoc
1627               && sym->ns->proc_name->attr.flavor != FL_MODULE)
1628             {
1629               if (gfc_notify_std (GFC_STD_F2008,
1630                                   "Fortran 2008: Internal procedure '%s' is"
1631                                   " used as actual argument at %L",
1632                                   sym->name, &e->where) == FAILURE)
1633                 return FAILURE;
1634             }
1635
1636           if (sym->attr.elemental && !sym->attr.intrinsic)
1637             {
1638               gfc_error ("ELEMENTAL non-INTRINSIC procedure '%s' is not "
1639                          "allowed as an actual argument at %L", sym->name,
1640                          &e->where);
1641             }
1642
1643           /* Check if a generic interface has a specific procedure
1644             with the same name before emitting an error.  */
1645           if (sym->attr.generic && count_specific_procs (e) != 1)
1646             return FAILURE;
1647           
1648           /* Just in case a specific was found for the expression.  */
1649           sym = e->symtree->n.sym;
1650
1651           /* If the symbol is the function that names the current (or
1652              parent) scope, then we really have a variable reference.  */
1653
1654           if (gfc_is_function_return_value (sym, sym->ns))
1655             goto got_variable;
1656
1657           /* If all else fails, see if we have a specific intrinsic.  */
1658           if (sym->ts.type == BT_UNKNOWN && sym->attr.intrinsic)
1659             {
1660               gfc_intrinsic_sym *isym;
1661
1662               isym = gfc_find_function (sym->name);
1663               if (isym == NULL || !isym->specific)
1664                 {
1665                   gfc_error ("Unable to find a specific INTRINSIC procedure "
1666                              "for the reference '%s' at %L", sym->name,
1667                              &e->where);
1668                   return FAILURE;
1669                 }
1670               sym->ts = isym->ts;
1671               sym->attr.intrinsic = 1;
1672               sym->attr.function = 1;
1673             }
1674
1675           if (gfc_resolve_expr (e) == FAILURE)
1676             return FAILURE;
1677           goto argument_list;
1678         }
1679
1680       /* See if the name is a module procedure in a parent unit.  */
1681
1682       if (was_declared (sym) || sym->ns->parent == NULL)
1683         goto got_variable;
1684
1685       if (gfc_find_sym_tree (sym->name, sym->ns->parent, 1, &parent_st))
1686         {
1687           gfc_error ("Symbol '%s' at %L is ambiguous", sym->name, &e->where);
1688           return FAILURE;
1689         }
1690
1691       if (parent_st == NULL)
1692         goto got_variable;
1693
1694       sym = parent_st->n.sym;
1695       e->symtree = parent_st;           /* Point to the right thing.  */
1696
1697       if (sym->attr.flavor == FL_PROCEDURE
1698           || sym->attr.intrinsic
1699           || sym->attr.external)
1700         {
1701           if (gfc_resolve_expr (e) == FAILURE)
1702             return FAILURE;
1703           goto argument_list;
1704         }
1705
1706     got_variable:
1707       e->expr_type = EXPR_VARIABLE;
1708       e->ts = sym->ts;
1709       if (sym->as != NULL)
1710         {
1711           e->rank = sym->as->rank;
1712           e->ref = gfc_get_ref ();
1713           e->ref->type = REF_ARRAY;
1714           e->ref->u.ar.type = AR_FULL;
1715           e->ref->u.ar.as = sym->as;
1716         }
1717
1718       /* Expressions are assigned a default ts.type of BT_PROCEDURE in
1719          primary.c (match_actual_arg). If above code determines that it
1720          is a  variable instead, it needs to be resolved as it was not
1721          done at the beginning of this function.  */
1722       save_need_full_assumed_size = need_full_assumed_size;
1723       if (e->expr_type != EXPR_VARIABLE)
1724         need_full_assumed_size = 0;
1725       if (gfc_resolve_expr (e) != SUCCESS)
1726         return FAILURE;
1727       need_full_assumed_size = save_need_full_assumed_size;
1728
1729     argument_list:
1730       /* Check argument list functions %VAL, %LOC and %REF.  There is
1731          nothing to do for %REF.  */
1732       if (arg->name && arg->name[0] == '%')
1733         {
1734           if (strncmp ("%VAL", arg->name, 4) == 0)
1735             {
1736               if (e->ts.type == BT_CHARACTER || e->ts.type == BT_DERIVED)
1737                 {
1738                   gfc_error ("By-value argument at %L is not of numeric "
1739                              "type", &e->where);
1740                   return FAILURE;
1741                 }
1742
1743               if (e->rank)
1744                 {
1745                   gfc_error ("By-value argument at %L cannot be an array or "
1746                              "an array section", &e->where);
1747                 return FAILURE;
1748                 }
1749
1750               /* Intrinsics are still PROC_UNKNOWN here.  However,
1751                  since same file external procedures are not resolvable
1752                  in gfortran, it is a good deal easier to leave them to
1753                  intrinsic.c.  */
1754               if (ptype != PROC_UNKNOWN
1755                   && ptype != PROC_DUMMY
1756                   && ptype != PROC_EXTERNAL
1757                   && ptype != PROC_MODULE)
1758                 {
1759                   gfc_error ("By-value argument at %L is not allowed "
1760                              "in this context", &e->where);
1761                   return FAILURE;
1762                 }
1763             }
1764
1765           /* Statement functions have already been excluded above.  */
1766           else if (strncmp ("%LOC", arg->name, 4) == 0
1767                    && e->ts.type == BT_PROCEDURE)
1768             {
1769               if (e->symtree->n.sym->attr.proc == PROC_INTERNAL)
1770                 {
1771                   gfc_error ("Passing internal procedure at %L by location "
1772                              "not allowed", &e->where);
1773                   return FAILURE;
1774                 }
1775             }
1776         }
1777
1778       /* Fortran 2008, C1237.  */
1779       if (e->expr_type == EXPR_VARIABLE && gfc_is_coindexed (e)
1780           && gfc_has_ultimate_pointer (e))
1781         {
1782           gfc_error ("Coindexed actual argument at %L with ultimate pointer "
1783                      "component", &e->where);
1784           return FAILURE;
1785         }
1786     }
1787
1788   return SUCCESS;
1789 }
1790
1791
1792 /* Do the checks of the actual argument list that are specific to elemental
1793    procedures.  If called with c == NULL, we have a function, otherwise if
1794    expr == NULL, we have a subroutine.  */
1795
1796 static gfc_try
1797 resolve_elemental_actual (gfc_expr *expr, gfc_code *c)
1798 {
1799   gfc_actual_arglist *arg0;
1800   gfc_actual_arglist *arg;
1801   gfc_symbol *esym = NULL;
1802   gfc_intrinsic_sym *isym = NULL;
1803   gfc_expr *e = NULL;
1804   gfc_intrinsic_arg *iformal = NULL;
1805   gfc_formal_arglist *eformal = NULL;
1806   bool formal_optional = false;
1807   bool set_by_optional = false;
1808   int i;
1809   int rank = 0;
1810
1811   /* Is this an elemental procedure?  */
1812   if (expr && expr->value.function.actual != NULL)
1813     {
1814       if (expr->value.function.esym != NULL
1815           && expr->value.function.esym->attr.elemental)
1816         {
1817           arg0 = expr->value.function.actual;
1818           esym = expr->value.function.esym;
1819         }
1820       else if (expr->value.function.isym != NULL
1821                && expr->value.function.isym->elemental)
1822         {
1823           arg0 = expr->value.function.actual;
1824           isym = expr->value.function.isym;
1825         }
1826       else
1827         return SUCCESS;
1828     }
1829   else if (c && c->ext.actual != NULL)
1830     {
1831       arg0 = c->ext.actual;
1832       
1833       if (c->resolved_sym)
1834         esym = c->resolved_sym;
1835       else
1836         esym = c->symtree->n.sym;
1837       gcc_assert (esym);
1838
1839       if (!esym->attr.elemental)
1840         return SUCCESS;
1841     }
1842   else
1843     return SUCCESS;
1844
1845   /* The rank of an elemental is the rank of its array argument(s).  */
1846   for (arg = arg0; arg; arg = arg->next)
1847     {
1848       if (arg->expr != NULL && arg->expr->rank > 0)
1849         {
1850           rank = arg->expr->rank;
1851           if (arg->expr->expr_type == EXPR_VARIABLE
1852               && arg->expr->symtree->n.sym->attr.optional)
1853             set_by_optional = true;
1854
1855           /* Function specific; set the result rank and shape.  */
1856           if (expr)
1857             {
1858               expr->rank = rank;
1859               if (!expr->shape && arg->expr->shape)
1860                 {
1861                   expr->shape = gfc_get_shape (rank);
1862                   for (i = 0; i < rank; i++)
1863                     mpz_init_set (expr->shape[i], arg->expr->shape[i]);
1864                 }
1865             }
1866           break;
1867         }
1868     }
1869
1870   /* If it is an array, it shall not be supplied as an actual argument
1871      to an elemental procedure unless an array of the same rank is supplied
1872      as an actual argument corresponding to a nonoptional dummy argument of
1873      that elemental procedure(12.4.1.5).  */
1874   formal_optional = false;
1875   if (isym)
1876     iformal = isym->formal;
1877   else
1878     eformal = esym->formal;
1879
1880   for (arg = arg0; arg; arg = arg->next)
1881     {
1882       if (eformal)
1883         {
1884           if (eformal->sym && eformal->sym->attr.optional)
1885             formal_optional = true;
1886           eformal = eformal->next;
1887         }
1888       else if (isym && iformal)
1889         {
1890           if (iformal->optional)
1891             formal_optional = true;
1892           iformal = iformal->next;
1893         }
1894       else if (isym)
1895         formal_optional = true;
1896
1897       if (pedantic && arg->expr != NULL
1898           && arg->expr->expr_type == EXPR_VARIABLE
1899           && arg->expr->symtree->n.sym->attr.optional
1900           && formal_optional
1901           && arg->expr->rank
1902           && (set_by_optional || arg->expr->rank != rank)
1903           && !(isym && isym->id == GFC_ISYM_CONVERSION))
1904         {
1905           gfc_warning ("'%s' at %L is an array and OPTIONAL; IF IT IS "
1906                        "MISSING, it cannot be the actual argument of an "
1907                        "ELEMENTAL procedure unless there is a non-optional "
1908                        "argument with the same rank (12.4.1.5)",
1909                        arg->expr->symtree->n.sym->name, &arg->expr->where);
1910           return FAILURE;
1911         }
1912     }
1913
1914   for (arg = arg0; arg; arg = arg->next)
1915     {
1916       if (arg->expr == NULL || arg->expr->rank == 0)
1917         continue;
1918
1919       /* Being elemental, the last upper bound of an assumed size array
1920          argument must be present.  */
1921       if (resolve_assumed_size_actual (arg->expr))
1922         return FAILURE;
1923
1924       /* Elemental procedure's array actual arguments must conform.  */
1925       if (e != NULL)
1926         {
1927           if (gfc_check_conformance (arg->expr, e,
1928                                      "elemental procedure") == FAILURE)
1929             return FAILURE;
1930         }
1931       else
1932         e = arg->expr;
1933     }
1934
1935   /* INTENT(OUT) is only allowed for subroutines; if any actual argument
1936      is an array, the intent inout/out variable needs to be also an array.  */
1937   if (rank > 0 && esym && expr == NULL)
1938     for (eformal = esym->formal, arg = arg0; arg && eformal;
1939          arg = arg->next, eformal = eformal->next)
1940       if ((eformal->sym->attr.intent == INTENT_OUT
1941            || eformal->sym->attr.intent == INTENT_INOUT)
1942           && arg->expr && arg->expr->rank == 0)
1943         {
1944           gfc_error ("Actual argument at %L for INTENT(%s) dummy '%s' of "
1945                      "ELEMENTAL subroutine '%s' is a scalar, but another "
1946                      "actual argument is an array", &arg->expr->where,
1947                      (eformal->sym->attr.intent == INTENT_OUT) ? "OUT"
1948                      : "INOUT", eformal->sym->name, esym->name);
1949           return FAILURE;
1950         }
1951   return SUCCESS;
1952 }
1953
1954
1955 /* This function does the checking of references to global procedures
1956    as defined in sections 18.1 and 14.1, respectively, of the Fortran
1957    77 and 95 standards.  It checks for a gsymbol for the name, making
1958    one if it does not already exist.  If it already exists, then the
1959    reference being resolved must correspond to the type of gsymbol.
1960    Otherwise, the new symbol is equipped with the attributes of the
1961    reference.  The corresponding code that is called in creating
1962    global entities is parse.c.
1963
1964    In addition, for all but -std=legacy, the gsymbols are used to
1965    check the interfaces of external procedures from the same file.
1966    The namespace of the gsymbol is resolved and then, once this is
1967    done the interface is checked.  */
1968
1969
1970 static bool
1971 not_in_recursive (gfc_symbol *sym, gfc_namespace *gsym_ns)
1972 {
1973   if (!gsym_ns->proc_name->attr.recursive)
1974     return true;
1975
1976   if (sym->ns == gsym_ns)
1977     return false;
1978
1979   if (sym->ns->parent && sym->ns->parent == gsym_ns)
1980     return false;
1981
1982   return true;
1983 }
1984
1985 static bool
1986 not_entry_self_reference  (gfc_symbol *sym, gfc_namespace *gsym_ns)
1987 {
1988   if (gsym_ns->entries)
1989     {
1990       gfc_entry_list *entry = gsym_ns->entries;
1991
1992       for (; entry; entry = entry->next)
1993         {
1994           if (strcmp (sym->name, entry->sym->name) == 0)
1995             {
1996               if (strcmp (gsym_ns->proc_name->name,
1997                           sym->ns->proc_name->name) == 0)
1998                 return false;
1999
2000               if (sym->ns->parent
2001                   && strcmp (gsym_ns->proc_name->name,
2002                              sym->ns->parent->proc_name->name) == 0)
2003                 return false;
2004             }
2005         }
2006     }
2007   return true;
2008 }
2009
2010 static void
2011 resolve_global_procedure (gfc_symbol *sym, locus *where,
2012                           gfc_actual_arglist **actual, int sub)
2013 {
2014   gfc_gsymbol * gsym;
2015   gfc_namespace *ns;
2016   enum gfc_symbol_type type;
2017
2018   type = sub ? GSYM_SUBROUTINE : GSYM_FUNCTION;
2019
2020   gsym = gfc_get_gsymbol (sym->name);
2021
2022   if ((gsym->type != GSYM_UNKNOWN && gsym->type != type))
2023     gfc_global_used (gsym, where);
2024
2025   if (gfc_option.flag_whole_file
2026         && (sym->attr.if_source == IFSRC_UNKNOWN
2027             || sym->attr.if_source == IFSRC_IFBODY)
2028         && gsym->type != GSYM_UNKNOWN
2029         && gsym->ns
2030         && gsym->ns->resolved != -1
2031         && gsym->ns->proc_name
2032         && not_in_recursive (sym, gsym->ns)
2033         && not_entry_self_reference (sym, gsym->ns))
2034     {
2035       gfc_symbol *def_sym;
2036
2037       /* Resolve the gsymbol namespace if needed.  */
2038       if (!gsym->ns->resolved)
2039         {
2040           gfc_dt_list *old_dt_list;
2041           struct gfc_omp_saved_state old_omp_state;
2042
2043           /* Stash away derived types so that the backend_decls do not
2044              get mixed up.  */
2045           old_dt_list = gfc_derived_types;
2046           gfc_derived_types = NULL;
2047           /* And stash away openmp state.  */
2048           gfc_omp_save_and_clear_state (&old_omp_state);
2049
2050           gfc_resolve (gsym->ns);
2051
2052           /* Store the new derived types with the global namespace.  */
2053           if (gfc_derived_types)
2054             gsym->ns->derived_types = gfc_derived_types;
2055
2056           /* Restore the derived types of this namespace.  */
2057           gfc_derived_types = old_dt_list;
2058           /* And openmp state.  */
2059           gfc_omp_restore_state (&old_omp_state);
2060         }
2061
2062       /* Make sure that translation for the gsymbol occurs before
2063          the procedure currently being resolved.  */
2064       ns = gfc_global_ns_list;
2065       for (; ns && ns != gsym->ns; ns = ns->sibling)
2066         {
2067           if (ns->sibling == gsym->ns)
2068             {
2069               ns->sibling = gsym->ns->sibling;
2070               gsym->ns->sibling = gfc_global_ns_list;
2071               gfc_global_ns_list = gsym->ns;
2072               break;
2073             }
2074         }
2075
2076       def_sym = gsym->ns->proc_name;
2077       if (def_sym->attr.entry_master)
2078         {
2079           gfc_entry_list *entry;
2080           for (entry = gsym->ns->entries; entry; entry = entry->next)
2081             if (strcmp (entry->sym->name, sym->name) == 0)
2082               {
2083                 def_sym = entry->sym;
2084                 break;
2085               }
2086         }
2087
2088       /* Differences in constant character lengths.  */
2089       if (sym->attr.function && sym->ts.type == BT_CHARACTER)
2090         {
2091           long int l1 = 0, l2 = 0;
2092           gfc_charlen *cl1 = sym->ts.u.cl;
2093           gfc_charlen *cl2 = def_sym->ts.u.cl;
2094
2095           if (cl1 != NULL
2096               && cl1->length != NULL
2097               && cl1->length->expr_type == EXPR_CONSTANT)
2098             l1 = mpz_get_si (cl1->length->value.integer);
2099
2100           if (cl2 != NULL
2101               && cl2->length != NULL
2102               && cl2->length->expr_type == EXPR_CONSTANT)
2103             l2 = mpz_get_si (cl2->length->value.integer);
2104
2105           if (l1 && l2 && l1 != l2)
2106             gfc_error ("Character length mismatch in return type of "
2107                        "function '%s' at %L (%ld/%ld)", sym->name,
2108                        &sym->declared_at, l1, l2);
2109         }
2110
2111      /* Type mismatch of function return type and expected type.  */
2112      if (sym->attr.function
2113          && !gfc_compare_types (&sym->ts, &def_sym->ts))
2114         gfc_error ("Return type mismatch of function '%s' at %L (%s/%s)",
2115                    sym->name, &sym->declared_at, gfc_typename (&sym->ts),
2116                    gfc_typename (&def_sym->ts));
2117
2118       if (def_sym->formal && sym->attr.if_source != IFSRC_IFBODY)
2119         {
2120           gfc_formal_arglist *arg = def_sym->formal;
2121           for ( ; arg; arg = arg->next)
2122             if (!arg->sym)
2123               continue;
2124             /* F2003, 12.3.1.1 (2a); F2008, 12.4.2.2 (2a)  */
2125             else if (arg->sym->attr.allocatable
2126                      || arg->sym->attr.asynchronous
2127                      || arg->sym->attr.optional
2128                      || arg->sym->attr.pointer
2129                      || arg->sym->attr.target
2130                      || arg->sym->attr.value
2131                      || arg->sym->attr.volatile_)
2132               {
2133                 gfc_error ("Dummy argument '%s' of procedure '%s' at %L "
2134                            "has an attribute that requires an explicit "
2135                            "interface for this procedure", arg->sym->name,
2136                            sym->name, &sym->declared_at);
2137                 break;
2138               }
2139             /* F2003, 12.3.1.1 (2b); F2008, 12.4.2.2 (2b)  */
2140             else if (arg->sym && arg->sym->as
2141                      && arg->sym->as->type == AS_ASSUMED_SHAPE)
2142               {
2143                 gfc_error ("Procedure '%s' at %L with assumed-shape dummy "
2144                            "argument '%s' must have an explicit interface",
2145                            sym->name, &sym->declared_at, arg->sym->name);
2146                 break;
2147               }
2148             /* F2008, 12.4.2.2 (2c)  */
2149             else if (arg->sym->attr.codimension)
2150               {
2151                 gfc_error ("Procedure '%s' at %L with coarray dummy argument "
2152                            "'%s' must have an explicit interface",
2153                            sym->name, &sym->declared_at, arg->sym->name);
2154                 break;
2155               }
2156             /* F2003, 12.3.1.1 (2c); F2008, 12.4.2.2 (2d)   */
2157             else if (false) /* TODO: is a parametrized derived type  */
2158               {
2159                 gfc_error ("Procedure '%s' at %L with parametrized derived "
2160                            "type argument '%s' must have an explicit "
2161                            "interface", sym->name, &sym->declared_at,
2162                            arg->sym->name);
2163                 break;
2164               }
2165             /* F2003, 12.3.1.1 (2d); F2008, 12.4.2.2 (2e)   */
2166             else if (arg->sym->ts.type == BT_CLASS)
2167               {
2168                 gfc_error ("Procedure '%s' at %L with polymorphic dummy "
2169                            "argument '%s' must have an explicit interface",
2170                            sym->name, &sym->declared_at, arg->sym->name);
2171                 break;
2172               }
2173         }
2174
2175       if (def_sym->attr.function)
2176         {
2177           /* F2003, 12.3.1.1 (3a); F2008, 12.4.2.2 (3a) */
2178           if (def_sym->as && def_sym->as->rank
2179               && (!sym->as || sym->as->rank != def_sym->as->rank))
2180             gfc_error ("The reference to function '%s' at %L either needs an "
2181                        "explicit INTERFACE or the rank is incorrect", sym->name,
2182                        where);
2183
2184           /* F2003, 12.3.1.1 (3b); F2008, 12.4.2.2 (3b) */
2185           if ((def_sym->result->attr.pointer
2186                || def_sym->result->attr.allocatable)
2187                && (sym->attr.if_source != IFSRC_IFBODY
2188                    || def_sym->result->attr.pointer
2189                         != sym->result->attr.pointer
2190                    || def_sym->result->attr.allocatable
2191                         != sym->result->attr.allocatable))
2192             gfc_error ("Function '%s' at %L with a POINTER or ALLOCATABLE "
2193                        "result must have an explicit interface", sym->name,
2194                        where);
2195
2196           /* F2003, 12.3.1.1 (3c); F2008, 12.4.2.2 (3c)  */
2197           if (sym->ts.type == BT_CHARACTER && sym->attr.if_source != IFSRC_IFBODY
2198               && def_sym->ts.type == BT_CHARACTER && def_sym->ts.u.cl->length != NULL)
2199             {
2200               gfc_charlen *cl = sym->ts.u.cl;
2201
2202               if (!sym->attr.entry_master && sym->attr.if_source == IFSRC_UNKNOWN
2203                   && cl && cl->length && cl->length->expr_type != EXPR_CONSTANT)
2204                 {
2205                   gfc_error ("Nonconstant character-length function '%s' at %L "
2206                              "must have an explicit interface", sym->name,
2207                              &sym->declared_at);
2208                 }
2209             }
2210         }
2211
2212       /* F2003, 12.3.1.1 (4); F2008, 12.4.2.2 (4) */
2213       if (def_sym->attr.elemental && !sym->attr.elemental)
2214         {
2215           gfc_error ("ELEMENTAL procedure '%s' at %L must have an explicit "
2216                      "interface", sym->name, &sym->declared_at);
2217         }
2218
2219       /* F2003, 12.3.1.1 (5); F2008, 12.4.2.2 (5) */
2220       if (def_sym->attr.is_bind_c && !sym->attr.is_bind_c)
2221         {
2222           gfc_error ("Procedure '%s' at %L with BIND(C) attribute must have "
2223                      "an explicit interface", sym->name, &sym->declared_at);
2224         }
2225
2226       if (gfc_option.flag_whole_file == 1
2227           || ((gfc_option.warn_std & GFC_STD_LEGACY)
2228               && !(gfc_option.warn_std & GFC_STD_GNU)))
2229         gfc_errors_to_warnings (1);
2230
2231       if (sym->attr.if_source != IFSRC_IFBODY)  
2232         gfc_procedure_use (def_sym, actual, where);
2233
2234       gfc_errors_to_warnings (0);
2235     }
2236
2237   if (gsym->type == GSYM_UNKNOWN)
2238     {
2239       gsym->type = type;
2240       gsym->where = *where;
2241     }
2242
2243   gsym->used = 1;
2244 }
2245
2246
2247 /************* Function resolution *************/
2248
2249 /* Resolve a function call known to be generic.
2250    Section 14.1.2.4.1.  */
2251
2252 static match
2253 resolve_generic_f0 (gfc_expr *expr, gfc_symbol *sym)
2254 {
2255   gfc_symbol *s;
2256
2257   if (sym->attr.generic)
2258     {
2259       s = gfc_search_interface (sym->generic, 0, &expr->value.function.actual);
2260       if (s != NULL)
2261         {
2262           expr->value.function.name = s->name;
2263           expr->value.function.esym = s;
2264
2265           if (s->ts.type != BT_UNKNOWN)
2266             expr->ts = s->ts;
2267           else if (s->result != NULL && s->result->ts.type != BT_UNKNOWN)
2268             expr->ts = s->result->ts;
2269
2270           if (s->as != NULL)
2271             expr->rank = s->as->rank;
2272           else if (s->result != NULL && s->result->as != NULL)
2273             expr->rank = s->result->as->rank;
2274
2275           gfc_set_sym_referenced (expr->value.function.esym);
2276
2277           return MATCH_YES;
2278         }
2279
2280       /* TODO: Need to search for elemental references in generic
2281          interface.  */
2282     }
2283
2284   if (sym->attr.intrinsic)
2285     return gfc_intrinsic_func_interface (expr, 0);
2286
2287   return MATCH_NO;
2288 }
2289
2290
2291 static gfc_try
2292 resolve_generic_f (gfc_expr *expr)
2293 {
2294   gfc_symbol *sym;
2295   match m;
2296
2297   sym = expr->symtree->n.sym;
2298
2299   for (;;)
2300     {
2301       m = resolve_generic_f0 (expr, sym);
2302       if (m == MATCH_YES)
2303         return SUCCESS;
2304       else if (m == MATCH_ERROR)
2305         return FAILURE;
2306
2307 generic:
2308       if (sym->ns->parent == NULL)
2309         break;
2310       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2311
2312       if (sym == NULL)
2313         break;
2314       if (!generic_sym (sym))
2315         goto generic;
2316     }
2317
2318   /* Last ditch attempt.  See if the reference is to an intrinsic
2319      that possesses a matching interface.  14.1.2.4  */
2320   if (sym && !gfc_is_intrinsic (sym, 0, expr->where))
2321     {
2322       gfc_error ("There is no specific function for the generic '%s' at %L",
2323                  expr->symtree->n.sym->name, &expr->where);
2324       return FAILURE;
2325     }
2326
2327   m = gfc_intrinsic_func_interface (expr, 0);
2328   if (m == MATCH_YES)
2329     return SUCCESS;
2330   if (m == MATCH_NO)
2331     gfc_error ("Generic function '%s' at %L is not consistent with a "
2332                "specific intrinsic interface", expr->symtree->n.sym->name,
2333                &expr->where);
2334
2335   return FAILURE;
2336 }
2337
2338
2339 /* Resolve a function call known to be specific.  */
2340
2341 static match
2342 resolve_specific_f0 (gfc_symbol *sym, gfc_expr *expr)
2343 {
2344   match m;
2345
2346   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
2347     {
2348       if (sym->attr.dummy)
2349         {
2350           sym->attr.proc = PROC_DUMMY;
2351           goto found;
2352         }
2353
2354       sym->attr.proc = PROC_EXTERNAL;
2355       goto found;
2356     }
2357
2358   if (sym->attr.proc == PROC_MODULE
2359       || sym->attr.proc == PROC_ST_FUNCTION
2360       || sym->attr.proc == PROC_INTERNAL)
2361     goto found;
2362
2363   if (sym->attr.intrinsic)
2364     {
2365       m = gfc_intrinsic_func_interface (expr, 1);
2366       if (m == MATCH_YES)
2367         return MATCH_YES;
2368       if (m == MATCH_NO)
2369         gfc_error ("Function '%s' at %L is INTRINSIC but is not compatible "
2370                    "with an intrinsic", sym->name, &expr->where);
2371
2372       return MATCH_ERROR;
2373     }
2374
2375   return MATCH_NO;
2376
2377 found:
2378   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2379
2380   if (sym->result)
2381     expr->ts = sym->result->ts;
2382   else
2383     expr->ts = sym->ts;
2384   expr->value.function.name = sym->name;
2385   expr->value.function.esym = sym;
2386   if (sym->as != NULL)
2387     expr->rank = sym->as->rank;
2388
2389   return MATCH_YES;
2390 }
2391
2392
2393 static gfc_try
2394 resolve_specific_f (gfc_expr *expr)
2395 {
2396   gfc_symbol *sym;
2397   match m;
2398
2399   sym = expr->symtree->n.sym;
2400
2401   for (;;)
2402     {
2403       m = resolve_specific_f0 (sym, expr);
2404       if (m == MATCH_YES)
2405         return SUCCESS;
2406       if (m == MATCH_ERROR)
2407         return FAILURE;
2408
2409       if (sym->ns->parent == NULL)
2410         break;
2411
2412       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
2413
2414       if (sym == NULL)
2415         break;
2416     }
2417
2418   gfc_error ("Unable to resolve the specific function '%s' at %L",
2419              expr->symtree->n.sym->name, &expr->where);
2420
2421   return SUCCESS;
2422 }
2423
2424
2425 /* Resolve a procedure call not known to be generic nor specific.  */
2426
2427 static gfc_try
2428 resolve_unknown_f (gfc_expr *expr)
2429 {
2430   gfc_symbol *sym;
2431   gfc_typespec *ts;
2432
2433   sym = expr->symtree->n.sym;
2434
2435   if (sym->attr.dummy)
2436     {
2437       sym->attr.proc = PROC_DUMMY;
2438       expr->value.function.name = sym->name;
2439       goto set_type;
2440     }
2441
2442   /* See if we have an intrinsic function reference.  */
2443
2444   if (gfc_is_intrinsic (sym, 0, expr->where))
2445     {
2446       if (gfc_intrinsic_func_interface (expr, 1) == MATCH_YES)
2447         return SUCCESS;
2448       return FAILURE;
2449     }
2450
2451   /* The reference is to an external name.  */
2452
2453   sym->attr.proc = PROC_EXTERNAL;
2454   expr->value.function.name = sym->name;
2455   expr->value.function.esym = expr->symtree->n.sym;
2456
2457   if (sym->as != NULL)
2458     expr->rank = sym->as->rank;
2459
2460   /* Type of the expression is either the type of the symbol or the
2461      default type of the symbol.  */
2462
2463 set_type:
2464   gfc_procedure_use (sym, &expr->value.function.actual, &expr->where);
2465
2466   if (sym->ts.type != BT_UNKNOWN)
2467     expr->ts = sym->ts;
2468   else
2469     {
2470       ts = gfc_get_default_type (sym->name, sym->ns);
2471
2472       if (ts->type == BT_UNKNOWN)
2473         {
2474           gfc_error ("Function '%s' at %L has no IMPLICIT type",
2475                      sym->name, &expr->where);
2476           return FAILURE;
2477         }
2478       else
2479         expr->ts = *ts;
2480     }
2481
2482   return SUCCESS;
2483 }
2484
2485
2486 /* Return true, if the symbol is an external procedure.  */
2487 static bool
2488 is_external_proc (gfc_symbol *sym)
2489 {
2490   if (!sym->attr.dummy && !sym->attr.contained
2491         && !(sym->attr.intrinsic
2492               || gfc_is_intrinsic (sym, sym->attr.subroutine, sym->declared_at))
2493         && sym->attr.proc != PROC_ST_FUNCTION
2494         && !sym->attr.proc_pointer
2495         && !sym->attr.use_assoc
2496         && sym->name)
2497     return true;
2498
2499   return false;
2500 }
2501
2502
2503 /* Figure out if a function reference is pure or not.  Also set the name
2504    of the function for a potential error message.  Return nonzero if the
2505    function is PURE, zero if not.  */
2506 static int
2507 pure_stmt_function (gfc_expr *, gfc_symbol *);
2508
2509 static int
2510 pure_function (gfc_expr *e, const char **name)
2511 {
2512   int pure;
2513
2514   *name = NULL;
2515
2516   if (e->symtree != NULL
2517         && e->symtree->n.sym != NULL
2518         && e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2519     return pure_stmt_function (e, e->symtree->n.sym);
2520
2521   if (e->value.function.esym)
2522     {
2523       pure = gfc_pure (e->value.function.esym);
2524       *name = e->value.function.esym->name;
2525     }
2526   else if (e->value.function.isym)
2527     {
2528       pure = e->value.function.isym->pure
2529              || e->value.function.isym->elemental;
2530       *name = e->value.function.isym->name;
2531     }
2532   else
2533     {
2534       /* Implicit functions are not pure.  */
2535       pure = 0;
2536       *name = e->value.function.name;
2537     }
2538
2539   return pure;
2540 }
2541
2542
2543 static bool
2544 impure_stmt_fcn (gfc_expr *e, gfc_symbol *sym,
2545                  int *f ATTRIBUTE_UNUSED)
2546 {
2547   const char *name;
2548
2549   /* Don't bother recursing into other statement functions
2550      since they will be checked individually for purity.  */
2551   if (e->expr_type != EXPR_FUNCTION
2552         || !e->symtree
2553         || e->symtree->n.sym == sym
2554         || e->symtree->n.sym->attr.proc == PROC_ST_FUNCTION)
2555     return false;
2556
2557   return pure_function (e, &name) ? false : true;
2558 }
2559
2560
2561 static int
2562 pure_stmt_function (gfc_expr *e, gfc_symbol *sym)
2563 {
2564   return gfc_traverse_expr (e, sym, impure_stmt_fcn, 0) ? 0 : 1;
2565 }
2566
2567
2568 static gfc_try
2569 is_scalar_expr_ptr (gfc_expr *expr)
2570 {
2571   gfc_try retval = SUCCESS;
2572   gfc_ref *ref;
2573   int start;
2574   int end;
2575
2576   /* See if we have a gfc_ref, which means we have a substring, array
2577      reference, or a component.  */
2578   if (expr->ref != NULL)
2579     {
2580       ref = expr->ref;
2581       while (ref->next != NULL)
2582         ref = ref->next;
2583
2584       switch (ref->type)
2585         {
2586         case REF_SUBSTRING:
2587           if (ref->u.ss.start == NULL || ref->u.ss.end == NULL
2588               || gfc_dep_compare_expr (ref->u.ss.start, ref->u.ss.end) != 0)
2589             retval = FAILURE;
2590           break;
2591
2592         case REF_ARRAY:
2593           if (ref->u.ar.type == AR_ELEMENT)
2594             retval = SUCCESS;
2595           else if (ref->u.ar.type == AR_FULL)
2596             {
2597               /* The user can give a full array if the array is of size 1.  */
2598               if (ref->u.ar.as != NULL
2599                   && ref->u.ar.as->rank == 1
2600                   && ref->u.ar.as->type == AS_EXPLICIT
2601                   && ref->u.ar.as->lower[0] != NULL
2602                   && ref->u.ar.as->lower[0]->expr_type == EXPR_CONSTANT
2603                   && ref->u.ar.as->upper[0] != NULL
2604                   && ref->u.ar.as->upper[0]->expr_type == EXPR_CONSTANT)
2605                 {
2606                   /* If we have a character string, we need to check if
2607                      its length is one.  */
2608                   if (expr->ts.type == BT_CHARACTER)
2609                     {
2610                       if (expr->ts.u.cl == NULL
2611                           || expr->ts.u.cl->length == NULL
2612                           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1)
2613                           != 0)
2614                         retval = FAILURE;
2615                     }
2616                   else
2617                     {
2618                       /* We have constant lower and upper bounds.  If the
2619                          difference between is 1, it can be considered a
2620                          scalar.  
2621                          FIXME: Use gfc_dep_compare_expr instead.  */
2622                       start = (int) mpz_get_si
2623                                 (ref->u.ar.as->lower[0]->value.integer);
2624                       end = (int) mpz_get_si
2625                                 (ref->u.ar.as->upper[0]->value.integer);
2626                       if (end - start + 1 != 1)
2627                         retval = FAILURE;
2628                    }
2629                 }
2630               else
2631                 retval = FAILURE;
2632             }
2633           else
2634             retval = FAILURE;
2635           break;
2636         default:
2637           retval = SUCCESS;
2638           break;
2639         }
2640     }
2641   else if (expr->ts.type == BT_CHARACTER && expr->rank == 0)
2642     {
2643       /* Character string.  Make sure it's of length 1.  */
2644       if (expr->ts.u.cl == NULL
2645           || expr->ts.u.cl->length == NULL
2646           || mpz_cmp_si (expr->ts.u.cl->length->value.integer, 1) != 0)
2647         retval = FAILURE;
2648     }
2649   else if (expr->rank != 0)
2650     retval = FAILURE;
2651
2652   return retval;
2653 }
2654
2655
2656 /* Match one of the iso_c_binding functions (c_associated or c_loc)
2657    and, in the case of c_associated, set the binding label based on
2658    the arguments.  */
2659
2660 static gfc_try
2661 gfc_iso_c_func_interface (gfc_symbol *sym, gfc_actual_arglist *args,
2662                           gfc_symbol **new_sym)
2663 {
2664   char name[GFC_MAX_SYMBOL_LEN + 1];
2665   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
2666   int optional_arg = 0;
2667   gfc_try retval = SUCCESS;
2668   gfc_symbol *args_sym;
2669   gfc_typespec *arg_ts;
2670   symbol_attribute arg_attr;
2671
2672   if (args->expr->expr_type == EXPR_CONSTANT
2673       || args->expr->expr_type == EXPR_OP
2674       || args->expr->expr_type == EXPR_NULL)
2675     {
2676       gfc_error ("Argument to '%s' at %L is not a variable",
2677                  sym->name, &(args->expr->where));
2678       return FAILURE;
2679     }
2680
2681   args_sym = args->expr->symtree->n.sym;
2682
2683   /* The typespec for the actual arg should be that stored in the expr
2684      and not necessarily that of the expr symbol (args_sym), because
2685      the actual expression could be a part-ref of the expr symbol.  */
2686   arg_ts = &(args->expr->ts);
2687   arg_attr = gfc_expr_attr (args->expr);
2688     
2689   if (sym->intmod_sym_id == ISOCBINDING_ASSOCIATED)
2690     {
2691       /* If the user gave two args then they are providing something for
2692          the optional arg (the second cptr).  Therefore, set the name and
2693          binding label to the c_associated for two cptrs.  Otherwise,
2694          set c_associated to expect one cptr.  */
2695       if (args->next)
2696         {
2697           /* two args.  */
2698           sprintf (name, "%s_2", sym->name);
2699           sprintf (binding_label, "%s_2", sym->binding_label);
2700           optional_arg = 1;
2701         }
2702       else
2703         {
2704           /* one arg.  */
2705           sprintf (name, "%s_1", sym->name);
2706           sprintf (binding_label, "%s_1", sym->binding_label);
2707           optional_arg = 0;
2708         }
2709
2710       /* Get a new symbol for the version of c_associated that
2711          will get called.  */
2712       *new_sym = get_iso_c_sym (sym, name, binding_label, optional_arg);
2713     }
2714   else if (sym->intmod_sym_id == ISOCBINDING_LOC
2715            || sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2716     {
2717       sprintf (name, "%s", sym->name);
2718       sprintf (binding_label, "%s", sym->binding_label);
2719
2720       /* Error check the call.  */
2721       if (args->next != NULL)
2722         {
2723           gfc_error_now ("More actual than formal arguments in '%s' "
2724                          "call at %L", name, &(args->expr->where));
2725           retval = FAILURE;
2726         }
2727       else if (sym->intmod_sym_id == ISOCBINDING_LOC)
2728         {
2729           gfc_ref *ref;
2730           bool seen_section;
2731
2732           /* Make sure we have either the target or pointer attribute.  */
2733           if (!arg_attr.target && !arg_attr.pointer)
2734             {
2735               gfc_error_now ("Parameter '%s' to '%s' at %L must be either "
2736                              "a TARGET or an associated pointer",
2737                              args_sym->name,
2738                              sym->name, &(args->expr->where));
2739               retval = FAILURE;
2740             }
2741
2742           if (gfc_is_coindexed (args->expr))
2743             {
2744               gfc_error_now ("Coindexed argument not permitted"
2745                              " in '%s' call at %L", name,
2746                              &(args->expr->where));
2747               retval = FAILURE;
2748             }
2749
2750           /* Follow references to make sure there are no array
2751              sections.  */
2752           seen_section = false;
2753
2754           for (ref=args->expr->ref; ref; ref = ref->next)
2755             {
2756               if (ref->type == REF_ARRAY)
2757                 {
2758                   if (ref->u.ar.type == AR_SECTION)
2759                     seen_section = true;
2760
2761                   if (ref->u.ar.type != AR_ELEMENT)
2762                     {
2763                       gfc_ref *r;
2764                       for (r = ref->next; r; r=r->next)
2765                         if (r->type == REF_COMPONENT)
2766                           {
2767                             gfc_error_now ("Array section not permitted"
2768                                            " in '%s' call at %L", name,
2769                                            &(args->expr->where));
2770                             retval = FAILURE;
2771                             break;
2772                           }
2773                     }
2774                 }
2775             }
2776
2777           if (seen_section && retval == SUCCESS)
2778             gfc_warning ("Array section in '%s' call at %L", name,
2779                          &(args->expr->where));
2780                          
2781           /* See if we have interoperable type and type param.  */
2782           if (verify_c_interop (arg_ts) == SUCCESS
2783               || gfc_check_any_c_kind (arg_ts) == SUCCESS)
2784             {
2785               if (args_sym->attr.target == 1)
2786                 {
2787                   /* Case 1a, section 15.1.2.5, J3/04-007: variable that
2788                      has the target attribute and is interoperable.  */
2789                   /* Case 1b, section 15.1.2.5, J3/04-007: allocated
2790                      allocatable variable that has the TARGET attribute and
2791                      is not an array of zero size.  */
2792                   if (args_sym->attr.allocatable == 1)
2793                     {
2794                       if (args_sym->attr.dimension != 0 
2795                           && (args_sym->as && args_sym->as->rank == 0))
2796                         {
2797                           gfc_error_now ("Allocatable variable '%s' used as a "
2798                                          "parameter to '%s' at %L must not be "
2799                                          "an array of zero size",
2800                                          args_sym->name, sym->name,
2801                                          &(args->expr->where));
2802                           retval = FAILURE;
2803                         }
2804                     }
2805                   else
2806                     {
2807                       /* A non-allocatable target variable with C
2808                          interoperable type and type parameters must be
2809                          interoperable.  */
2810                       if (args_sym && args_sym->attr.dimension)
2811                         {
2812                           if (args_sym->as->type == AS_ASSUMED_SHAPE)
2813                             {
2814                               gfc_error ("Assumed-shape array '%s' at %L "
2815                                          "cannot be an argument to the "
2816                                          "procedure '%s' because "
2817                                          "it is not C interoperable",
2818                                          args_sym->name,
2819                                          &(args->expr->where), sym->name);
2820                               retval = FAILURE;
2821                             }
2822                           else if (args_sym->as->type == AS_DEFERRED)
2823                             {
2824                               gfc_error ("Deferred-shape array '%s' at %L "
2825                                          "cannot be an argument to the "
2826                                          "procedure '%s' because "
2827                                          "it is not C interoperable",
2828                                          args_sym->name,
2829                                          &(args->expr->where), sym->name);
2830                               retval = FAILURE;
2831                             }
2832                         }
2833                               
2834                       /* Make sure it's not a character string.  Arrays of
2835                          any type should be ok if the variable is of a C
2836                          interoperable type.  */
2837                       if (arg_ts->type == BT_CHARACTER)
2838                         if (arg_ts->u.cl != NULL
2839                             && (arg_ts->u.cl->length == NULL
2840                                 || arg_ts->u.cl->length->expr_type
2841                                    != EXPR_CONSTANT
2842                                 || mpz_cmp_si
2843                                     (arg_ts->u.cl->length->value.integer, 1)
2844                                    != 0)
2845                             && is_scalar_expr_ptr (args->expr) != SUCCESS)
2846                           {
2847                             gfc_error_now ("CHARACTER argument '%s' to '%s' "
2848                                            "at %L must have a length of 1",
2849                                            args_sym->name, sym->name,
2850                                            &(args->expr->where));
2851                             retval = FAILURE;
2852                           }
2853                     }
2854                 }
2855               else if (arg_attr.pointer
2856                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2857                 {
2858                   /* Case 1c, section 15.1.2.5, J3/04-007: an associated
2859                      scalar pointer.  */
2860                   gfc_error_now ("Argument '%s' to '%s' at %L must be an "
2861                                  "associated scalar POINTER", args_sym->name,
2862                                  sym->name, &(args->expr->where));
2863                   retval = FAILURE;
2864                 }
2865             }
2866           else
2867             {
2868               /* The parameter is not required to be C interoperable.  If it
2869                  is not C interoperable, it must be a nonpolymorphic scalar
2870                  with no length type parameters.  It still must have either
2871                  the pointer or target attribute, and it can be
2872                  allocatable (but must be allocated when c_loc is called).  */
2873               if (args->expr->rank != 0 
2874                   && is_scalar_expr_ptr (args->expr) != SUCCESS)
2875                 {
2876                   gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2877                                  "scalar", args_sym->name, sym->name,
2878                                  &(args->expr->where));
2879                   retval = FAILURE;
2880                 }
2881               else if (arg_ts->type == BT_CHARACTER 
2882                        && is_scalar_expr_ptr (args->expr) != SUCCESS)
2883                 {
2884                   gfc_error_now ("CHARACTER argument '%s' to '%s' at "
2885                                  "%L must have a length of 1",
2886                                  args_sym->name, sym->name,
2887                                  &(args->expr->where));
2888                   retval = FAILURE;
2889                 }
2890               else if (arg_ts->type == BT_CLASS)
2891                 {
2892                   gfc_error_now ("Parameter '%s' to '%s' at %L must not be "
2893                                  "polymorphic", args_sym->name, sym->name,
2894                                  &(args->expr->where));
2895                   retval = FAILURE;
2896                 }
2897             }
2898         }
2899       else if (sym->intmod_sym_id == ISOCBINDING_FUNLOC)
2900         {
2901           if (args_sym->attr.flavor != FL_PROCEDURE)
2902             {
2903               /* TODO: Update this error message to allow for procedure
2904                  pointers once they are implemented.  */
2905               gfc_error_now ("Parameter '%s' to '%s' at %L must be a "
2906                              "procedure",
2907                              args_sym->name, sym->name,
2908                              &(args->expr->where));
2909               retval = FAILURE;
2910             }
2911           else if (args_sym->attr.is_bind_c != 1)
2912             {
2913               gfc_error_now ("Parameter '%s' to '%s' at %L must be "
2914                              "BIND(C)",
2915                              args_sym->name, sym->name,
2916                              &(args->expr->where));
2917               retval = FAILURE;
2918             }
2919         }
2920       
2921       /* for c_loc/c_funloc, the new symbol is the same as the old one */
2922       *new_sym = sym;
2923     }
2924   else
2925     {
2926       gfc_internal_error ("gfc_iso_c_func_interface(): Unhandled "
2927                           "iso_c_binding function: '%s'!\n", sym->name);
2928     }
2929
2930   return retval;
2931 }
2932
2933
2934 /* Resolve a function call, which means resolving the arguments, then figuring
2935    out which entity the name refers to.  */
2936
2937 static gfc_try
2938 resolve_function (gfc_expr *expr)
2939 {
2940   gfc_actual_arglist *arg;
2941   gfc_symbol *sym;
2942   const char *name;
2943   gfc_try t;
2944   int temp;
2945   procedure_type p = PROC_INTRINSIC;
2946   bool no_formal_args;
2947
2948   sym = NULL;
2949   if (expr->symtree)
2950     sym = expr->symtree->n.sym;
2951
2952   /* If this is a procedure pointer component, it has already been resolved.  */
2953   if (gfc_is_proc_ptr_comp (expr, NULL))
2954     return SUCCESS;
2955   
2956   if (sym && sym->attr.intrinsic
2957       && resolve_intrinsic (sym, &expr->where) == FAILURE)
2958     return FAILURE;
2959
2960   if (sym && (sym->attr.flavor == FL_VARIABLE || sym->attr.subroutine))
2961     {
2962       gfc_error ("'%s' at %L is not a function", sym->name, &expr->where);
2963       return FAILURE;
2964     }
2965
2966   /* If this ia a deferred TBP with an abstract interface (which may
2967      of course be referenced), expr->value.function.esym will be set.  */
2968   if (sym && sym->attr.abstract && !expr->value.function.esym)
2969     {
2970       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
2971                  sym->name, &expr->where);
2972       return FAILURE;
2973     }
2974
2975   /* Switch off assumed size checking and do this again for certain kinds
2976      of procedure, once the procedure itself is resolved.  */
2977   need_full_assumed_size++;
2978
2979   if (expr->symtree && expr->symtree->n.sym)
2980     p = expr->symtree->n.sym->attr.proc;
2981
2982   if (expr->value.function.isym && expr->value.function.isym->inquiry)
2983     inquiry_argument = true;
2984   no_formal_args = sym && is_external_proc (sym) && sym->formal == NULL;
2985
2986   if (resolve_actual_arglist (expr->value.function.actual,
2987                               p, no_formal_args) == FAILURE)
2988     {
2989       inquiry_argument = false;
2990       return FAILURE;
2991     }
2992
2993   inquiry_argument = false;
2994  
2995   /* Need to setup the call to the correct c_associated, depending on
2996      the number of cptrs to user gives to compare.  */
2997   if (sym && sym->attr.is_iso_c == 1)
2998     {
2999       if (gfc_iso_c_func_interface (sym, expr->value.function.actual, &sym)
3000           == FAILURE)
3001         return FAILURE;
3002       
3003       /* Get the symtree for the new symbol (resolved func).
3004          the old one will be freed later, when it's no longer used.  */
3005       gfc_find_sym_tree (sym->name, sym->ns, 1, &(expr->symtree));
3006     }
3007   
3008   /* Resume assumed_size checking.  */
3009   need_full_assumed_size--;
3010
3011   /* If the procedure is external, check for usage.  */
3012   if (sym && is_external_proc (sym))
3013     resolve_global_procedure (sym, &expr->where,
3014                               &expr->value.function.actual, 0);
3015
3016   if (sym && sym->ts.type == BT_CHARACTER
3017       && sym->ts.u.cl
3018       && sym->ts.u.cl->length == NULL
3019       && !sym->attr.dummy
3020       && !sym->ts.deferred
3021       && expr->value.function.esym == NULL
3022       && !sym->attr.contained)
3023     {
3024       /* Internal procedures are taken care of in resolve_contained_fntype.  */
3025       gfc_error ("Function '%s' is declared CHARACTER(*) and cannot "
3026                  "be used at %L since it is not a dummy argument",
3027                  sym->name, &expr->where);
3028       return FAILURE;
3029     }
3030
3031   /* See if function is already resolved.  */
3032
3033   if (expr->value.function.name != NULL)
3034     {
3035       if (expr->ts.type == BT_UNKNOWN)
3036         expr->ts = sym->ts;
3037       t = SUCCESS;
3038     }
3039   else
3040     {
3041       /* Apply the rules of section 14.1.2.  */
3042
3043       switch (procedure_kind (sym))
3044         {
3045         case PTYPE_GENERIC:
3046           t = resolve_generic_f (expr);
3047           break;
3048
3049         case PTYPE_SPECIFIC:
3050           t = resolve_specific_f (expr);
3051           break;
3052
3053         case PTYPE_UNKNOWN:
3054           t = resolve_unknown_f (expr);
3055           break;
3056
3057         default:
3058           gfc_internal_error ("resolve_function(): bad function type");
3059         }
3060     }
3061
3062   /* If the expression is still a function (it might have simplified),
3063      then we check to see if we are calling an elemental function.  */
3064
3065   if (expr->expr_type != EXPR_FUNCTION)
3066     return t;
3067
3068   temp = need_full_assumed_size;
3069   need_full_assumed_size = 0;
3070
3071   if (resolve_elemental_actual (expr, NULL) == FAILURE)
3072     return FAILURE;
3073
3074   if (omp_workshare_flag
3075       && expr->value.function.esym
3076       && ! gfc_elemental (expr->value.function.esym))
3077     {
3078       gfc_error ("User defined non-ELEMENTAL function '%s' at %L not allowed "
3079                  "in WORKSHARE construct", expr->value.function.esym->name,
3080                  &expr->where);
3081       t = FAILURE;
3082     }
3083
3084 #define GENERIC_ID expr->value.function.isym->id
3085   else if (expr->value.function.actual != NULL
3086            && expr->value.function.isym != NULL
3087            && GENERIC_ID != GFC_ISYM_LBOUND
3088            && GENERIC_ID != GFC_ISYM_LEN
3089            && GENERIC_ID != GFC_ISYM_LOC
3090            && GENERIC_ID != GFC_ISYM_PRESENT)
3091     {
3092       /* Array intrinsics must also have the last upper bound of an
3093          assumed size array argument.  UBOUND and SIZE have to be
3094          excluded from the check if the second argument is anything
3095          than a constant.  */
3096
3097       for (arg = expr->value.function.actual; arg; arg = arg->next)
3098         {
3099           if ((GENERIC_ID == GFC_ISYM_UBOUND || GENERIC_ID == GFC_ISYM_SIZE)
3100               && arg->next != NULL && arg->next->expr)
3101             {
3102               if (arg->next->expr->expr_type != EXPR_CONSTANT)
3103                 break;
3104
3105               if (arg->next->name && strncmp(arg->next->name, "kind", 4) == 0)
3106                 break;
3107
3108               if ((int)mpz_get_si (arg->next->expr->value.integer)
3109                         < arg->expr->rank)
3110                 break;
3111             }
3112
3113           if (arg->expr != NULL
3114               && arg->expr->rank > 0
3115               && resolve_assumed_size_actual (arg->expr))
3116             return FAILURE;
3117         }
3118     }
3119 #undef GENERIC_ID
3120
3121   need_full_assumed_size = temp;
3122   name = NULL;
3123
3124   if (!pure_function (expr, &name) && name)
3125     {
3126       if (forall_flag)
3127         {
3128           gfc_error ("reference to non-PURE function '%s' at %L inside a "
3129                      "FORALL %s", name, &expr->where,
3130                      forall_flag == 2 ? "mask" : "block");
3131           t = FAILURE;
3132         }
3133       else if (gfc_pure (NULL))
3134         {
3135           gfc_error ("Function reference to '%s' at %L is to a non-PURE "
3136                      "procedure within a PURE procedure", name, &expr->where);
3137           t = FAILURE;
3138         }
3139     }
3140
3141   if (!pure_function (expr, &name) && name && gfc_implicit_pure (NULL))
3142     gfc_current_ns->proc_name->attr.implicit_pure = 0;
3143
3144   /* Functions without the RECURSIVE attribution are not allowed to
3145    * call themselves.  */
3146   if (expr->value.function.esym && !expr->value.function.esym->attr.recursive)
3147     {
3148       gfc_symbol *esym;
3149       esym = expr->value.function.esym;
3150
3151       if (is_illegal_recursion (esym, gfc_current_ns))
3152       {
3153         if (esym->attr.entry && esym->ns->entries)
3154           gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3155                      " function '%s' is not RECURSIVE",
3156                      esym->name, &expr->where, esym->ns->entries->sym->name);
3157         else
3158           gfc_error ("Function '%s' at %L cannot be called recursively, as it"
3159                      " is not RECURSIVE", esym->name, &expr->where);
3160
3161         t = FAILURE;
3162       }
3163     }
3164
3165   /* Character lengths of use associated functions may contains references to
3166      symbols not referenced from the current program unit otherwise.  Make sure
3167      those symbols are marked as referenced.  */
3168
3169   if (expr->ts.type == BT_CHARACTER && expr->value.function.esym
3170       && expr->value.function.esym->attr.use_assoc)
3171     {
3172       gfc_expr_set_symbols_referenced (expr->ts.u.cl->length);
3173     }
3174
3175   /* Make sure that the expression has a typespec that works.  */
3176   if (expr->ts.type == BT_UNKNOWN)
3177     {
3178       if (expr->symtree->n.sym->result
3179             && expr->symtree->n.sym->result->ts.type != BT_UNKNOWN
3180             && !expr->symtree->n.sym->result->attr.proc_pointer)
3181         expr->ts = expr->symtree->n.sym->result->ts;
3182     }
3183
3184   return t;
3185 }
3186
3187
3188 /************* Subroutine resolution *************/
3189
3190 static void
3191 pure_subroutine (gfc_code *c, gfc_symbol *sym)
3192 {
3193   if (gfc_pure (sym))
3194     return;
3195
3196   if (forall_flag)
3197     gfc_error ("Subroutine call to '%s' in FORALL block at %L is not PURE",
3198                sym->name, &c->loc);
3199   else if (gfc_pure (NULL))
3200     gfc_error ("Subroutine call to '%s' at %L is not PURE", sym->name,
3201                &c->loc);
3202 }
3203
3204
3205 static match
3206 resolve_generic_s0 (gfc_code *c, gfc_symbol *sym)
3207 {
3208   gfc_symbol *s;
3209
3210   if (sym->attr.generic)
3211     {
3212       s = gfc_search_interface (sym->generic, 1, &c->ext.actual);
3213       if (s != NULL)
3214         {
3215           c->resolved_sym = s;
3216           pure_subroutine (c, s);
3217           return MATCH_YES;
3218         }
3219
3220       /* TODO: Need to search for elemental references in generic interface.  */
3221     }
3222
3223   if (sym->attr.intrinsic)
3224     return gfc_intrinsic_sub_interface (c, 0);
3225
3226   return MATCH_NO;
3227 }
3228
3229
3230 static gfc_try
3231 resolve_generic_s (gfc_code *c)
3232 {
3233   gfc_symbol *sym;
3234   match m;
3235
3236   sym = c->symtree->n.sym;
3237
3238   for (;;)
3239     {
3240       m = resolve_generic_s0 (c, sym);
3241       if (m == MATCH_YES)
3242         return SUCCESS;
3243       else if (m == MATCH_ERROR)
3244         return FAILURE;
3245
3246 generic:
3247       if (sym->ns->parent == NULL)
3248         break;
3249       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3250
3251       if (sym == NULL)
3252         break;
3253       if (!generic_sym (sym))
3254         goto generic;
3255     }
3256
3257   /* Last ditch attempt.  See if the reference is to an intrinsic
3258      that possesses a matching interface.  14.1.2.4  */
3259   sym = c->symtree->n.sym;
3260
3261   if (!gfc_is_intrinsic (sym, 1, c->loc))
3262     {
3263       gfc_error ("There is no specific subroutine for the generic '%s' at %L",
3264                  sym->name, &c->loc);
3265       return FAILURE;
3266     }
3267
3268   m = gfc_intrinsic_sub_interface (c, 0);
3269   if (m == MATCH_YES)
3270     return SUCCESS;
3271   if (m == MATCH_NO)
3272     gfc_error ("Generic subroutine '%s' at %L is not consistent with an "
3273                "intrinsic subroutine interface", sym->name, &c->loc);
3274
3275   return FAILURE;
3276 }
3277
3278
3279 /* Set the name and binding label of the subroutine symbol in the call
3280    expression represented by 'c' to include the type and kind of the
3281    second parameter.  This function is for resolving the appropriate
3282    version of c_f_pointer() and c_f_procpointer().  For example, a
3283    call to c_f_pointer() for a default integer pointer could have a
3284    name of c_f_pointer_i4.  If no second arg exists, which is an error
3285    for these two functions, it defaults to the generic symbol's name
3286    and binding label.  */
3287
3288 static void
3289 set_name_and_label (gfc_code *c, gfc_symbol *sym,
3290                     char *name, char *binding_label)
3291 {
3292   gfc_expr *arg = NULL;
3293   char type;
3294   int kind;
3295
3296   /* The second arg of c_f_pointer and c_f_procpointer determines
3297      the type and kind for the procedure name.  */
3298   arg = c->ext.actual->next->expr;
3299
3300   if (arg != NULL)
3301     {
3302       /* Set up the name to have the given symbol's name,
3303          plus the type and kind.  */
3304       /* a derived type is marked with the type letter 'u' */
3305       if (arg->ts.type == BT_DERIVED)
3306         {
3307           type = 'd';
3308           kind = 0; /* set the kind as 0 for now */
3309         }
3310       else
3311         {
3312           type = gfc_type_letter (arg->ts.type);
3313           kind = arg->ts.kind;
3314         }
3315
3316       if (arg->ts.type == BT_CHARACTER)
3317         /* Kind info for character strings not needed.  */
3318         kind = 0;
3319
3320       sprintf (name, "%s_%c%d", sym->name, type, kind);
3321       /* Set up the binding label as the given symbol's label plus
3322          the type and kind.  */
3323       sprintf (binding_label, "%s_%c%d", sym->binding_label, type, kind);
3324     }
3325   else
3326     {
3327       /* If the second arg is missing, set the name and label as
3328          was, cause it should at least be found, and the missing
3329          arg error will be caught by compare_parameters().  */
3330       sprintf (name, "%s", sym->name);
3331       sprintf (binding_label, "%s", sym->binding_label);
3332     }
3333    
3334   return;
3335 }
3336
3337
3338 /* Resolve a generic version of the iso_c_binding procedure given
3339    (sym) to the specific one based on the type and kind of the
3340    argument(s).  Currently, this function resolves c_f_pointer() and
3341    c_f_procpointer based on the type and kind of the second argument
3342    (FPTR).  Other iso_c_binding procedures aren't specially handled.
3343    Upon successfully exiting, c->resolved_sym will hold the resolved
3344    symbol.  Returns MATCH_ERROR if an error occurred; MATCH_YES
3345    otherwise.  */
3346
3347 match
3348 gfc_iso_c_sub_interface (gfc_code *c, gfc_symbol *sym)
3349 {
3350   gfc_symbol *new_sym;
3351   /* this is fine, since we know the names won't use the max */
3352   char name[GFC_MAX_SYMBOL_LEN + 1];
3353   char binding_label[GFC_MAX_BINDING_LABEL_LEN + 1];
3354   /* default to success; will override if find error */
3355   match m = MATCH_YES;
3356
3357   /* Make sure the actual arguments are in the necessary order (based on the 
3358      formal args) before resolving.  */
3359   gfc_procedure_use (sym, &c->ext.actual, &(c->loc));
3360
3361   if ((sym->intmod_sym_id == ISOCBINDING_F_POINTER) ||
3362       (sym->intmod_sym_id == ISOCBINDING_F_PROCPOINTER))
3363     {
3364       set_name_and_label (c, sym, name, binding_label);
3365       
3366       if (sym->intmod_sym_id == ISOCBINDING_F_POINTER)
3367         {
3368           if (c->ext.actual != NULL && c->ext.actual->next != NULL)
3369             {
3370               /* Make sure we got a third arg if the second arg has non-zero
3371                  rank.  We must also check that the type and rank are
3372                  correct since we short-circuit this check in
3373                  gfc_procedure_use() (called above to sort actual args).  */
3374               if (c->ext.actual->next->expr->rank != 0)
3375                 {
3376                   if(c->ext.actual->next->next == NULL 
3377                      || c->ext.actual->next->next->expr == NULL)
3378                     {
3379                       m = MATCH_ERROR;
3380                       gfc_error ("Missing SHAPE parameter for call to %s "
3381                                  "at %L", sym->name, &(c->loc));
3382                     }
3383                   else if (c->ext.actual->next->next->expr->ts.type
3384                            != BT_INTEGER
3385                            || c->ext.actual->next->next->expr->rank != 1)
3386                     {
3387                       m = MATCH_ERROR;
3388                       gfc_error ("SHAPE parameter for call to %s at %L must "
3389                                  "be a rank 1 INTEGER array", sym->name,
3390                                  &(c->loc));
3391                     }
3392                 }
3393             }
3394         }
3395       
3396       if (m != MATCH_ERROR)
3397         {
3398           /* the 1 means to add the optional arg to formal list */
3399           new_sym = get_iso_c_sym (sym, name, binding_label, 1);
3400          
3401           /* for error reporting, say it's declared where the original was */
3402           new_sym->declared_at = sym->declared_at;
3403         }
3404     }
3405   else
3406     {
3407       /* no differences for c_loc or c_funloc */
3408       new_sym = sym;
3409     }
3410
3411   /* set the resolved symbol */
3412   if (m != MATCH_ERROR)
3413     c->resolved_sym = new_sym;
3414   else
3415     c->resolved_sym = sym;
3416   
3417   return m;
3418 }
3419
3420
3421 /* Resolve a subroutine call known to be specific.  */
3422
3423 static match
3424 resolve_specific_s0 (gfc_code *c, gfc_symbol *sym)
3425 {
3426   match m;
3427
3428   if(sym->attr.is_iso_c)
3429     {
3430       m = gfc_iso_c_sub_interface (c,sym);
3431       return m;
3432     }
3433   
3434   if (sym->attr.external || sym->attr.if_source == IFSRC_IFBODY)
3435     {
3436       if (sym->attr.dummy)
3437         {
3438           sym->attr.proc = PROC_DUMMY;
3439           goto found;
3440         }
3441
3442       sym->attr.proc = PROC_EXTERNAL;
3443       goto found;
3444     }
3445
3446   if (sym->attr.proc == PROC_MODULE || sym->attr.proc == PROC_INTERNAL)
3447     goto found;
3448
3449   if (sym->attr.intrinsic)
3450     {
3451       m = gfc_intrinsic_sub_interface (c, 1);
3452       if (m == MATCH_YES)
3453         return MATCH_YES;
3454       if (m == MATCH_NO)
3455         gfc_error ("Subroutine '%s' at %L is INTRINSIC but is not compatible "
3456                    "with an intrinsic", sym->name, &c->loc);
3457
3458       return MATCH_ERROR;
3459     }
3460
3461   return MATCH_NO;
3462
3463 found:
3464   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3465
3466   c->resolved_sym = sym;
3467   pure_subroutine (c, sym);
3468
3469   return MATCH_YES;
3470 }
3471
3472
3473 static gfc_try
3474 resolve_specific_s (gfc_code *c)
3475 {
3476   gfc_symbol *sym;
3477   match m;
3478
3479   sym = c->symtree->n.sym;
3480
3481   for (;;)
3482     {
3483       m = resolve_specific_s0 (c, sym);
3484       if (m == MATCH_YES)
3485         return SUCCESS;
3486       if (m == MATCH_ERROR)
3487         return FAILURE;
3488
3489       if (sym->ns->parent == NULL)
3490         break;
3491
3492       gfc_find_symbol (sym->name, sym->ns->parent, 1, &sym);
3493
3494       if (sym == NULL)
3495         break;
3496     }
3497
3498   sym = c->symtree->n.sym;
3499   gfc_error ("Unable to resolve the specific subroutine '%s' at %L",
3500              sym->name, &c->loc);
3501
3502   return FAILURE;
3503 }
3504
3505
3506 /* Resolve a subroutine call not known to be generic nor specific.  */
3507
3508 static gfc_try
3509 resolve_unknown_s (gfc_code *c)
3510 {
3511   gfc_symbol *sym;
3512
3513   sym = c->symtree->n.sym;
3514
3515   if (sym->attr.dummy)
3516     {
3517       sym->attr.proc = PROC_DUMMY;
3518       goto found;
3519     }
3520
3521   /* See if we have an intrinsic function reference.  */
3522
3523   if (gfc_is_intrinsic (sym, 1, c->loc))
3524     {
3525       if (gfc_intrinsic_sub_interface (c, 1) == MATCH_YES)
3526         return SUCCESS;
3527       return FAILURE;
3528     }
3529
3530   /* The reference is to an external name.  */
3531
3532 found:
3533   gfc_procedure_use (sym, &c->ext.actual, &c->loc);
3534
3535   c->resolved_sym = sym;
3536
3537   pure_subroutine (c, sym);
3538
3539   return SUCCESS;
3540 }
3541
3542
3543 /* Resolve a subroutine call.  Although it was tempting to use the same code
3544    for functions, subroutines and functions are stored differently and this
3545    makes things awkward.  */
3546
3547 static gfc_try
3548 resolve_call (gfc_code *c)
3549 {
3550   gfc_try t;
3551   procedure_type ptype = PROC_INTRINSIC;
3552   gfc_symbol *csym, *sym;
3553   bool no_formal_args;
3554
3555   csym = c->symtree ? c->symtree->n.sym : NULL;
3556
3557   if (csym && csym->ts.type != BT_UNKNOWN)
3558     {
3559       gfc_error ("'%s' at %L has a type, which is not consistent with "
3560                  "the CALL at %L", csym->name, &csym->declared_at, &c->loc);
3561       return FAILURE;
3562     }
3563
3564   if (csym && gfc_current_ns->parent && csym->ns != gfc_current_ns)
3565     {
3566       gfc_symtree *st;
3567       gfc_find_sym_tree (csym->name, gfc_current_ns, 1, &st);
3568       sym = st ? st->n.sym : NULL;
3569       if (sym && csym != sym
3570               && sym->ns == gfc_current_ns
3571               && sym->attr.flavor == FL_PROCEDURE
3572               && sym->attr.contained)
3573         {
3574           sym->refs++;
3575           if (csym->attr.generic)
3576             c->symtree->n.sym = sym;
3577           else
3578             c->symtree = st;
3579           csym = c->symtree->n.sym;
3580         }
3581     }
3582
3583   /* If this ia a deferred TBP with an abstract interface
3584      (which may of course be referenced), c->expr1 will be set.  */
3585   if (csym && csym->attr.abstract && !c->expr1)
3586     {
3587       gfc_error ("ABSTRACT INTERFACE '%s' must not be referenced at %L",
3588                  csym->name, &c->loc);
3589       return FAILURE;
3590     }
3591
3592   /* Subroutines without the RECURSIVE attribution are not allowed to
3593    * call themselves.  */
3594   if (csym && is_illegal_recursion (csym, gfc_current_ns))
3595     {
3596       if (csym->attr.entry && csym->ns->entries)
3597         gfc_error ("ENTRY '%s' at %L cannot be called recursively, as"
3598                    " subroutine '%s' is not RECURSIVE",
3599                    csym->name, &c->loc, csym->ns->entries->sym->name);
3600       else
3601         gfc_error ("SUBROUTINE '%s' at %L cannot be called recursively, as it"
3602                    " is not RECURSIVE", csym->name, &c->loc);
3603
3604       t = FAILURE;
3605     }
3606
3607   /* Switch off assumed size checking and do this again for certain kinds
3608      of procedure, once the procedure itself is resolved.  */
3609   need_full_assumed_size++;
3610
3611   if (csym)
3612     ptype = csym->attr.proc;
3613
3614   no_formal_args = csym && is_external_proc (csym) && csym->formal == NULL;
3615   if (resolve_actual_arglist (c->ext.actual, ptype,
3616                               no_formal_args) == FAILURE)
3617     return FAILURE;
3618
3619   /* Resume assumed_size checking.  */
3620   need_full_assumed_size--;
3621
3622   /* If external, check for usage.  */
3623   if (csym && is_external_proc (csym))
3624     resolve_global_procedure (csym, &c->loc, &c->ext.actual, 1);
3625
3626   t = SUCCESS;
3627   if (c->resolved_sym == NULL)
3628     {
3629       c->resolved_isym = NULL;
3630       switch (procedure_kind (csym))
3631         {
3632         case PTYPE_GENERIC:
3633           t = resolve_generic_s (c);
3634           break;
3635
3636         case PTYPE_SPECIFIC:
3637           t = resolve_specific_s (c);
3638           break;
3639
3640         case PTYPE_UNKNOWN:
3641           t = resolve_unknown_s (c);
3642           break;
3643
3644         default:
3645           gfc_internal_error ("resolve_subroutine(): bad function type");
3646         }
3647     }
3648
3649   /* Some checks of elemental subroutine actual arguments.  */
3650   if (resolve_elemental_actual (NULL, c) == FAILURE)
3651     return FAILURE;
3652
3653   return t;
3654 }
3655
3656
3657 /* Compare the shapes of two arrays that have non-NULL shapes.  If both
3658    op1->shape and op2->shape are non-NULL return SUCCESS if their shapes
3659    match.  If both op1->shape and op2->shape are non-NULL return FAILURE
3660    if their shapes do not match.  If either op1->shape or op2->shape is
3661    NULL, return SUCCESS.  */
3662
3663 static gfc_try
3664 compare_shapes (gfc_expr *op1, gfc_expr *op2)
3665 {
3666   gfc_try t;
3667   int i;
3668
3669   t = SUCCESS;
3670
3671   if (op1->shape != NULL && op2->shape != NULL)
3672     {
3673       for (i = 0; i < op1->rank; i++)
3674         {
3675           if (mpz_cmp (op1->shape[i], op2->shape[i]) != 0)
3676            {
3677              gfc_error ("Shapes for operands at %L and %L are not conformable",
3678                          &op1->where, &op2->where);
3679              t = FAILURE;
3680              break;
3681            }
3682         }
3683     }
3684
3685   return t;
3686 }
3687
3688
3689 /* Resolve an operator expression node.  This can involve replacing the
3690    operation with a user defined function call.  */
3691
3692 static gfc_try
3693 resolve_operator (gfc_expr *e)
3694 {
3695   gfc_expr *op1, *op2;
3696   char msg[200];
3697   bool dual_locus_error;
3698   gfc_try t;
3699
3700   /* Resolve all subnodes-- give them types.  */
3701
3702   switch (e->value.op.op)
3703     {
3704     default:
3705       if (gfc_resolve_expr (e->value.op.op2) == FAILURE)
3706         return FAILURE;
3707
3708     /* Fall through...  */
3709
3710     case INTRINSIC_NOT:
3711     case INTRINSIC_UPLUS:
3712     case INTRINSIC_UMINUS:
3713     case INTRINSIC_PARENTHESES:
3714       if (gfc_resolve_expr (e->value.op.op1) == FAILURE)
3715         return FAILURE;
3716       break;
3717     }
3718
3719   /* Typecheck the new node.  */
3720
3721   op1 = e->value.op.op1;
3722   op2 = e->value.op.op2;
3723   dual_locus_error = false;
3724
3725   if ((op1 && op1->expr_type == EXPR_NULL)
3726       || (op2 && op2->expr_type == EXPR_NULL))
3727     {
3728       sprintf (msg, _("Invalid context for NULL() pointer at %%L"));
3729       goto bad_op;
3730     }
3731
3732   switch (e->value.op.op)
3733     {
3734     case INTRINSIC_UPLUS:
3735     case INTRINSIC_UMINUS:
3736       if (op1->ts.type == BT_INTEGER
3737           || op1->ts.type == BT_REAL
3738           || op1->ts.type == BT_COMPLEX)
3739         {
3740           e->ts = op1->ts;
3741           break;
3742         }
3743
3744       sprintf (msg, _("Operand of unary numeric operator '%s' at %%L is %s"),
3745                gfc_op2string (e->value.op.op), gfc_typename (&e->ts));
3746       goto bad_op;
3747
3748     case INTRINSIC_PLUS:
3749     case INTRINSIC_MINUS:
3750     case INTRINSIC_TIMES:
3751     case INTRINSIC_DIVIDE:
3752     case INTRINSIC_POWER:
3753       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3754         {
3755           gfc_type_convert_binary (e, 1);
3756           break;
3757         }
3758
3759       sprintf (msg,
3760                _("Operands of binary numeric operator '%s' at %%L are %s/%s"),
3761                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3762                gfc_typename (&op2->ts));
3763       goto bad_op;
3764
3765     case INTRINSIC_CONCAT:
3766       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3767           && op1->ts.kind == op2->ts.kind)
3768         {
3769           e->ts.type = BT_CHARACTER;
3770           e->ts.kind = op1->ts.kind;
3771           break;
3772         }
3773
3774       sprintf (msg,
3775                _("Operands of string concatenation operator at %%L are %s/%s"),
3776                gfc_typename (&op1->ts), gfc_typename (&op2->ts));
3777       goto bad_op;
3778
3779     case INTRINSIC_AND:
3780     case INTRINSIC_OR:
3781     case INTRINSIC_EQV:
3782     case INTRINSIC_NEQV:
3783       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3784         {
3785           e->ts.type = BT_LOGICAL;
3786           e->ts.kind = gfc_kind_max (op1, op2);
3787           if (op1->ts.kind < e->ts.kind)
3788             gfc_convert_type (op1, &e->ts, 2);
3789           else if (op2->ts.kind < e->ts.kind)
3790             gfc_convert_type (op2, &e->ts, 2);
3791           break;
3792         }
3793
3794       sprintf (msg, _("Operands of logical operator '%s' at %%L are %s/%s"),
3795                gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3796                gfc_typename (&op2->ts));
3797
3798       goto bad_op;
3799
3800     case INTRINSIC_NOT:
3801       if (op1->ts.type == BT_LOGICAL)
3802         {
3803           e->ts.type = BT_LOGICAL;
3804           e->ts.kind = op1->ts.kind;
3805           break;
3806         }
3807
3808       sprintf (msg, _("Operand of .not. operator at %%L is %s"),
3809                gfc_typename (&op1->ts));
3810       goto bad_op;
3811
3812     case INTRINSIC_GT:
3813     case INTRINSIC_GT_OS:
3814     case INTRINSIC_GE:
3815     case INTRINSIC_GE_OS:
3816     case INTRINSIC_LT:
3817     case INTRINSIC_LT_OS:
3818     case INTRINSIC_LE:
3819     case INTRINSIC_LE_OS:
3820       if (op1->ts.type == BT_COMPLEX || op2->ts.type == BT_COMPLEX)
3821         {
3822           strcpy (msg, _("COMPLEX quantities cannot be compared at %L"));
3823           goto bad_op;
3824         }
3825
3826       /* Fall through...  */
3827
3828     case INTRINSIC_EQ:
3829     case INTRINSIC_EQ_OS:
3830     case INTRINSIC_NE:
3831     case INTRINSIC_NE_OS:
3832       if (op1->ts.type == BT_CHARACTER && op2->ts.type == BT_CHARACTER
3833           && op1->ts.kind == op2->ts.kind)
3834         {
3835           e->ts.type = BT_LOGICAL;
3836           e->ts.kind = gfc_default_logical_kind;
3837           break;
3838         }
3839
3840       if (gfc_numeric_ts (&op1->ts) && gfc_numeric_ts (&op2->ts))
3841         {
3842           gfc_type_convert_binary (e, 1);
3843
3844           e->ts.type = BT_LOGICAL;
3845           e->ts.kind = gfc_default_logical_kind;
3846           break;
3847         }
3848
3849       if (op1->ts.type == BT_LOGICAL && op2->ts.type == BT_LOGICAL)
3850         sprintf (msg,
3851                  _("Logicals at %%L must be compared with %s instead of %s"),
3852                  (e->value.op.op == INTRINSIC_EQ 
3853                   || e->value.op.op == INTRINSIC_EQ_OS)
3854                  ? ".eqv." : ".neqv.", gfc_op2string (e->value.op.op));
3855       else
3856         sprintf (msg,
3857                  _("Operands of comparison operator '%s' at %%L are %s/%s"),
3858                  gfc_op2string (e->value.op.op), gfc_typename (&op1->ts),
3859                  gfc_typename (&op2->ts));
3860
3861       goto bad_op;
3862
3863     case INTRINSIC_USER:
3864       if (e->value.op.uop->op == NULL)
3865         sprintf (msg, _("Unknown operator '%s' at %%L"), e->value.op.uop->name);
3866       else if (op2 == NULL)
3867         sprintf (msg, _("Operand of user operator '%s' at %%L is %s"),
3868                  e->value.op.uop->name, gfc_typename (&op1->ts));
3869       else
3870         {
3871           sprintf (msg, _("Operands of user operator '%s' at %%L are %s/%s"),
3872                    e->value.op.uop->name, gfc_typename (&op1->ts),
3873                    gfc_typename (&op2->ts));
3874           e->value.op.uop->op->sym->attr.referenced = 1;
3875         }
3876
3877       goto bad_op;
3878
3879     case INTRINSIC_PARENTHESES:
3880       e->ts = op1->ts;
3881       if (e->ts.type == BT_CHARACTER)
3882         e->ts.u.cl = op1->ts.u.cl;
3883       break;
3884
3885     default:
3886       gfc_internal_error ("resolve_operator(): Bad intrinsic");
3887     }
3888
3889   /* Deal with arrayness of an operand through an operator.  */
3890
3891   t = SUCCESS;
3892
3893   switch (e->value.op.op)
3894     {
3895     case INTRINSIC_PLUS:
3896     case INTRINSIC_MINUS:
3897     case INTRINSIC_TIMES:
3898     case INTRINSIC_DIVIDE:
3899     case INTRINSIC_POWER:
3900     case INTRINSIC_CONCAT:
3901     case INTRINSIC_AND:
3902     case INTRINSIC_OR:
3903     case INTRINSIC_EQV:
3904     case INTRINSIC_NEQV:
3905     case INTRINSIC_EQ:
3906     case INTRINSIC_EQ_OS:
3907     case INTRINSIC_NE:
3908     case INTRINSIC_NE_OS:
3909     case INTRINSIC_GT:
3910     case INTRINSIC_GT_OS:
3911     case INTRINSIC_GE:
3912     case INTRINSIC_GE_OS:
3913     case INTRINSIC_LT:
3914     case INTRINSIC_LT_OS:
3915     case INTRINSIC_LE:
3916     case INTRINSIC_LE_OS:
3917
3918       if (op1->rank == 0 && op2->rank == 0)
3919         e->rank = 0;
3920
3921       if (op1->rank == 0 && op2->rank != 0)
3922         {
3923           e->rank = op2->rank;
3924
3925           if (e->shape == NULL)
3926             e->shape = gfc_copy_shape (op2->shape, op2->rank);
3927         }
3928
3929       if (op1->rank != 0 && op2->rank == 0)
3930         {
3931           e->rank = op1->rank;
3932
3933           if (e->shape == NULL)
3934             e->shape = gfc_copy_shape (op1->shape, op1->rank);
3935         }
3936
3937       if (op1->rank != 0 && op2->rank != 0)
3938         {
3939           if (op1->rank == op2->rank)
3940             {
3941               e->rank = op1->rank;
3942               if (e->shape == NULL)
3943                 {
3944                   t = compare_shapes (op1, op2);
3945                   if (t == FAILURE)
3946                     e->shape = NULL;
3947                   else
3948                     e->shape = gfc_copy_shape (op1->shape, op1->rank);
3949                 }
3950             }
3951           else
3952             {
3953               /* Allow higher level expressions to work.  */
3954               e->rank = 0;
3955
3956               /* Try user-defined operators, and otherwise throw an error.  */
3957               dual_locus_error = true;
3958               sprintf (msg,
3959                        _("Inconsistent ranks for operator at %%L and %%L"));
3960               goto bad_op;
3961             }
3962         }
3963
3964       break;
3965
3966     case INTRINSIC_PARENTHESES:
3967     case INTRINSIC_NOT:
3968     case INTRINSIC_UPLUS:
3969     case INTRINSIC_UMINUS:
3970       /* Simply copy arrayness attribute */
3971       e->rank = op1->rank;
3972
3973       if (e->shape == NULL)
3974         e->shape = gfc_copy_shape (op1->shape, op1->rank);
3975
3976       break;
3977
3978     default:
3979       break;
3980     }
3981
3982   /* Attempt to simplify the expression.  */
3983   if (t == SUCCESS)
3984     {
3985       t = gfc_simplify_expr (e, 0);
3986       /* Some calls do not succeed in simplification and return FAILURE
3987          even though there is no error; e.g. variable references to
3988          PARAMETER arrays.  */
3989       if (!gfc_is_constant_expr (e))
3990         t = SUCCESS;
3991     }
3992   return t;
3993
3994 bad_op:
3995
3996   {
3997     bool real_error;
3998     if (gfc_extend_expr (e, &real_error) == SUCCESS)
3999       return SUCCESS;
4000
4001     if (real_error)
4002       return FAILURE;
4003   }
4004
4005   if (dual_locus_error)
4006     gfc_error (msg, &op1->where, &op2->where);
4007   else
4008     gfc_error (msg, &e->where);
4009
4010   return FAILURE;
4011 }
4012
4013
4014 /************** Array resolution subroutines **************/
4015
4016 typedef enum
4017 { CMP_LT, CMP_EQ, CMP_GT, CMP_UNKNOWN }
4018 comparison;
4019
4020 /* Compare two integer expressions.  */
4021
4022 static comparison
4023 compare_bound (gfc_expr *a, gfc_expr *b)
4024 {
4025   int i;
4026
4027   if (a == NULL || a->expr_type != EXPR_CONSTANT
4028       || b == NULL || b->expr_type != EXPR_CONSTANT)
4029     return CMP_UNKNOWN;
4030
4031   /* If either of the types isn't INTEGER, we must have
4032      raised an error earlier.  */
4033
4034   if (a->ts.type != BT_INTEGER || b->ts.type != BT_INTEGER)
4035     return CMP_UNKNOWN;
4036
4037   i = mpz_cmp (a->value.integer, b->value.integer);
4038
4039   if (i < 0)
4040     return CMP_LT;
4041   if (i > 0)
4042     return CMP_GT;
4043   return CMP_EQ;
4044 }
4045
4046
4047 /* Compare an integer expression with an integer.  */
4048
4049 static comparison
4050 compare_bound_int (gfc_expr *a, int b)
4051 {
4052   int i;
4053
4054   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4055     return CMP_UNKNOWN;
4056
4057   if (a->ts.type != BT_INTEGER)
4058     gfc_internal_error ("compare_bound_int(): Bad expression");
4059
4060   i = mpz_cmp_si (a->value.integer, b);
4061
4062   if (i < 0)
4063     return CMP_LT;
4064   if (i > 0)
4065     return CMP_GT;
4066   return CMP_EQ;
4067 }
4068
4069
4070 /* Compare an integer expression with a mpz_t.  */
4071
4072 static comparison
4073 compare_bound_mpz_t (gfc_expr *a, mpz_t b)
4074 {
4075   int i;
4076
4077   if (a == NULL || a->expr_type != EXPR_CONSTANT)
4078     return CMP_UNKNOWN;
4079
4080   if (a->ts.type != BT_INTEGER)
4081     gfc_internal_error ("compare_bound_int(): Bad expression");
4082
4083   i = mpz_cmp (a->value.integer, b);
4084
4085   if (i < 0)
4086     return CMP_LT;
4087   if (i > 0)
4088     return CMP_GT;
4089   return CMP_EQ;
4090 }
4091
4092
4093 /* Compute the last value of a sequence given by a triplet.  
4094    Return 0 if it wasn't able to compute the last value, or if the
4095    sequence if empty, and 1 otherwise.  */
4096
4097 static int
4098 compute_last_value_for_triplet (gfc_expr *start, gfc_expr *end,
4099                                 gfc_expr *stride, mpz_t last)
4100 {
4101   mpz_t rem;
4102
4103   if (start == NULL || start->expr_type != EXPR_CONSTANT
4104       || end == NULL || end->expr_type != EXPR_CONSTANT
4105       || (stride != NULL && stride->expr_type != EXPR_CONSTANT))
4106     return 0;
4107
4108   if (start->ts.type != BT_INTEGER || end->ts.type != BT_INTEGER
4109       || (stride != NULL && stride->ts.type != BT_INTEGER))
4110     return 0;
4111
4112   if (stride == NULL || compare_bound_int(stride, 1) == CMP_EQ)
4113     {
4114       if (compare_bound (start, end) == CMP_GT)
4115         return 0;
4116       mpz_set (last, end->value.integer);
4117       return 1;
4118     }
4119
4120   if (compare_bound_int (stride, 0) == CMP_GT)
4121     {
4122       /* Stride is positive */
4123       if (mpz_cmp (start->value.integer, end->value.integer) > 0)
4124         return 0;
4125     }
4126   else
4127     {
4128       /* Stride is negative */
4129       if (mpz_cmp (start->value.integer, end->value.integer) < 0)
4130         return 0;
4131     }
4132
4133   mpz_init (rem);
4134   mpz_sub (rem, end->value.integer, start->value.integer);
4135   mpz_tdiv_r (rem, rem, stride->value.integer);
4136   mpz_sub (last, end->value.integer, rem);
4137   mpz_clear (rem);
4138
4139   return 1;
4140 }
4141
4142
4143 /* Compare a single dimension of an array reference to the array
4144    specification.  */
4145
4146 static gfc_try
4147 check_dimension (int i, gfc_array_ref *ar, gfc_array_spec *as)
4148 {
4149   mpz_t last_value;
4150
4151   if (ar->dimen_type[i] == DIMEN_STAR)
4152     {
4153       gcc_assert (ar->stride[i] == NULL);
4154       /* This implies [*] as [*:] and [*:3] are not possible.  */
4155       if (ar->start[i] == NULL)
4156         {
4157           gcc_assert (ar->end[i] == NULL);
4158           return SUCCESS;
4159         }
4160     }
4161
4162 /* Given start, end and stride values, calculate the minimum and
4163    maximum referenced indexes.  */
4164
4165   switch (ar->dimen_type[i])
4166     {
4167     case DIMEN_VECTOR:
4168     case DIMEN_THIS_IMAGE:
4169       break;
4170
4171     case DIMEN_STAR:
4172     case DIMEN_ELEMENT:
4173       if (compare_bound (ar->start[i], as->lower[i]) == CMP_LT)
4174         {
4175           if (i < as->rank)
4176             gfc_warning ("Array reference at %L is out of bounds "
4177                          "(%ld < %ld) in dimension %d", &ar->c_where[i],
4178                          mpz_get_si (ar->start[i]->value.integer),
4179                          mpz_get_si (as->lower[i]->value.integer), i+1);
4180           else
4181             gfc_warning ("Array reference at %L is out of bounds "
4182                          "(%ld < %ld) in codimension %d", &ar->c_where[i],
4183                          mpz_get_si (ar->start[i]->value.integer),
4184                          mpz_get_si (as->lower[i]->value.integer),
4185                          i + 1 - as->rank);
4186           return SUCCESS;
4187         }
4188       if (compare_bound (ar->start[i], as->upper[i]) == CMP_GT)
4189         {
4190           if (i < as->rank)
4191             gfc_warning ("Array reference at %L is out of bounds "
4192                          "(%ld > %ld) in dimension %d", &ar->c_where[i],
4193                          mpz_get_si (ar->start[i]->value.integer),
4194                          mpz_get_si (as->upper[i]->value.integer), i+1);
4195           else
4196             gfc_warning ("Array reference at %L is out of bounds "
4197                          "(%ld > %ld) in codimension %d", &ar->c_where[i],
4198                          mpz_get_si (ar->start[i]->value.integer),
4199                          mpz_get_si (as->upper[i]->value.integer),
4200                          i + 1 - as->rank);
4201           return SUCCESS;
4202         }
4203
4204       break;
4205
4206     case DIMEN_RANGE:
4207       {
4208 #define AR_START (ar->start[i] ? ar->start[i] : as->lower[i])
4209 #define AR_END (ar->end[i] ? ar->end[i] : as->upper[i])
4210
4211         comparison comp_start_end = compare_bound (AR_START, AR_END);
4212
4213         /* Check for zero stride, which is not allowed.  */
4214         if (compare_bound_int (ar->stride[i], 0) == CMP_EQ)
4215           {
4216             gfc_error ("Illegal stride of zero at %L", &ar->c_where[i]);
4217             return FAILURE;
4218           }
4219
4220         /* if start == len || (stride > 0 && start < len)
4221                            || (stride < 0 && start > len),
4222            then the array section contains at least one element.  In this
4223            case, there is an out-of-bounds access if
4224            (start < lower || start > upper).  */
4225         if (compare_bound (AR_START, AR_END) == CMP_EQ
4226             || ((compare_bound_int (ar->stride[i], 0) == CMP_GT
4227                  || ar->stride[i] == NULL) && comp_start_end == CMP_LT)
4228             || (compare_bound_int (ar->stride[i], 0) == CMP_LT
4229                 && comp_start_end == CMP_GT))
4230           {
4231             if (compare_bound (AR_START, as->lower[i]) == CMP_LT)
4232               {
4233                 gfc_warning ("Lower array reference at %L is out of bounds "
4234                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4235                        mpz_get_si (AR_START->value.integer),
4236                        mpz_get_si (as->lower[i]->value.integer), i+1);
4237                 return SUCCESS;
4238               }
4239             if (compare_bound (AR_START, as->upper[i]) == CMP_GT)
4240               {
4241                 gfc_warning ("Lower array reference at %L is out of bounds "
4242                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4243                        mpz_get_si (AR_START->value.integer),
4244                        mpz_get_si (as->upper[i]->value.integer), i+1);
4245                 return SUCCESS;
4246               }
4247           }
4248
4249         /* If we can compute the highest index of the array section,
4250            then it also has to be between lower and upper.  */
4251         mpz_init (last_value);
4252         if (compute_last_value_for_triplet (AR_START, AR_END, ar->stride[i],
4253                                             last_value))
4254           {
4255             if (compare_bound_mpz_t (as->lower[i], last_value) == CMP_GT)
4256               {
4257                 gfc_warning ("Upper array reference at %L is out of bounds "
4258                        "(%ld < %ld) in dimension %d", &ar->c_where[i],
4259                        mpz_get_si (last_value),
4260                        mpz_get_si (as->lower[i]->value.integer), i+1);
4261                 mpz_clear (last_value);
4262                 return SUCCESS;
4263               }
4264             if (compare_bound_mpz_t (as->upper[i], last_value) == CMP_LT)
4265               {
4266                 gfc_warning ("Upper array reference at %L is out of bounds "
4267                        "(%ld > %ld) in dimension %d", &ar->c_where[i],
4268                        mpz_get_si (last_value),
4269                        mpz_get_si (as->upper[i]->value.integer), i+1);
4270                 mpz_clear (last_value);
4271                 return SUCCESS;
4272               }
4273           }
4274         mpz_clear (last_value);
4275
4276 #undef AR_START
4277 #undef AR_END
4278       }
4279       break;
4280
4281     default:
4282       gfc_internal_error ("check_dimension(): Bad array reference");
4283     }
4284
4285   return SUCCESS;
4286 }
4287
4288
4289 /* Compare an array reference with an array specification.  */
4290
4291 static gfc_try
4292 compare_spec_to_ref (gfc_array_ref *ar)
4293 {
4294   gfc_array_spec *as;
4295   int i;
4296
4297   as = ar->as;
4298   i = as->rank - 1;
4299   /* TODO: Full array sections are only allowed as actual parameters.  */
4300   if (as->type == AS_ASSUMED_SIZE
4301       && (/*ar->type == AR_FULL
4302           ||*/ (ar->type == AR_SECTION
4303               && ar->dimen_type[i] == DIMEN_RANGE && ar->end[i] == NULL)))
4304     {
4305       gfc_error ("Rightmost upper bound of assumed size array section "
4306                  "not specified at %L", &ar->where);
4307       return FAILURE;
4308     }
4309
4310   if (ar->type == AR_FULL)
4311     return SUCCESS;
4312
4313   if (as->rank != ar->dimen)
4314     {
4315       gfc_error ("Rank mismatch in array reference at %L (%d/%d)",
4316                  &ar->where, ar->dimen, as->rank);
4317       return FAILURE;
4318     }
4319
4320   /* ar->codimen == 0 is a local array.  */
4321   if (as->corank != ar->codimen && ar->codimen != 0)
4322     {
4323       gfc_error ("Coindex rank mismatch in array reference at %L (%d/%d)",
4324                  &ar->where, ar->codimen, as->corank);
4325       return FAILURE;
4326     }
4327
4328   for (i = 0; i < as->rank; i++)
4329     if (check_dimension (i, ar, as) == FAILURE)
4330       return FAILURE;
4331
4332   /* Local access has no coarray spec.  */
4333   if (ar->codimen != 0)
4334     for (i = as->rank; i < as->rank + as->corank; i++)
4335       {
4336         if (ar->dimen_type[i] != DIMEN_ELEMENT && !ar->in_allocate
4337             && ar->dimen_type[i] != DIMEN_THIS_IMAGE)
4338           {
4339             gfc_error ("Coindex of codimension %d must be a scalar at %L",
4340                        i + 1 - as->rank, &ar->where);
4341             return FAILURE;
4342           }
4343         if (check_dimension (i, ar, as) == FAILURE)
4344           return FAILURE;
4345       }
4346
4347   if (as->corank && ar->codimen == 0)
4348     {
4349       int n;
4350       ar->codimen = as->corank;
4351       for (n = ar->dimen; n < ar->dimen + ar->codimen; n++)
4352         ar->dimen_type[n] = DIMEN_THIS_IMAGE;
4353     }
4354
4355   return SUCCESS;
4356 }
4357
4358
4359 /* Resolve one part of an array index.  */
4360
4361 static gfc_try
4362 gfc_resolve_index_1 (gfc_expr *index, int check_scalar,
4363                      int force_index_integer_kind)
4364 {
4365   gfc_typespec ts;
4366
4367   if (index == NULL)
4368     return SUCCESS;
4369
4370   if (gfc_resolve_expr (index) == FAILURE)
4371     return FAILURE;
4372
4373   if (check_scalar && index->rank != 0)
4374     {
4375       gfc_error ("Array index at %L must be scalar", &index->where);
4376       return FAILURE;
4377     }
4378
4379   if (index->ts.type != BT_INTEGER && index->ts.type != BT_REAL)
4380     {
4381       gfc_error ("Array index at %L must be of INTEGER type, found %s",
4382                  &index->where, gfc_basic_typename (index->ts.type));
4383       return FAILURE;
4384     }
4385
4386   if (index->ts.type == BT_REAL)
4387     if (gfc_notify_std (GFC_STD_LEGACY, "Extension: REAL array index at %L",
4388                         &index->where) == FAILURE)
4389       return FAILURE;
4390
4391   if ((index->ts.kind != gfc_index_integer_kind
4392        && force_index_integer_kind)
4393       || index->ts.type != BT_INTEGER)
4394     {
4395       gfc_clear_ts (&ts);
4396       ts.type = BT_INTEGER;
4397       ts.kind = gfc_index_integer_kind;
4398
4399       gfc_convert_type_warn (index, &ts, 2, 0);
4400     }
4401
4402   return SUCCESS;
4403 }
4404
4405 /* Resolve one part of an array index.  */
4406
4407 gfc_try
4408 gfc_resolve_index (gfc_expr *index, int check_scalar)
4409 {
4410   return gfc_resolve_index_1 (index, check_scalar, 1);
4411 }
4412
4413 /* Resolve a dim argument to an intrinsic function.  */
4414
4415 gfc_try
4416 gfc_resolve_dim_arg (gfc_expr *dim)
4417 {
4418   if (dim == NULL)
4419     return SUCCESS;
4420
4421   if (gfc_resolve_expr (dim) == FAILURE)
4422     return FAILURE;
4423
4424   if (dim->rank != 0)
4425     {
4426       gfc_error ("Argument dim at %L must be scalar", &dim->where);
4427       return FAILURE;
4428
4429     }
4430
4431   if (dim->ts.type != BT_INTEGER)
4432     {
4433       gfc_error ("Argument dim at %L must be of INTEGER type", &dim->where);
4434       return FAILURE;
4435     }
4436
4437   if (dim->ts.kind != gfc_index_integer_kind)
4438     {
4439       gfc_typespec ts;
4440
4441       gfc_clear_ts (&ts);
4442       ts.type = BT_INTEGER;
4443       ts.kind = gfc_index_integer_kind;
4444
4445       gfc_convert_type_warn (dim, &ts, 2, 0);
4446     }
4447
4448   return SUCCESS;
4449 }
4450
4451 /* Given an expression that contains array references, update those array
4452    references to point to the right array specifications.  While this is
4453    filled in during matching, this information is difficult to save and load
4454    in a module, so we take care of it here.
4455
4456    The idea here is that the original array reference comes from the
4457    base symbol.  We traverse the list of reference structures, setting
4458    the stored reference to references.  Component references can
4459    provide an additional array specification.  */
4460
4461 static void
4462 find_array_spec (gfc_expr *e)
4463 {
4464   gfc_array_spec *as;
4465   gfc_component *c;
4466   gfc_symbol *derived;
4467   gfc_ref *ref;
4468
4469   if (e->symtree->n.sym->ts.type == BT_CLASS)
4470     as = CLASS_DATA (e->symtree->n.sym)->as;
4471   else
4472     as = e->symtree->n.sym->as;
4473   derived = NULL;
4474
4475   for (ref = e->ref; ref; ref = ref->next)
4476     switch (ref->type)
4477       {
4478       case REF_ARRAY:
4479         if (as == NULL)
4480           gfc_internal_error ("find_array_spec(): Missing spec");
4481
4482         ref->u.ar.as = as;
4483         as = NULL;
4484         break;
4485
4486       case REF_COMPONENT:
4487         if (derived == NULL)
4488           derived = e->symtree->n.sym->ts.u.derived;
4489
4490         if (derived->attr.is_class)
4491           derived = derived->components->ts.u.derived;
4492
4493         c = derived->components;
4494
4495         for (; c; c = c->next)
4496           if (c == ref->u.c.component)
4497             {
4498               /* Track the sequence of component references.  */
4499               if (c->ts.type == BT_DERIVED)
4500                 derived = c->ts.u.derived;
4501               break;
4502             }
4503
4504         if (c == NULL)
4505           gfc_internal_error ("find_array_spec(): Component not found");
4506
4507         if (c->attr.dimension)
4508           {
4509             if (as != NULL)
4510               gfc_internal_error ("find_array_spec(): unused as(1)");
4511             as = c->as;
4512           }
4513
4514         break;
4515
4516       case REF_SUBSTRING:
4517         break;
4518       }
4519
4520   if (as != NULL)
4521     gfc_internal_error ("find_array_spec(): unused as(2)");
4522 }
4523
4524
4525 /* Resolve an array reference.  */
4526
4527 static gfc_try
4528 resolve_array_ref (gfc_array_ref *ar)
4529 {
4530   int i, check_scalar;
4531   gfc_expr *e;
4532
4533   for (i = 0; i < ar->dimen + ar->codimen; i++)
4534     {
4535       check_scalar = ar->dimen_type[i] == DIMEN_RANGE;
4536
4537       /* Do not force gfc_index_integer_kind for the start.  We can
4538          do fine with any integer kind.  This avoids temporary arrays
4539          created for indexing with a vector.  */
4540       if (gfc_resolve_index_1 (ar->start[i], check_scalar, 0) == FAILURE)
4541         return FAILURE;
4542       if (gfc_resolve_index (ar->end[i], check_scalar) == FAILURE)
4543         return FAILURE;
4544       if (gfc_resolve_index (ar->stride[i], check_scalar) == FAILURE)
4545         return FAILURE;
4546
4547       e = ar->start[i];
4548
4549       if (ar->dimen_type[i] == DIMEN_UNKNOWN)
4550         switch (e->rank)
4551           {
4552           case 0:
4553             ar->dimen_type[i] = DIMEN_ELEMENT;
4554             break;
4555
4556           case 1:
4557             ar->dimen_type[i] = DIMEN_VECTOR;
4558             if (e->expr_type == EXPR_VARIABLE
4559                 && e->symtree->n.sym->ts.type == BT_DERIVED)
4560               ar->start[i] = gfc_get_parentheses (e);
4561             break;
4562
4563           default:
4564             gfc_error ("Array index at %L is an array of rank %d",
4565                        &ar->c_where[i], e->rank);
4566             return FAILURE;
4567           }
4568
4569       /* Fill in the upper bound, which may be lower than the
4570          specified one for something like a(2:10:5), which is
4571          identical to a(2:7:5).  Only relevant for strides not equal
4572          to one.  */
4573       if (ar->dimen_type[i] == DIMEN_RANGE
4574           && ar->stride[i] != NULL && ar->stride[i]->expr_type == EXPR_CONSTANT
4575           && mpz_cmp_si (ar->stride[i]->value.integer, 1L) != 0)
4576         {
4577           mpz_t size, end;
4578
4579           if (gfc_ref_dimen_size (ar, i, &size, &end) == SUCCESS)
4580             {
4581               if (ar->end[i] == NULL)
4582                 {
4583                   ar->end[i] =
4584                     gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
4585                                            &ar->where);
4586                   mpz_set (ar->end[i]->value.integer, end);
4587                 }
4588               else if (ar->end[i]->ts.type == BT_INTEGER
4589                        && ar->end[i]->expr_type == EXPR_CONSTANT)
4590                 {
4591                   mpz_set (ar->end[i]->value.integer, end);
4592                 }
4593               else
4594                 gcc_unreachable ();
4595
4596               mpz_clear (size);
4597               mpz_clear (end);
4598             }
4599         }
4600     }
4601
4602   if (ar->type == AR_FULL && ar->as->rank == 0)
4603     ar->type = AR_ELEMENT;
4604
4605   /* If the reference type is unknown, figure out what kind it is.  */
4606
4607   if (ar->type == AR_UNKNOWN)
4608     {
4609       ar->type = AR_ELEMENT;
4610       for (i = 0; i < ar->dimen; i++)
4611         if (ar->dimen_type[i] == DIMEN_RANGE
4612             || ar->dimen_type[i] == DIMEN_VECTOR)
4613           {
4614             ar->type = AR_SECTION;
4615             break;
4616           }
4617     }
4618
4619   if (!ar->as->cray_pointee && compare_spec_to_ref (ar) == FAILURE)
4620     return FAILURE;
4621
4622   return SUCCESS;
4623 }
4624
4625
4626 static gfc_try
4627 resolve_substring (gfc_ref *ref)
4628 {
4629   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
4630
4631   if (ref->u.ss.start != NULL)
4632     {
4633       if (gfc_resolve_expr (ref->u.ss.start) == FAILURE)
4634         return FAILURE;
4635
4636       if (ref->u.ss.start->ts.type != BT_INTEGER)
4637         {
4638           gfc_error ("Substring start index at %L must be of type INTEGER",
4639                      &ref->u.ss.start->where);
4640           return FAILURE;
4641         }
4642
4643       if (ref->u.ss.start->rank != 0)
4644         {
4645           gfc_error ("Substring start index at %L must be scalar",
4646                      &ref->u.ss.start->where);
4647           return FAILURE;
4648         }
4649
4650       if (compare_bound_int (ref->u.ss.start, 1) == CMP_LT
4651           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4652               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4653         {
4654           gfc_error ("Substring start index at %L is less than one",
4655                      &ref->u.ss.start->where);
4656           return FAILURE;
4657         }
4658     }
4659
4660   if (ref->u.ss.end != NULL)
4661     {
4662       if (gfc_resolve_expr (ref->u.ss.end) == FAILURE)
4663         return FAILURE;
4664
4665       if (ref->u.ss.end->ts.type != BT_INTEGER)
4666         {
4667           gfc_error ("Substring end index at %L must be of type INTEGER",
4668                      &ref->u.ss.end->where);
4669           return FAILURE;
4670         }
4671
4672       if (ref->u.ss.end->rank != 0)
4673         {
4674           gfc_error ("Substring end index at %L must be scalar",
4675                      &ref->u.ss.end->where);
4676           return FAILURE;
4677         }
4678
4679       if (ref->u.ss.length != NULL
4680           && compare_bound (ref->u.ss.end, ref->u.ss.length->length) == CMP_GT
4681           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4682               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4683         {
4684           gfc_error ("Substring end index at %L exceeds the string length",
4685                      &ref->u.ss.start->where);
4686           return FAILURE;
4687         }
4688
4689       if (compare_bound_mpz_t (ref->u.ss.end,
4690                                gfc_integer_kinds[k].huge) == CMP_GT
4691           && (compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_EQ
4692               || compare_bound (ref->u.ss.end, ref->u.ss.start) == CMP_GT))
4693         {
4694           gfc_error ("Substring end index at %L is too large",
4695                      &ref->u.ss.end->where);
4696           return FAILURE;
4697         }
4698     }
4699
4700   return SUCCESS;
4701 }
4702
4703
4704 /* This function supplies missing substring charlens.  */
4705
4706 void
4707 gfc_resolve_substring_charlen (gfc_expr *e)
4708 {
4709   gfc_ref *char_ref;
4710   gfc_expr *start, *end;
4711
4712   for (char_ref = e->ref; char_ref; char_ref = char_ref->next)
4713     if (char_ref->type == REF_SUBSTRING)
4714       break;
4715
4716   if (!char_ref)
4717     return;
4718
4719   gcc_assert (char_ref->next == NULL);
4720
4721   if (e->ts.u.cl)
4722     {
4723       if (e->ts.u.cl->length)
4724         gfc_free_expr (e->ts.u.cl->length);
4725       else if (e->expr_type == EXPR_VARIABLE
4726                  && e->symtree->n.sym->attr.dummy)
4727         return;
4728     }
4729
4730   e->ts.type = BT_CHARACTER;
4731   e->ts.kind = gfc_default_character_kind;
4732
4733   if (!e->ts.u.cl)
4734     e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
4735
4736   if (char_ref->u.ss.start)
4737     start = gfc_copy_expr (char_ref->u.ss.start);
4738   else
4739     start = gfc_get_int_expr (gfc_default_integer_kind, NULL, 1);
4740
4741   if (char_ref->u.ss.end)
4742     end = gfc_copy_expr (char_ref->u.ss.end);
4743   else if (e->expr_type == EXPR_VARIABLE)
4744     end = gfc_copy_expr (e->symtree->n.sym->ts.u.cl->length);
4745   else
4746     end = NULL;
4747
4748   if (!start || !end)
4749     return;
4750
4751   /* Length = (end - start +1).  */
4752   e->ts.u.cl->length = gfc_subtract (end, start);
4753   e->ts.u.cl->length = gfc_add (e->ts.u.cl->length,
4754                                 gfc_get_int_expr (gfc_default_integer_kind,
4755                                                   NULL, 1));
4756
4757   e->ts.u.cl->length->ts.type = BT_INTEGER;
4758   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
4759
4760   /* Make sure that the length is simplified.  */
4761   gfc_simplify_expr (e->ts.u.cl->length, 1);
4762   gfc_resolve_expr (e->ts.u.cl->length);
4763 }
4764
4765
4766 /* Resolve subtype references.  */
4767
4768 static gfc_try
4769 resolve_ref (gfc_expr *expr)
4770 {
4771   int current_part_dimension, n_components, seen_part_dimension;
4772   gfc_ref *ref;
4773
4774   for (ref = expr->ref; ref; ref = ref->next)
4775     if (ref->type == REF_ARRAY && ref->u.ar.as == NULL)
4776       {
4777         find_array_spec (expr);
4778         break;
4779       }
4780
4781   for (ref = expr->ref; ref; ref = ref->next)
4782     switch (ref->type)
4783       {
4784       case REF_ARRAY:
4785         if (resolve_array_ref (&ref->u.ar) == FAILURE)
4786           return FAILURE;
4787         break;
4788
4789       case REF_COMPONENT:
4790         break;
4791
4792       case REF_SUBSTRING:
4793         resolve_substring (ref);
4794         break;
4795       }
4796
4797   /* Check constraints on part references.  */
4798
4799   current_part_dimension = 0;
4800   seen_part_dimension = 0;
4801   n_components = 0;
4802
4803   for (ref = expr->ref; ref; ref = ref->next)
4804     {
4805       switch (ref->type)
4806         {
4807         case REF_ARRAY:
4808           switch (ref->u.ar.type)
4809             {
4810             case AR_FULL:
4811               /* Coarray scalar.  */
4812               if (ref->u.ar.as->rank == 0)
4813                 {
4814                   current_part_dimension = 0;
4815                   break;
4816                 }
4817               /* Fall through.  */
4818             case AR_SECTION:
4819               current_part_dimension = 1;
4820               break;
4821
4822             case AR_ELEMENT:
4823               current_part_dimension = 0;
4824               break;
4825
4826             case AR_UNKNOWN:
4827               gfc_internal_error ("resolve_ref(): Bad array reference");
4828             }
4829
4830           break;
4831
4832         case REF_COMPONENT:
4833           if (current_part_dimension || seen_part_dimension)
4834             {
4835               /* F03:C614.  */
4836               if (ref->u.c.component->attr.pointer
4837                   || ref->u.c.component->attr.proc_pointer)
4838                 {
4839                   gfc_error ("Component to the right of a part reference "
4840                              "with nonzero rank must not have the POINTER "
4841                              "attribute at %L", &expr->where);
4842                   return FAILURE;
4843                 }
4844               else if (ref->u.c.component->attr.allocatable)
4845                 {
4846                   gfc_error ("Component to the right of a part reference "
4847                              "with nonzero rank must not have the ALLOCATABLE "
4848                              "attribute at %L", &expr->where);
4849                   return FAILURE;
4850                 }
4851             }
4852
4853           n_components++;
4854           break;
4855
4856         case REF_SUBSTRING:
4857           break;
4858         }
4859
4860       if (((ref->type == REF_COMPONENT && n_components > 1)
4861            || ref->next == NULL)
4862           && current_part_dimension
4863           && seen_part_dimension)
4864         {
4865           gfc_error ("Two or more part references with nonzero rank must "
4866                      "not be specified at %L", &expr->where);
4867           return FAILURE;
4868         }
4869
4870       if (ref->type == REF_COMPONENT)
4871         {
4872           if (current_part_dimension)
4873             seen_part_dimension = 1;
4874
4875           /* reset to make sure */
4876           current_part_dimension = 0;
4877         }
4878     }
4879
4880   return SUCCESS;
4881 }
4882
4883
4884 /* Given an expression, determine its shape.  This is easier than it sounds.
4885    Leaves the shape array NULL if it is not possible to determine the shape.  */
4886
4887 static void
4888 expression_shape (gfc_expr *e)
4889 {
4890   mpz_t array[GFC_MAX_DIMENSIONS];
4891   int i;
4892
4893   if (e->rank == 0 || e->shape != NULL)
4894     return;
4895
4896   for (i = 0; i < e->rank; i++)
4897     if (gfc_array_dimen_size (e, i, &array[i]) == FAILURE)
4898       goto fail;
4899
4900   e->shape = gfc_get_shape (e->rank);
4901
4902   memcpy (e->shape, array, e->rank * sizeof (mpz_t));
4903
4904   return;
4905
4906 fail:
4907   for (i--; i >= 0; i--)
4908     mpz_clear (array[i]);
4909 }
4910
4911
4912 /* Given a variable expression node, compute the rank of the expression by
4913    examining the base symbol and any reference structures it may have.  */
4914
4915 static void
4916 expression_rank (gfc_expr *e)
4917 {
4918   gfc_ref *ref;
4919   int i, rank;
4920
4921   /* Just to make sure, because EXPR_COMPCALL's also have an e->ref and that
4922      could lead to serious confusion...  */
4923   gcc_assert (e->expr_type != EXPR_COMPCALL);
4924
4925   if (e->ref == NULL)
4926     {
4927       if (e->expr_type == EXPR_ARRAY)
4928         goto done;
4929       /* Constructors can have a rank different from one via RESHAPE().  */
4930
4931       if (e->symtree == NULL)
4932         {
4933           e->rank = 0;
4934           goto done;
4935         }
4936
4937       e->rank = (e->symtree->n.sym->as == NULL)
4938                 ? 0 : e->symtree->n.sym->as->rank;
4939       goto done;
4940     }
4941
4942   rank = 0;
4943
4944   for (ref = e->ref; ref; ref = ref->next)
4945     {
4946       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.proc_pointer
4947           && ref->u.c.component->attr.function && !ref->next)
4948         rank = ref->u.c.component->as ? ref->u.c.component->as->rank : 0;
4949
4950       if (ref->type != REF_ARRAY)
4951         continue;
4952
4953       if (ref->u.ar.type == AR_FULL)
4954         {
4955           rank = ref->u.ar.as->rank;
4956           break;
4957         }
4958
4959       if (ref->u.ar.type == AR_SECTION)
4960         {
4961           /* Figure out the rank of the section.  */
4962           if (rank != 0)
4963             gfc_internal_error ("expression_rank(): Two array specs");
4964
4965           for (i = 0; i < ref->u.ar.dimen; i++)
4966             if (ref->u.ar.dimen_type[i] == DIMEN_RANGE
4967                 || ref->u.ar.dimen_type[i] == DIMEN_VECTOR)
4968               rank++;
4969
4970           break;
4971         }
4972     }
4973
4974   e->rank = rank;
4975
4976 done:
4977   expression_shape (e);
4978 }
4979
4980
4981 /* Resolve a variable expression.  */
4982
4983 static gfc_try
4984 resolve_variable (gfc_expr *e)
4985 {
4986   gfc_symbol *sym;
4987   gfc_try t;
4988
4989   t = SUCCESS;
4990
4991   if (e->symtree == NULL)
4992     return FAILURE;
4993   sym = e->symtree->n.sym;
4994
4995   /* If this is an associate-name, it may be parsed with an array reference
4996      in error even though the target is scalar.  Fail directly in this case.  */
4997   if (sym->assoc && !sym->attr.dimension && e->ref && e->ref->type == REF_ARRAY)
4998     return FAILURE;
4999
5000   /* On the other hand, the parser may not have known this is an array;
5001      in this case, we have to add a FULL reference.  */
5002   if (sym->assoc && sym->attr.dimension && !e->ref)
5003     {
5004       e->ref = gfc_get_ref ();
5005       e->ref->type = REF_ARRAY;
5006       e->ref->u.ar.type = AR_FULL;
5007       e->ref->u.ar.dimen = 0;
5008     }
5009
5010   if (e->ref && resolve_ref (e) == FAILURE)
5011     return FAILURE;
5012
5013   if (sym->attr.flavor == FL_PROCEDURE
5014       && (!sym->attr.function
5015           || (sym->attr.function && sym->result
5016               && sym->result->attr.proc_pointer
5017               && !sym->result->attr.function)))
5018     {
5019       e->ts.type = BT_PROCEDURE;
5020       goto resolve_procedure;
5021     }
5022
5023   if (sym->ts.type != BT_UNKNOWN)
5024     gfc_variable_attr (e, &e->ts);
5025   else
5026     {
5027       /* Must be a simple variable reference.  */
5028       if (gfc_set_default_type (sym, 1, sym->ns) == FAILURE)
5029         return FAILURE;
5030       e->ts = sym->ts;
5031     }
5032
5033   if (check_assumed_size_reference (sym, e))
5034     return FAILURE;
5035
5036   /* Deal with forward references to entries during resolve_code, to
5037      satisfy, at least partially, 12.5.2.5.  */
5038   if (gfc_current_ns->entries
5039       && current_entry_id == sym->entry_id
5040       && cs_base
5041       && cs_base->current
5042       && cs_base->current->op != EXEC_ENTRY)
5043     {
5044       gfc_entry_list *entry;
5045       gfc_formal_arglist *formal;
5046       int n;
5047       bool seen;
5048
5049       /* If the symbol is a dummy...  */
5050       if (sym->attr.dummy && sym->ns == gfc_current_ns)
5051         {
5052           entry = gfc_current_ns->entries;
5053           seen = false;
5054
5055           /* ...test if the symbol is a parameter of previous entries.  */
5056           for (; entry && entry->id <= current_entry_id; entry = entry->next)
5057             for (formal = entry->sym->formal; formal; formal = formal->next)
5058               {
5059                 if (formal->sym && sym->name == formal->sym->name)
5060                   seen = true;
5061               }
5062
5063           /*  If it has not been seen as a dummy, this is an error.  */
5064           if (!seen)
5065             {
5066               if (specification_expr)
5067                 gfc_error ("Variable '%s', used in a specification expression"
5068                            ", is referenced at %L before the ENTRY statement "
5069                            "in which it is a parameter",
5070                            sym->name, &cs_base->current->loc);
5071               else
5072                 gfc_error ("Variable '%s' is used at %L before the ENTRY "
5073                            "statement in which it is a parameter",
5074                            sym->name, &cs_base->current->loc);
5075               t = FAILURE;
5076             }
5077         }
5078
5079       /* Now do the same check on the specification expressions.  */
5080       specification_expr = 1;
5081       if (sym->ts.type == BT_CHARACTER
5082           && gfc_resolve_expr (sym->ts.u.cl->length) == FAILURE)
5083         t = FAILURE;
5084
5085       if (sym->as)
5086         for (n = 0; n < sym->as->rank; n++)
5087           {
5088              specification_expr = 1;
5089              if (gfc_resolve_expr (sym->as->lower[n]) == FAILURE)
5090                t = FAILURE;
5091              specification_expr = 1;
5092              if (gfc_resolve_expr (sym->as->upper[n]) == FAILURE)
5093                t = FAILURE;
5094           }
5095       specification_expr = 0;
5096
5097       if (t == SUCCESS)
5098         /* Update the symbol's entry level.  */
5099         sym->entry_id = current_entry_id + 1;
5100     }
5101
5102   /* If a symbol has been host_associated mark it.  This is used latter,
5103      to identify if aliasing is possible via host association.  */
5104   if (sym->attr.flavor == FL_VARIABLE
5105         && gfc_current_ns->parent
5106         && (gfc_current_ns->parent == sym->ns
5107               || (gfc_current_ns->parent->parent
5108                     && gfc_current_ns->parent->parent == sym->ns)))
5109     sym->attr.host_assoc = 1;
5110
5111 resolve_procedure:
5112   if (t == SUCCESS && resolve_procedure_expression (e) == FAILURE)
5113     t = FAILURE;
5114
5115   /* F2008, C617 and C1229.  */
5116   if (!inquiry_argument && (e->ts.type == BT_CLASS || e->ts.type == BT_DERIVED)
5117       && gfc_is_coindexed (e))
5118     {
5119       gfc_ref *ref, *ref2 = NULL;
5120
5121       for (ref = e->ref; ref; ref = ref->next)
5122         {
5123           if (ref->type == REF_COMPONENT)
5124             ref2 = ref;
5125           if (ref->type == REF_ARRAY && ref->u.ar.codimen > 0)
5126             break;
5127         }
5128
5129       for ( ; ref; ref = ref->next)
5130         if (ref->type == REF_COMPONENT)
5131           break;
5132
5133       /* Expression itself is not coindexed object.  */
5134       if (ref && e->ts.type == BT_CLASS)
5135         {
5136           gfc_error ("Polymorphic subobject of coindexed object at %L",
5137                      &e->where);
5138           t = FAILURE;
5139         }
5140
5141       /* Expression itself is coindexed object.  */
5142       if (ref == NULL)
5143         {
5144           gfc_component *c;
5145           c = ref2 ? ref2->u.c.component : e->symtree->n.sym->components;
5146           for ( ; c; c = c->next)
5147             if (c->attr.allocatable && c->ts.type == BT_CLASS)
5148               {
5149                 gfc_error ("Coindexed object with polymorphic allocatable "
5150                          "subcomponent at %L", &e->where);
5151                 t = FAILURE;
5152                 break;
5153               }
5154         }
5155     }
5156
5157   return t;
5158 }
5159
5160
5161 /* Checks to see that the correct symbol has been host associated.
5162    The only situation where this arises is that in which a twice
5163    contained function is parsed after the host association is made.
5164    Therefore, on detecting this, change the symbol in the expression
5165    and convert the array reference into an actual arglist if the old
5166    symbol is a variable.  */
5167 static bool
5168 check_host_association (gfc_expr *e)
5169 {
5170   gfc_symbol *sym, *old_sym;
5171   gfc_symtree *st;
5172   int n;
5173   gfc_ref *ref;
5174   gfc_actual_arglist *arg, *tail = NULL;
5175   bool retval = e->expr_type == EXPR_FUNCTION;
5176
5177   /*  If the expression is the result of substitution in
5178       interface.c(gfc_extend_expr) because there is no way in
5179       which the host association can be wrong.  */
5180   if (e->symtree == NULL
5181         || e->symtree->n.sym == NULL
5182         || e->user_operator)
5183     return retval;
5184
5185   old_sym = e->symtree->n.sym;
5186
5187   if (gfc_current_ns->parent
5188         && old_sym->ns != gfc_current_ns)
5189     {
5190       /* Use the 'USE' name so that renamed module symbols are
5191          correctly handled.  */
5192       gfc_find_symbol (e->symtree->name, gfc_current_ns, 1, &sym);
5193
5194       if (sym && old_sym != sym
5195               && sym->ts.type == old_sym->ts.type
5196               && sym->attr.flavor == FL_PROCEDURE
5197               && sym->attr.contained)
5198         {
5199           /* Clear the shape, since it might not be valid.  */
5200           if (e->shape != NULL)
5201             {
5202               for (n = 0; n < e->rank; n++)
5203                 mpz_clear (e->shape[n]);
5204
5205               free (e->shape);
5206             }
5207
5208           /* Give the expression the right symtree!  */
5209           gfc_find_sym_tree (e->symtree->name, NULL, 1, &st);
5210           gcc_assert (st != NULL);
5211
5212           if (old_sym->attr.flavor == FL_PROCEDURE
5213                 || e->expr_type == EXPR_FUNCTION)
5214             {
5215               /* Original was function so point to the new symbol, since
5216                  the actual argument list is already attached to the
5217                  expression. */
5218               e->value.function.esym = NULL;
5219               e->symtree = st;
5220             }
5221           else
5222             {
5223               /* Original was variable so convert array references into
5224                  an actual arglist. This does not need any checking now
5225                  since resolve_function will take care of it.  */
5226               e->value.function.actual = NULL;
5227               e->expr_type = EXPR_FUNCTION;
5228               e->symtree = st;
5229
5230               /* Ambiguity will not arise if the array reference is not
5231                  the last reference.  */
5232               for (ref = e->ref; ref; ref = ref->next)
5233                 if (ref->type == REF_ARRAY && ref->next == NULL)
5234                   break;
5235
5236               gcc_assert (ref->type == REF_ARRAY);
5237
5238               /* Grab the start expressions from the array ref and
5239                  copy them into actual arguments.  */
5240               for (n = 0; n < ref->u.ar.dimen; n++)
5241                 {
5242                   arg = gfc_get_actual_arglist ();
5243                   arg->expr = gfc_copy_expr (ref->u.ar.start[n]);
5244                   if (e->value.function.actual == NULL)
5245                     tail = e->value.function.actual = arg;
5246                   else
5247                     {
5248                       tail->next = arg;
5249                       tail = arg;
5250                     }
5251                 }
5252
5253               /* Dump the reference list and set the rank.  */
5254               gfc_free_ref_list (e->ref);
5255               e->ref = NULL;
5256               e->rank = sym->as ? sym->as->rank : 0;
5257             }
5258
5259           gfc_resolve_expr (e);
5260           sym->refs++;
5261         }
5262     }
5263   /* This might have changed!  */
5264   return e->expr_type == EXPR_FUNCTION;
5265 }
5266
5267
5268 static void
5269 gfc_resolve_character_operator (gfc_expr *e)
5270 {
5271   gfc_expr *op1 = e->value.op.op1;
5272   gfc_expr *op2 = e->value.op.op2;
5273   gfc_expr *e1 = NULL;
5274   gfc_expr *e2 = NULL;
5275
5276   gcc_assert (e->value.op.op == INTRINSIC_CONCAT);
5277
5278   if (op1->ts.u.cl && op1->ts.u.cl->length)
5279     e1 = gfc_copy_expr (op1->ts.u.cl->length);
5280   else if (op1->expr_type == EXPR_CONSTANT)
5281     e1 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5282                            op1->value.character.length);
5283
5284   if (op2->ts.u.cl && op2->ts.u.cl->length)
5285     e2 = gfc_copy_expr (op2->ts.u.cl->length);
5286   else if (op2->expr_type == EXPR_CONSTANT)
5287     e2 = gfc_get_int_expr (gfc_default_integer_kind, NULL,
5288                            op2->value.character.length);
5289
5290   e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5291
5292   if (!e1 || !e2)
5293     return;
5294
5295   e->ts.u.cl->length = gfc_add (e1, e2);
5296   e->ts.u.cl->length->ts.type = BT_INTEGER;
5297   e->ts.u.cl->length->ts.kind = gfc_charlen_int_kind;
5298   gfc_simplify_expr (e->ts.u.cl->length, 0);
5299   gfc_resolve_expr (e->ts.u.cl->length);
5300
5301   return;
5302 }
5303
5304
5305 /*  Ensure that an character expression has a charlen and, if possible, a
5306     length expression.  */
5307
5308 static void
5309 fixup_charlen (gfc_expr *e)
5310 {
5311   /* The cases fall through so that changes in expression type and the need
5312      for multiple fixes are picked up.  In all circumstances, a charlen should
5313      be available for the middle end to hang a backend_decl on.  */
5314   switch (e->expr_type)
5315     {
5316     case EXPR_OP:
5317       gfc_resolve_character_operator (e);
5318
5319     case EXPR_ARRAY:
5320       if (e->expr_type == EXPR_ARRAY)
5321         gfc_resolve_character_array_constructor (e);
5322
5323     case EXPR_SUBSTRING:
5324       if (!e->ts.u.cl && e->ref)
5325         gfc_resolve_substring_charlen (e);
5326
5327     default:
5328       if (!e->ts.u.cl)
5329         e->ts.u.cl = gfc_new_charlen (gfc_current_ns, NULL);
5330
5331       break;
5332     }
5333 }
5334
5335
5336 /* Update an actual argument to include the passed-object for type-bound
5337    procedures at the right position.  */
5338
5339 static gfc_actual_arglist*
5340 update_arglist_pass (gfc_actual_arglist* lst, gfc_expr* po, unsigned argpos,
5341                      const char *name)
5342 {
5343   gcc_assert (argpos > 0);
5344
5345   if (argpos == 1)
5346     {
5347       gfc_actual_arglist* result;
5348
5349       result = gfc_get_actual_arglist ();
5350       result->expr = po;
5351       result->next = lst;
5352       if (name)
5353         result->name = name;
5354
5355       return result;
5356     }
5357
5358   if (lst)
5359     lst->next = update_arglist_pass (lst->next, po, argpos - 1, name);
5360   else
5361     lst = update_arglist_pass (NULL, po, argpos - 1, name);
5362   return lst;
5363 }
5364
5365
5366 /* Extract the passed-object from an EXPR_COMPCALL (a copy of it).  */
5367
5368 static gfc_expr*
5369 extract_compcall_passed_object (gfc_expr* e)
5370 {
5371   gfc_expr* po;
5372
5373   gcc_assert (e->expr_type == EXPR_COMPCALL);
5374
5375   if (e->value.compcall.base_object)
5376     po = gfc_copy_expr (e->value.compcall.base_object);
5377   else
5378     {
5379       po = gfc_get_expr ();
5380       po->expr_type = EXPR_VARIABLE;
5381       po->symtree = e->symtree;
5382       po->ref = gfc_copy_ref (e->ref);
5383       po->where = e->where;
5384     }
5385
5386   if (gfc_resolve_expr (po) == FAILURE)
5387     return NULL;
5388
5389   return po;
5390 }
5391
5392
5393 /* Update the arglist of an EXPR_COMPCALL expression to include the
5394    passed-object.  */
5395
5396 static gfc_try
5397 update_compcall_arglist (gfc_expr* e)
5398 {
5399   gfc_expr* po;
5400   gfc_typebound_proc* tbp;
5401
5402   tbp = e->value.compcall.tbp;
5403
5404   if (tbp->error)
5405     return FAILURE;
5406
5407   po = extract_compcall_passed_object (e);
5408   if (!po)
5409     return FAILURE;
5410
5411   if (tbp->nopass || e->value.compcall.ignore_pass)
5412     {
5413       gfc_free_expr (po);
5414       return SUCCESS;
5415     }
5416
5417   gcc_assert (tbp->pass_arg_num > 0);
5418   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5419                                                   tbp->pass_arg_num,
5420                                                   tbp->pass_arg);
5421
5422   return SUCCESS;
5423 }
5424
5425
5426 /* Extract the passed object from a PPC call (a copy of it).  */
5427
5428 static gfc_expr*
5429 extract_ppc_passed_object (gfc_expr *e)
5430 {
5431   gfc_expr *po;
5432   gfc_ref **ref;
5433
5434   po = gfc_get_expr ();
5435   po->expr_type = EXPR_VARIABLE;
5436   po->symtree = e->symtree;
5437   po->ref = gfc_copy_ref (e->ref);
5438   po->where = e->where;
5439
5440   /* Remove PPC reference.  */
5441   ref = &po->ref;
5442   while ((*ref)->next)
5443     ref = &(*ref)->next;
5444   gfc_free_ref_list (*ref);
5445   *ref = NULL;
5446
5447   if (gfc_resolve_expr (po) == FAILURE)
5448     return NULL;
5449
5450   return po;
5451 }
5452
5453
5454 /* Update the actual arglist of a procedure pointer component to include the
5455    passed-object.  */
5456
5457 static gfc_try
5458 update_ppc_arglist (gfc_expr* e)
5459 {
5460   gfc_expr* po;
5461   gfc_component *ppc;
5462   gfc_typebound_proc* tb;
5463
5464   if (!gfc_is_proc_ptr_comp (e, &ppc))
5465     return FAILURE;
5466
5467   tb = ppc->tb;
5468
5469   if (tb->error)
5470     return FAILURE;
5471   else if (tb->nopass)
5472     return SUCCESS;
5473
5474   po = extract_ppc_passed_object (e);
5475   if (!po)
5476     return FAILURE;
5477
5478   /* F08:R739.  */
5479   if (po->rank > 0)
5480     {
5481       gfc_error ("Passed-object at %L must be scalar", &e->where);
5482       return FAILURE;
5483     }
5484
5485   /* F08:C611.  */
5486   if (po->ts.type == BT_DERIVED && po->ts.u.derived->attr.abstract)
5487     {
5488       gfc_error ("Base object for procedure-pointer component call at %L is of"
5489                  " ABSTRACT type '%s'", &e->where, po->ts.u.derived->name);
5490       return FAILURE;
5491     }
5492
5493   gcc_assert (tb->pass_arg_num > 0);
5494   e->value.compcall.actual = update_arglist_pass (e->value.compcall.actual, po,
5495                                                   tb->pass_arg_num,
5496                                                   tb->pass_arg);
5497
5498   return SUCCESS;
5499 }
5500
5501
5502 /* Check that the object a TBP is called on is valid, i.e. it must not be
5503    of ABSTRACT type (as in subobject%abstract_parent%tbp()).  */
5504
5505 static gfc_try
5506 check_typebound_baseobject (gfc_expr* e)
5507 {
5508   gfc_expr* base;
5509   gfc_try return_value = FAILURE;
5510
5511   base = extract_compcall_passed_object (e);
5512   if (!base)
5513     return FAILURE;
5514
5515   gcc_assert (base->ts.type == BT_DERIVED || base->ts.type == BT_CLASS);
5516
5517   /* F08:C611.  */
5518   if (base->ts.type == BT_DERIVED && base->ts.u.derived->attr.abstract)
5519     {
5520       gfc_error ("Base object for type-bound procedure call at %L is of"
5521                  " ABSTRACT type '%s'", &e->where, base->ts.u.derived->name);
5522       goto cleanup;
5523     }
5524
5525   /* F08:C1230. If the procedure called is NOPASS,
5526      the base object must be scalar.  */
5527   if (e->value.compcall.tbp->nopass && base->rank > 0)
5528     {
5529       gfc_error ("Base object for NOPASS type-bound procedure call at %L must"
5530                  " be scalar", &e->where);
5531       goto cleanup;
5532     }
5533
5534   /* FIXME: Remove once PR 43214 is fixed (TBP with non-scalar PASS).  */
5535   if (base->rank > 0)
5536     {
5537       gfc_error ("Non-scalar base object at %L currently not implemented",
5538                  &e->where);
5539       goto cleanup;
5540     }
5541
5542   return_value = SUCCESS;
5543
5544 cleanup:
5545   gfc_free_expr (base);
5546   return return_value;
5547 }
5548
5549
5550 /* Resolve a call to a type-bound procedure, either function or subroutine,
5551    statically from the data in an EXPR_COMPCALL expression.  The adapted
5552    arglist and the target-procedure symtree are returned.  */
5553
5554 static gfc_try
5555 resolve_typebound_static (gfc_expr* e, gfc_symtree** target,
5556                           gfc_actual_arglist** actual)
5557 {
5558   gcc_assert (e->expr_type == EXPR_COMPCALL);
5559   gcc_assert (!e->value.compcall.tbp->is_generic);
5560
5561   /* Update the actual arglist for PASS.  */
5562   if (update_compcall_arglist (e) == FAILURE)
5563     return FAILURE;
5564
5565   *actual = e->value.compcall.actual;
5566   *target = e->value.compcall.tbp->u.specific;
5567
5568   gfc_free_ref_list (e->ref);
5569   e->ref = NULL;
5570   e->value.compcall.actual = NULL;
5571
5572   return SUCCESS;
5573 }
5574
5575
5576 /* Get the ultimate declared type from an expression.  In addition,
5577    return the last class/derived type reference and the copy of the
5578    reference list.  */
5579 static gfc_symbol*
5580 get_declared_from_expr (gfc_ref **class_ref, gfc_ref **new_ref,
5581                         gfc_expr *e)
5582 {
5583   gfc_symbol *declared;
5584   gfc_ref *ref;
5585
5586   declared = NULL;
5587   if (class_ref)
5588     *class_ref = NULL;
5589   if (new_ref)
5590     *new_ref = gfc_copy_ref (e->ref);
5591
5592   for (ref = e->ref; ref; ref = ref->next)
5593     {
5594       if (ref->type != REF_COMPONENT)
5595         continue;
5596
5597       if (ref->u.c.component->ts.type == BT_CLASS
5598             || ref->u.c.component->ts.type == BT_DERIVED)
5599         {
5600           declared = ref->u.c.component->ts.u.derived;
5601           if (class_ref)
5602             *class_ref = ref;
5603         }
5604     }
5605
5606   if (declared == NULL)
5607     declared = e->symtree->n.sym->ts.u.derived;
5608
5609   return declared;
5610 }
5611
5612
5613 /* Given an EXPR_COMPCALL calling a GENERIC typebound procedure, figure out
5614    which of the specific bindings (if any) matches the arglist and transform
5615    the expression into a call of that binding.  */
5616
5617 static gfc_try
5618 resolve_typebound_generic_call (gfc_expr* e, const char **name)
5619 {
5620   gfc_typebound_proc* genproc;
5621   const char* genname;
5622   gfc_symtree *st;
5623   gfc_symbol *derived;
5624
5625   gcc_assert (e->expr_type == EXPR_COMPCALL);
5626   genname = e->value.compcall.name;
5627   genproc = e->value.compcall.tbp;
5628
5629   if (!genproc->is_generic)
5630     return SUCCESS;
5631
5632   /* Try the bindings on this type and in the inheritance hierarchy.  */
5633   for (; genproc; genproc = genproc->overridden)
5634     {
5635       gfc_tbp_generic* g;
5636
5637       gcc_assert (genproc->is_generic);
5638       for (g = genproc->u.generic; g; g = g->next)
5639         {
5640           gfc_symbol* target;
5641           gfc_actual_arglist* args;
5642           bool matches;
5643
5644           gcc_assert (g->specific);
5645
5646           if (g->specific->error)
5647             continue;
5648
5649           target = g->specific->u.specific->n.sym;
5650
5651           /* Get the right arglist by handling PASS/NOPASS.  */
5652           args = gfc_copy_actual_arglist (e->value.compcall.actual);
5653           if (!g->specific->nopass)
5654             {
5655               gfc_expr* po;
5656               po = extract_compcall_passed_object (e);
5657               if (!po)
5658                 return FAILURE;
5659
5660               gcc_assert (g->specific->pass_arg_num > 0);
5661               gcc_assert (!g->specific->error);
5662               args = update_arglist_pass (args, po, g->specific->pass_arg_num,
5663                                           g->specific->pass_arg);
5664             }
5665           resolve_actual_arglist (args, target->attr.proc,
5666                                   is_external_proc (target) && !target->formal);
5667
5668           /* Check if this arglist matches the formal.  */
5669           matches = gfc_arglist_matches_symbol (&args, target);
5670
5671           /* Clean up and break out of the loop if we've found it.  */
5672           gfc_free_actual_arglist (args);
5673           if (matches)
5674             {
5675               e->value.compcall.tbp = g->specific;
5676               genname = g->specific_st->name;
5677               /* Pass along the name for CLASS methods, where the vtab
5678                  procedure pointer component has to be referenced.  */
5679               if (name)
5680                 *name = genname;
5681               goto success;
5682             }
5683         }
5684     }
5685
5686   /* Nothing matching found!  */
5687   gfc_error ("Found no matching specific binding for the call to the GENERIC"
5688              " '%s' at %L", genname, &e->where);
5689   return FAILURE;
5690
5691 success:
5692   /* Make sure that we have the right specific instance for the name.  */
5693   derived = get_declared_from_expr (NULL, NULL, e);
5694
5695   st = gfc_find_typebound_proc (derived, NULL, genname, true, &e->where);
5696   if (st)
5697     e->value.compcall.tbp = st->n.tb;
5698
5699   return SUCCESS;
5700 }
5701
5702
5703 /* Resolve a call to a type-bound subroutine.  */
5704
5705 static gfc_try
5706 resolve_typebound_call (gfc_code* c, const char **name)
5707 {
5708   gfc_actual_arglist* newactual;
5709   gfc_symtree* target;
5710
5711   /* Check that's really a SUBROUTINE.  */
5712   if (!c->expr1->value.compcall.tbp->subroutine)
5713     {
5714       gfc_error ("'%s' at %L should be a SUBROUTINE",
5715                  c->expr1->value.compcall.name, &c->loc);
5716       return FAILURE;
5717     }
5718
5719   if (check_typebound_baseobject (c->expr1) == FAILURE)
5720     return FAILURE;
5721
5722   /* Pass along the name for CLASS methods, where the vtab
5723      procedure pointer component has to be referenced.  */
5724   if (name)
5725     *name = c->expr1->value.compcall.name;
5726
5727   if (resolve_typebound_generic_call (c->expr1, name) == FAILURE)
5728     return FAILURE;
5729
5730   /* Transform into an ordinary EXEC_CALL for now.  */
5731
5732   if (resolve_typebound_static (c->expr1, &target, &newactual) == FAILURE)
5733     return FAILURE;
5734
5735   c->ext.actual = newactual;
5736   c->symtree = target;
5737   c->op = (c->expr1->value.compcall.assign ? EXEC_ASSIGN_CALL : EXEC_CALL);
5738
5739   gcc_assert (!c->expr1->ref && !c->expr1->value.compcall.actual);
5740
5741   gfc_free_expr (c->expr1);
5742   c->expr1 = gfc_get_expr ();
5743   c->expr1->expr_type = EXPR_FUNCTION;
5744   c->expr1->symtree = target;
5745   c->expr1->where = c->loc;
5746
5747   return resolve_call (c);
5748 }
5749
5750
5751 /* Resolve a component-call expression.  */
5752 static gfc_try
5753 resolve_compcall (gfc_expr* e, const char **name)
5754 {
5755   gfc_actual_arglist* newactual;
5756   gfc_symtree* target;
5757
5758   /* Check that's really a FUNCTION.  */
5759   if (!e->value.compcall.tbp->function)
5760     {
5761       gfc_error ("'%s' at %L should be a FUNCTION",
5762                  e->value.compcall.name, &e->where);
5763       return FAILURE;
5764     }
5765
5766   /* These must not be assign-calls!  */
5767   gcc_assert (!e->value.compcall.assign);
5768
5769   if (check_typebound_baseobject (e) == FAILURE)
5770     return FAILURE;
5771
5772   /* Pass along the name for CLASS methods, where the vtab
5773      procedure pointer component has to be referenced.  */
5774   if (name)
5775     *name = e->value.compcall.name;
5776
5777   if (resolve_typebound_generic_call (e, name) == FAILURE)
5778     return FAILURE;
5779   gcc_assert (!e->value.compcall.tbp->is_generic);
5780
5781   /* Take the rank from the function's symbol.  */
5782   if (e->value.compcall.tbp->u.specific->n.sym->as)
5783     e->rank = e->value.compcall.tbp->u.specific->n.sym->as->rank;
5784
5785   /* For now, we simply transform it into an EXPR_FUNCTION call with the same
5786      arglist to the TBP's binding target.  */
5787
5788   if (resolve_typebound_static (e, &target, &newactual) == FAILURE)
5789     return FAILURE;
5790
5791   e->value.function.actual = newactual;
5792   e->value.function.name = NULL;
5793   e->value.function.esym = target->n.sym;
5794   e->value.function.isym = NULL;
5795   e->symtree = target;
5796   e->ts = target->n.sym->ts;
5797   e->expr_type = EXPR_FUNCTION;
5798
5799   /* Resolution is not necessary if this is a class subroutine; this
5800      function only has to identify the specific proc. Resolution of
5801      the call will be done next in resolve_typebound_call.  */
5802   return gfc_resolve_expr (e);
5803 }
5804
5805
5806
5807 /* Resolve a typebound function, or 'method'. First separate all
5808    the non-CLASS references by calling resolve_compcall directly.  */
5809
5810 static gfc_try
5811 resolve_typebound_function (gfc_expr* e)
5812 {
5813   gfc_symbol *declared;
5814   gfc_component *c;
5815   gfc_ref *new_ref;
5816   gfc_ref *class_ref;
5817   gfc_symtree *st;
5818   const char *name;
5819   gfc_typespec ts;
5820   gfc_expr *expr;
5821
5822   st = e->symtree;
5823
5824   /* Deal with typebound operators for CLASS objects.  */
5825   expr = e->value.compcall.base_object;
5826   if (expr && expr->ts.type == BT_CLASS && e->value.compcall.name)
5827     {
5828       /* Since the typebound operators are generic, we have to ensure
5829          that any delays in resolution are corrected and that the vtab
5830          is present.  */
5831       ts = expr->ts;
5832       declared = ts.u.derived;
5833       c = gfc_find_component (declared, "_vptr", true, true);
5834       if (c->ts.u.derived == NULL)
5835         c->ts.u.derived = gfc_find_derived_vtab (declared);
5836
5837       if (resolve_compcall (e, &name) == FAILURE)
5838         return FAILURE;
5839
5840       /* Use the generic name if it is there.  */
5841       name = name ? name : e->value.function.esym->name;
5842       e->symtree = expr->symtree;
5843       e->ref = gfc_copy_ref (expr->ref);
5844       gfc_add_vptr_component (e);
5845       gfc_add_component_ref (e, name);
5846       e->value.function.esym = NULL;
5847       return SUCCESS;
5848     }
5849
5850   if (st == NULL)
5851     return resolve_compcall (e, NULL);
5852
5853   if (resolve_ref (e) == FAILURE)
5854     return FAILURE;
5855
5856   /* Get the CLASS declared type.  */
5857   declared = get_declared_from_expr (&class_ref, &new_ref, e);
5858
5859   /* Weed out cases of the ultimate component being a derived type.  */
5860   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5861          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5862     {
5863       gfc_free_ref_list (new_ref);
5864       return resolve_compcall (e, NULL);
5865     }
5866
5867   c = gfc_find_component (declared, "_data", true, true);
5868   declared = c->ts.u.derived;
5869
5870   /* Treat the call as if it is a typebound procedure, in order to roll
5871      out the correct name for the specific function.  */
5872   if (resolve_compcall (e, &name) == FAILURE)
5873     return FAILURE;
5874   ts = e->ts;
5875
5876   /* Then convert the expression to a procedure pointer component call.  */
5877   e->value.function.esym = NULL;
5878   e->symtree = st;
5879
5880   if (new_ref)  
5881     e->ref = new_ref;
5882
5883   /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5884   gfc_add_vptr_component (e);
5885   gfc_add_component_ref (e, name);
5886
5887   /* Recover the typespec for the expression.  This is really only
5888      necessary for generic procedures, where the additional call
5889      to gfc_add_component_ref seems to throw the collection of the
5890      correct typespec.  */
5891   e->ts = ts;
5892   return SUCCESS;
5893 }
5894
5895 /* Resolve a typebound subroutine, or 'method'. First separate all
5896    the non-CLASS references by calling resolve_typebound_call
5897    directly.  */
5898
5899 static gfc_try
5900 resolve_typebound_subroutine (gfc_code *code)
5901 {
5902   gfc_symbol *declared;
5903   gfc_component *c;
5904   gfc_ref *new_ref;
5905   gfc_ref *class_ref;
5906   gfc_symtree *st;
5907   const char *name;
5908   gfc_typespec ts;
5909   gfc_expr *expr;
5910
5911   st = code->expr1->symtree;
5912
5913   /* Deal with typebound operators for CLASS objects.  */
5914   expr = code->expr1->value.compcall.base_object;
5915   if (expr && expr->ts.type == BT_CLASS && code->expr1->value.compcall.name)
5916     {
5917       /* Since the typebound operators are generic, we have to ensure
5918          that any delays in resolution are corrected and that the vtab
5919          is present.  */
5920       declared = expr->ts.u.derived;
5921       c = gfc_find_component (declared, "_vptr", true, true);
5922       if (c->ts.u.derived == NULL)
5923         c->ts.u.derived = gfc_find_derived_vtab (declared);
5924
5925       if (resolve_typebound_call (code, &name) == FAILURE)
5926         return FAILURE;
5927
5928       /* Use the generic name if it is there.  */
5929       name = name ? name : code->expr1->value.function.esym->name;
5930       code->expr1->symtree = expr->symtree;
5931       code->expr1->ref = gfc_copy_ref (expr->ref);
5932       gfc_add_vptr_component (code->expr1);
5933       gfc_add_component_ref (code->expr1, name);
5934       code->expr1->value.function.esym = NULL;
5935       return SUCCESS;
5936     }
5937
5938   if (st == NULL)
5939     return resolve_typebound_call (code, NULL);
5940
5941   if (resolve_ref (code->expr1) == FAILURE)
5942     return FAILURE;
5943
5944   /* Get the CLASS declared type.  */
5945   get_declared_from_expr (&class_ref, &new_ref, code->expr1);
5946
5947   /* Weed out cases of the ultimate component being a derived type.  */
5948   if ((class_ref && class_ref->u.c.component->ts.type == BT_DERIVED)
5949          || (!class_ref && st->n.sym->ts.type != BT_CLASS))
5950     {
5951       gfc_free_ref_list (new_ref);
5952       return resolve_typebound_call (code, NULL);
5953     }
5954
5955   if (resolve_typebound_call (code, &name) == FAILURE)
5956     return FAILURE;
5957   ts = code->expr1->ts;
5958
5959   /* Then convert the expression to a procedure pointer component call.  */
5960   code->expr1->value.function.esym = NULL;
5961   code->expr1->symtree = st;
5962
5963   if (new_ref)
5964     code->expr1->ref = new_ref;
5965
5966   /* '_vptr' points to the vtab, which contains the procedure pointers.  */
5967   gfc_add_vptr_component (code->expr1);
5968   gfc_add_component_ref (code->expr1, name);
5969
5970   /* Recover the typespec for the expression.  This is really only
5971      necessary for generic procedures, where the additional call
5972      to gfc_add_component_ref seems to throw the collection of the
5973      correct typespec.  */
5974   code->expr1->ts = ts;
5975   return SUCCESS;
5976 }
5977
5978
5979 /* Resolve a CALL to a Procedure Pointer Component (Subroutine).  */
5980
5981 static gfc_try
5982 resolve_ppc_call (gfc_code* c)
5983 {
5984   gfc_component *comp;
5985   bool b;
5986
5987   b = gfc_is_proc_ptr_comp (c->expr1, &comp);
5988   gcc_assert (b);
5989
5990   c->resolved_sym = c->expr1->symtree->n.sym;
5991   c->expr1->expr_type = EXPR_VARIABLE;
5992
5993   if (!comp->attr.subroutine)
5994     gfc_add_subroutine (&comp->attr, comp->name, &c->expr1->where);
5995
5996   if (resolve_ref (c->expr1) == FAILURE)
5997     return FAILURE;
5998
5999   if (update_ppc_arglist (c->expr1) == FAILURE)
6000     return FAILURE;
6001
6002   c->ext.actual = c->expr1->value.compcall.actual;
6003
6004   if (resolve_actual_arglist (c->ext.actual, comp->attr.proc,
6005                               comp->formal == NULL) == FAILURE)
6006     return FAILURE;
6007
6008   gfc_ppc_use (comp, &c->expr1->value.compcall.actual, &c->expr1->where);
6009
6010   return SUCCESS;
6011 }
6012
6013
6014 /* Resolve a Function Call to a Procedure Pointer Component (Function).  */
6015
6016 static gfc_try
6017 resolve_expr_ppc (gfc_expr* e)
6018 {
6019   gfc_component *comp;
6020   bool b;
6021
6022   b = gfc_is_proc_ptr_comp (e, &comp);
6023   gcc_assert (b);
6024
6025   /* Convert to EXPR_FUNCTION.  */
6026   e->expr_type = EXPR_FUNCTION;
6027   e->value.function.isym = NULL;
6028   e->value.function.actual = e->value.compcall.actual;
6029   e->ts = comp->ts;
6030   if (comp->as != NULL)
6031     e->rank = comp->as->rank;
6032
6033   if (!comp->attr.function)
6034     gfc_add_function (&comp->attr, comp->name, &e->where);
6035
6036   if (resolve_ref (e) == FAILURE)
6037     return FAILURE;
6038
6039   if (resolve_actual_arglist (e->value.function.actual, comp->attr.proc,
6040                               comp->formal == NULL) == FAILURE)
6041     return FAILURE;
6042
6043   if (update_ppc_arglist (e) == FAILURE)
6044     return FAILURE;
6045
6046   gfc_ppc_use (comp, &e->value.compcall.actual, &e->where);
6047
6048   return SUCCESS;
6049 }
6050
6051
6052 static bool
6053 gfc_is_expandable_expr (gfc_expr *e)
6054 {
6055   gfc_constructor *con;
6056
6057   if (e->expr_type == EXPR_ARRAY)
6058     {
6059       /* Traverse the constructor looking for variables that are flavor
6060          parameter.  Parameters must be expanded since they are fully used at
6061          compile time.  */
6062       con = gfc_constructor_first (e->value.constructor);
6063       for (; con; con = gfc_constructor_next (con))
6064         {
6065           if (con->expr->expr_type == EXPR_VARIABLE
6066               && con->expr->symtree
6067               && (con->expr->symtree->n.sym->attr.flavor == FL_PARAMETER
6068               || con->expr->symtree->n.sym->attr.flavor == FL_VARIABLE))
6069             return true;
6070           if (con->expr->expr_type == EXPR_ARRAY
6071               && gfc_is_expandable_expr (con->expr))
6072             return true;
6073         }
6074     }
6075
6076   return false;
6077 }
6078
6079 /* Resolve an expression.  That is, make sure that types of operands agree
6080    with their operators, intrinsic operators are converted to function calls
6081    for overloaded types and unresolved function references are resolved.  */
6082
6083 gfc_try
6084 gfc_resolve_expr (gfc_expr *e)
6085 {
6086   gfc_try t;
6087   bool inquiry_save;
6088
6089   if (e == NULL)
6090     return SUCCESS;
6091
6092   /* inquiry_argument only applies to variables.  */
6093   inquiry_save = inquiry_argument;
6094   if (e->expr_type != EXPR_VARIABLE)
6095     inquiry_argument = false;
6096
6097   switch (e->expr_type)
6098     {
6099     case EXPR_OP:
6100       t = resolve_operator (e);
6101       break;
6102
6103     case EXPR_FUNCTION:
6104     case EXPR_VARIABLE:
6105
6106       if (check_host_association (e))
6107         t = resolve_function (e);
6108       else
6109         {
6110           t = resolve_variable (e);
6111           if (t == SUCCESS)
6112             expression_rank (e);
6113         }
6114
6115       if (e->ts.type == BT_CHARACTER && e->ts.u.cl == NULL && e->ref
6116           && e->ref->type != REF_SUBSTRING)
6117         gfc_resolve_substring_charlen (e);
6118
6119       break;
6120
6121     case EXPR_COMPCALL:
6122       t = resolve_typebound_function (e);
6123       break;
6124
6125     case EXPR_SUBSTRING:
6126       t = resolve_ref (e);
6127       break;
6128
6129     case EXPR_CONSTANT:
6130     case EXPR_NULL:
6131       t = SUCCESS;
6132       break;
6133
6134     case EXPR_PPC:
6135       t = resolve_expr_ppc (e);
6136       break;
6137
6138     case EXPR_ARRAY:
6139       t = FAILURE;
6140       if (resolve_ref (e) == FAILURE)
6141         break;
6142
6143       t = gfc_resolve_array_constructor (e);
6144       /* Also try to expand a constructor.  */
6145       if (t == SUCCESS)
6146         {
6147           expression_rank (e);
6148           if (gfc_is_constant_expr (e) || gfc_is_expandable_expr (e))
6149             gfc_expand_constructor (e, false);
6150         }
6151
6152       /* This provides the opportunity for the length of constructors with
6153          character valued function elements to propagate the string length
6154          to the expression.  */
6155       if (t == SUCCESS && e->ts.type == BT_CHARACTER)
6156         {
6157           /* For efficiency, we call gfc_expand_constructor for BT_CHARACTER
6158              here rather then add a duplicate test for it above.  */ 
6159           gfc_expand_constructor (e, false);
6160           t = gfc_resolve_character_array_constructor (e);
6161         }
6162
6163       break;
6164
6165     case EXPR_STRUCTURE:
6166       t = resolve_ref (e);
6167       if (t == FAILURE)
6168         break;
6169
6170       t = resolve_structure_cons (e, 0);
6171       if (t == FAILURE)
6172         break;
6173
6174       t = gfc_simplify_expr (e, 0);
6175       break;
6176
6177     default:
6178       gfc_internal_error ("gfc_resolve_expr(): Bad expression type");
6179     }
6180
6181   if (e->ts.type == BT_CHARACTER && t == SUCCESS && !e->ts.u.cl)
6182     fixup_charlen (e);
6183
6184   inquiry_argument = inquiry_save;
6185
6186   return t;
6187 }
6188
6189
6190 /* Resolve an expression from an iterator.  They must be scalar and have
6191    INTEGER or (optionally) REAL type.  */
6192
6193 static gfc_try
6194 gfc_resolve_iterator_expr (gfc_expr *expr, bool real_ok,
6195                            const char *name_msgid)
6196 {
6197   if (gfc_resolve_expr (expr) == FAILURE)
6198     return FAILURE;
6199
6200   if (expr->rank != 0)
6201     {
6202       gfc_error ("%s at %L must be a scalar", _(name_msgid), &expr->where);
6203       return FAILURE;
6204     }
6205
6206   if (expr->ts.type != BT_INTEGER)
6207     {
6208       if (expr->ts.type == BT_REAL)
6209         {
6210           if (real_ok)
6211             return gfc_notify_std (GFC_STD_F95_DEL,
6212                                    "Deleted feature: %s at %L must be integer",
6213                                    _(name_msgid), &expr->where);
6214           else
6215             {
6216               gfc_error ("%s at %L must be INTEGER", _(name_msgid),
6217                          &expr->where);
6218               return FAILURE;
6219             }
6220         }
6221       else
6222         {
6223           gfc_error ("%s at %L must be INTEGER", _(name_msgid), &expr->where);
6224           return FAILURE;
6225         }
6226     }
6227   return SUCCESS;
6228 }
6229
6230
6231 /* Resolve the expressions in an iterator structure.  If REAL_OK is
6232    false allow only INTEGER type iterators, otherwise allow REAL types.  */
6233
6234 gfc_try
6235 gfc_resolve_iterator (gfc_iterator *iter, bool real_ok)
6236 {
6237   if (gfc_resolve_iterator_expr (iter->var, real_ok, "Loop variable")
6238       == FAILURE)
6239     return FAILURE;
6240
6241   if (gfc_check_vardef_context (iter->var, false, false, _("iterator variable"))
6242       == FAILURE)
6243     return FAILURE;
6244
6245   if (gfc_resolve_iterator_expr (iter->start, real_ok,
6246                                  "Start expression in DO loop") == FAILURE)
6247     return FAILURE;
6248
6249   if (gfc_resolve_iterator_expr (iter->end, real_ok,
6250                                  "End expression in DO loop") == FAILURE)
6251     return FAILURE;
6252
6253   if (gfc_resolve_iterator_expr (iter->step, real_ok,
6254                                  "Step expression in DO loop") == FAILURE)
6255     return FAILURE;
6256
6257   if (iter->step->expr_type == EXPR_CONSTANT)
6258     {
6259       if ((iter->step->ts.type == BT_INTEGER
6260            && mpz_cmp_ui (iter->step->value.integer, 0) == 0)
6261           || (iter->step->ts.type == BT_REAL
6262               && mpfr_sgn (iter->step->value.real) == 0))
6263         {
6264           gfc_error ("Step expression in DO loop at %L cannot be zero",
6265                      &iter->step->where);
6266           return FAILURE;
6267         }
6268     }
6269
6270   /* Convert start, end, and step to the same type as var.  */
6271   if (iter->start->ts.kind != iter->var->ts.kind
6272       || iter->start->ts.type != iter->var->ts.type)
6273     gfc_convert_type (iter->start, &iter->var->ts, 2);
6274
6275   if (iter->end->ts.kind != iter->var->ts.kind
6276       || iter->end->ts.type != iter->var->ts.type)
6277     gfc_convert_type (iter->end, &iter->var->ts, 2);
6278
6279   if (iter->step->ts.kind != iter->var->ts.kind
6280       || iter->step->ts.type != iter->var->ts.type)
6281     gfc_convert_type (iter->step, &iter->var->ts, 2);
6282
6283   if (iter->start->expr_type == EXPR_CONSTANT
6284       && iter->end->expr_type == EXPR_CONSTANT
6285       && iter->step->expr_type == EXPR_CONSTANT)
6286     {
6287       int sgn, cmp;
6288       if (iter->start->ts.type == BT_INTEGER)
6289         {
6290           sgn = mpz_cmp_ui (iter->step->value.integer, 0);
6291           cmp = mpz_cmp (iter->end->value.integer, iter->start->value.integer);
6292         }
6293       else
6294         {
6295           sgn = mpfr_sgn (iter->step->value.real);
6296           cmp = mpfr_cmp (iter->end->value.real, iter->start->value.real);
6297         }
6298       if ((sgn > 0 && cmp < 0) || (sgn < 0 && cmp > 0))
6299         gfc_warning ("DO loop at %L will be executed zero times",
6300                      &iter->step->where);
6301     }
6302
6303   return SUCCESS;
6304 }
6305
6306
6307 /* Traversal function for find_forall_index.  f == 2 signals that
6308    that variable itself is not to be checked - only the references.  */
6309
6310 static bool
6311 forall_index (gfc_expr *expr, gfc_symbol *sym, int *f)
6312 {
6313   if (expr->expr_type != EXPR_VARIABLE)
6314     return false;
6315   
6316   /* A scalar assignment  */
6317   if (!expr->ref || *f == 1)
6318     {
6319       if (expr->symtree->n.sym == sym)
6320         return true;
6321       else
6322         return false;
6323     }
6324
6325   if (*f == 2)
6326     *f = 1;
6327   return false;
6328 }
6329
6330
6331 /* Check whether the FORALL index appears in the expression or not.
6332    Returns SUCCESS if SYM is found in EXPR.  */
6333
6334 gfc_try
6335 find_forall_index (gfc_expr *expr, gfc_symbol *sym, int f)
6336 {
6337   if (gfc_traverse_expr (expr, sym, forall_index, f))
6338     return SUCCESS;
6339   else
6340     return FAILURE;
6341 }
6342
6343
6344 /* Resolve a list of FORALL iterators.  The FORALL index-name is constrained
6345    to be a scalar INTEGER variable.  The subscripts and stride are scalar
6346    INTEGERs, and if stride is a constant it must be nonzero.
6347    Furthermore "A subscript or stride in a forall-triplet-spec shall
6348    not contain a reference to any index-name in the
6349    forall-triplet-spec-list in which it appears." (7.5.4.1)  */
6350
6351 static void
6352 resolve_forall_iterators (gfc_forall_iterator *it)
6353 {
6354   gfc_forall_iterator *iter, *iter2;
6355
6356   for (iter = it; iter; iter = iter->next)
6357     {
6358       if (gfc_resolve_expr (iter->var) == SUCCESS
6359           && (iter->var->ts.type != BT_INTEGER || iter->var->rank != 0))
6360         gfc_error ("FORALL index-name at %L must be a scalar INTEGER",
6361                    &iter->var->where);
6362
6363       if (gfc_resolve_expr (iter->start) == SUCCESS
6364           && (iter->start->ts.type != BT_INTEGER || iter->start->rank != 0))
6365         gfc_error ("FORALL start expression at %L must be a scalar INTEGER",
6366                    &iter->start->where);
6367       if (iter->var->ts.kind != iter->start->ts.kind)
6368         gfc_convert_type (iter->start, &iter->var->ts, 2);
6369
6370       if (gfc_resolve_expr (iter->end) == SUCCESS
6371           && (iter->end->ts.type != BT_INTEGER || iter->end->rank != 0))
6372         gfc_error ("FORALL end expression at %L must be a scalar INTEGER",
6373                    &iter->end->where);
6374       if (iter->var->ts.kind != iter->end->ts.kind)
6375         gfc_convert_type (iter->end, &iter->var->ts, 2);
6376
6377       if (gfc_resolve_expr (iter->stride) == SUCCESS)
6378         {
6379           if (iter->stride->ts.type != BT_INTEGER || iter->stride->rank != 0)
6380             gfc_error ("FORALL stride expression at %L must be a scalar %s",
6381                        &iter->stride->where, "INTEGER");
6382
6383           if (iter->stride->expr_type == EXPR_CONSTANT
6384               && mpz_cmp_ui(iter->stride->value.integer, 0) == 0)
6385             gfc_error ("FORALL stride expression at %L cannot be zero",
6386                        &iter->stride->where);
6387         }
6388       if (iter->var->ts.kind != iter->stride->ts.kind)
6389         gfc_convert_type (iter->stride, &iter->var->ts, 2);
6390     }
6391
6392   for (iter = it; iter; iter = iter->next)
6393     for (iter2 = iter; iter2; iter2 = iter2->next)
6394       {
6395         if (find_forall_index (iter2->start,
6396                                iter->var->symtree->n.sym, 0) == SUCCESS
6397             || find_forall_index (iter2->end,
6398                                   iter->var->symtree->n.sym, 0) == SUCCESS
6399             || find_forall_index (iter2->stride,
6400                                   iter->var->symtree->n.sym, 0) == SUCCESS)
6401           gfc_error ("FORALL index '%s' may not appear in triplet "
6402                      "specification at %L", iter->var->symtree->name,
6403                      &iter2->start->where);
6404       }
6405 }
6406
6407
6408 /* Given a pointer to a symbol that is a derived type, see if it's
6409    inaccessible, i.e. if it's defined in another module and the components are
6410    PRIVATE.  The search is recursive if necessary.  Returns zero if no
6411    inaccessible components are found, nonzero otherwise.  */
6412
6413 static int
6414 derived_inaccessible (gfc_symbol *sym)
6415 {
6416   gfc_component *c;
6417
6418   if (sym->attr.use_assoc && sym->attr.private_comp)
6419     return 1;
6420
6421   for (c = sym->components; c; c = c->next)
6422     {
6423         if (c->ts.type == BT_DERIVED && derived_inaccessible (c->ts.u.derived))
6424           return 1;
6425     }
6426
6427   return 0;
6428 }
6429
6430
6431 /* Resolve the argument of a deallocate expression.  The expression must be
6432    a pointer or a full array.  */
6433
6434 static gfc_try
6435 resolve_deallocate_expr (gfc_expr *e)
6436 {
6437   symbol_attribute attr;
6438   int allocatable, pointer;
6439   gfc_ref *ref;
6440   gfc_symbol *sym;
6441   gfc_component *c;
6442
6443   if (gfc_resolve_expr (e) == FAILURE)
6444     return FAILURE;
6445
6446   if (e->expr_type != EXPR_VARIABLE)
6447     goto bad;
6448
6449   sym = e->symtree->n.sym;
6450
6451   if (sym->ts.type == BT_CLASS)
6452     {
6453       allocatable = CLASS_DATA (sym)->attr.allocatable;
6454       pointer = CLASS_DATA (sym)->attr.class_pointer;
6455     }
6456   else
6457     {
6458       allocatable = sym->attr.allocatable;
6459       pointer = sym->attr.pointer;
6460     }
6461   for (ref = e->ref; ref; ref = ref->next)
6462     {
6463       switch (ref->type)
6464         {
6465         case REF_ARRAY:
6466           if (ref->u.ar.type != AR_FULL
6467               && !(ref->u.ar.type == AR_ELEMENT && ref->u.ar.as->rank == 0
6468                    && ref->u.ar.codimen && gfc_ref_this_image (ref)))
6469             allocatable = 0;
6470           break;
6471
6472         case REF_COMPONENT:
6473           c = ref->u.c.component;
6474           if (c->ts.type == BT_CLASS)
6475             {
6476               allocatable = CLASS_DATA (c)->attr.allocatable;
6477               pointer = CLASS_DATA (c)->attr.class_pointer;
6478             }
6479           else
6480             {
6481               allocatable = c->attr.allocatable;
6482               pointer = c->attr.pointer;
6483             }
6484           break;
6485
6486         case REF_SUBSTRING:
6487           allocatable = 0;
6488           break;
6489         }
6490     }
6491
6492   attr = gfc_expr_attr (e);
6493
6494   if (allocatable == 0 && attr.pointer == 0)
6495     {
6496     bad:
6497       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6498                  &e->where);
6499       return FAILURE;
6500     }
6501
6502   /* F2008, C644.  */
6503   if (gfc_is_coindexed (e))
6504     {
6505       gfc_error ("Coindexed allocatable object at %L", &e->where);
6506       return FAILURE;
6507     }
6508
6509   if (pointer
6510       && gfc_check_vardef_context (e, true, true, _("DEALLOCATE object"))
6511          == FAILURE)
6512     return FAILURE;
6513   if (gfc_check_vardef_context (e, false, true, _("DEALLOCATE object"))
6514       == FAILURE)
6515     return FAILURE;
6516
6517   return SUCCESS;
6518 }
6519
6520
6521 /* Returns true if the expression e contains a reference to the symbol sym.  */
6522 static bool
6523 sym_in_expr (gfc_expr *e, gfc_symbol *sym, int *f ATTRIBUTE_UNUSED)
6524 {
6525   if (e->expr_type == EXPR_VARIABLE && e->symtree->n.sym == sym)
6526     return true;
6527
6528   return false;
6529 }
6530
6531 bool
6532 gfc_find_sym_in_expr (gfc_symbol *sym, gfc_expr *e)
6533 {
6534   return gfc_traverse_expr (e, sym, sym_in_expr, 0);
6535 }
6536
6537
6538 /* Given the expression node e for an allocatable/pointer of derived type to be
6539    allocated, get the expression node to be initialized afterwards (needed for
6540    derived types with default initializers, and derived types with allocatable
6541    components that need nullification.)  */
6542
6543 gfc_expr *
6544 gfc_expr_to_initialize (gfc_expr *e)
6545 {
6546   gfc_expr *result;
6547   gfc_ref *ref;
6548   int i;
6549
6550   result = gfc_copy_expr (e);
6551
6552   /* Change the last array reference from AR_ELEMENT to AR_FULL.  */
6553   for (ref = result->ref; ref; ref = ref->next)
6554     if (ref->type == REF_ARRAY && ref->next == NULL)
6555       {
6556         ref->u.ar.type = AR_FULL;
6557
6558         for (i = 0; i < ref->u.ar.dimen; i++)
6559           ref->u.ar.start[i] = ref->u.ar.end[i] = ref->u.ar.stride[i] = NULL;
6560
6561         result->rank = ref->u.ar.dimen;
6562         break;
6563       }
6564
6565   return result;
6566 }
6567
6568
6569 /* If the last ref of an expression is an array ref, return a copy of the
6570    expression with that one removed.  Otherwise, a copy of the original
6571    expression.  This is used for allocate-expressions and pointer assignment
6572    LHS, where there may be an array specification that needs to be stripped
6573    off when using gfc_check_vardef_context.  */
6574
6575 static gfc_expr*
6576 remove_last_array_ref (gfc_expr* e)
6577 {
6578   gfc_expr* e2;
6579   gfc_ref** r;
6580
6581   e2 = gfc_copy_expr (e);
6582   for (r = &e2->ref; *r; r = &(*r)->next)
6583     if ((*r)->type == REF_ARRAY && !(*r)->next)
6584       {
6585         gfc_free_ref_list (*r);
6586         *r = NULL;
6587         break;
6588       }
6589
6590   return e2;
6591 }
6592
6593
6594 /* Used in resolve_allocate_expr to check that a allocation-object and
6595    a source-expr are conformable.  This does not catch all possible 
6596    cases; in particular a runtime checking is needed.  */
6597
6598 static gfc_try
6599 conformable_arrays (gfc_expr *e1, gfc_expr *e2)
6600 {
6601   gfc_ref *tail;
6602   for (tail = e2->ref; tail && tail->next; tail = tail->next);
6603   
6604   /* First compare rank.  */
6605   if (tail && e1->rank != tail->u.ar.as->rank)
6606     {
6607       gfc_error ("Source-expr at %L must be scalar or have the "
6608                  "same rank as the allocate-object at %L",
6609                  &e1->where, &e2->where);
6610       return FAILURE;
6611     }
6612
6613   if (e1->shape)
6614     {
6615       int i;
6616       mpz_t s;
6617
6618       mpz_init (s);
6619
6620       for (i = 0; i < e1->rank; i++)
6621         {
6622           if (tail->u.ar.end[i])
6623             {
6624               mpz_set (s, tail->u.ar.end[i]->value.integer);
6625               mpz_sub (s, s, tail->u.ar.start[i]->value.integer);
6626               mpz_add_ui (s, s, 1);
6627             }
6628           else
6629             {
6630               mpz_set (s, tail->u.ar.start[i]->value.integer);
6631             }
6632
6633           if (mpz_cmp (e1->shape[i], s) != 0)
6634             {
6635               gfc_error ("Source-expr at %L and allocate-object at %L must "
6636                          "have the same shape", &e1->where, &e2->where);
6637               mpz_clear (s);
6638               return FAILURE;
6639             }
6640         }
6641
6642       mpz_clear (s);
6643     }
6644
6645   return SUCCESS;
6646 }
6647
6648
6649 /* Resolve the expression in an ALLOCATE statement, doing the additional
6650    checks to see whether the expression is OK or not.  The expression must
6651    have a trailing array reference that gives the size of the array.  */
6652
6653 static gfc_try
6654 resolve_allocate_expr (gfc_expr *e, gfc_code *code)
6655 {
6656   int i, pointer, allocatable, dimension, is_abstract;
6657   int codimension;
6658   bool coindexed;
6659   symbol_attribute attr;
6660   gfc_ref *ref, *ref2;
6661   gfc_expr *e2;
6662   gfc_array_ref *ar;
6663   gfc_symbol *sym = NULL;
6664   gfc_alloc *a;
6665   gfc_component *c;
6666   gfc_try t;
6667
6668   /* Mark the ultimost array component as being in allocate to allow DIMEN_STAR
6669      checking of coarrays.  */
6670   for (ref = e->ref; ref; ref = ref->next)
6671     if (ref->next == NULL)
6672       break;
6673
6674   if (ref && ref->type == REF_ARRAY)
6675     ref->u.ar.in_allocate = true;
6676
6677   if (gfc_resolve_expr (e) == FAILURE)
6678     goto failure;
6679
6680   /* Make sure the expression is allocatable or a pointer.  If it is
6681      pointer, the next-to-last reference must be a pointer.  */
6682
6683   ref2 = NULL;
6684   if (e->symtree)
6685     sym = e->symtree->n.sym;
6686
6687   /* Check whether ultimate component is abstract and CLASS.  */
6688   is_abstract = 0;
6689
6690   if (e->expr_type != EXPR_VARIABLE)
6691     {
6692       allocatable = 0;
6693       attr = gfc_expr_attr (e);
6694       pointer = attr.pointer;
6695       dimension = attr.dimension;
6696       codimension = attr.codimension;
6697     }
6698   else
6699     {
6700       if (sym->ts.type == BT_CLASS)
6701         {
6702           allocatable = CLASS_DATA (sym)->attr.allocatable;
6703           pointer = CLASS_DATA (sym)->attr.class_pointer;
6704           dimension = CLASS_DATA (sym)->attr.dimension;
6705           codimension = CLASS_DATA (sym)->attr.codimension;
6706           is_abstract = CLASS_DATA (sym)->attr.abstract;
6707         }
6708       else
6709         {
6710           allocatable = sym->attr.allocatable;
6711           pointer = sym->attr.pointer;
6712           dimension = sym->attr.dimension;
6713           codimension = sym->attr.codimension;
6714         }
6715
6716       coindexed = false;
6717
6718       for (ref = e->ref; ref; ref2 = ref, ref = ref->next)
6719         {
6720           switch (ref->type)
6721             {
6722               case REF_ARRAY:
6723                 if (ref->u.ar.codimen > 0)
6724                   {
6725                     int n;
6726                     for (n = ref->u.ar.dimen;
6727                          n < ref->u.ar.dimen + ref->u.ar.codimen; n++)
6728                       if (ref->u.ar.dimen_type[n] != DIMEN_THIS_IMAGE)
6729                         {
6730                           coindexed = true;
6731                           break;
6732                         }
6733                    }
6734
6735                 if (ref->next != NULL)
6736                   pointer = 0;
6737                 break;
6738
6739               case REF_COMPONENT:
6740                 /* F2008, C644.  */
6741                 if (coindexed)
6742                   {
6743                     gfc_error ("Coindexed allocatable object at %L",
6744                                &e->where);
6745                     goto failure;
6746                   }
6747
6748                 c = ref->u.c.component;
6749                 if (c->ts.type == BT_CLASS)
6750                   {
6751                     allocatable = CLASS_DATA (c)->attr.allocatable;
6752                     pointer = CLASS_DATA (c)->attr.class_pointer;
6753                     dimension = CLASS_DATA (c)->attr.dimension;
6754                     codimension = CLASS_DATA (c)->attr.codimension;
6755                     is_abstract = CLASS_DATA (c)->attr.abstract;
6756                   }
6757                 else
6758                   {
6759                     allocatable = c->attr.allocatable;
6760                     pointer = c->attr.pointer;
6761                     dimension = c->attr.dimension;
6762                     codimension = c->attr.codimension;
6763                     is_abstract = c->attr.abstract;
6764                   }
6765                 break;
6766
6767               case REF_SUBSTRING:
6768                 allocatable = 0;
6769                 pointer = 0;
6770                 break;
6771             }
6772         }
6773     }
6774
6775   if (allocatable == 0 && pointer == 0)
6776     {
6777       gfc_error ("Allocate-object at %L must be ALLOCATABLE or a POINTER",
6778                  &e->where);
6779       goto failure;
6780     }
6781
6782   /* Some checks for the SOURCE tag.  */
6783   if (code->expr3)
6784     {
6785       /* Check F03:C631.  */
6786       if (!gfc_type_compatible (&e->ts, &code->expr3->ts))
6787         {
6788           gfc_error ("Type of entity at %L is type incompatible with "
6789                       "source-expr at %L", &e->where, &code->expr3->where);
6790           goto failure;
6791         }
6792
6793       /* Check F03:C632 and restriction following Note 6.18.  */
6794       if (code->expr3->rank > 0
6795           && conformable_arrays (code->expr3, e) == FAILURE)
6796         goto failure;
6797
6798       /* Check F03:C633.  */
6799       if (code->expr3->ts.kind != e->ts.kind)
6800         {
6801           gfc_error ("The allocate-object at %L and the source-expr at %L "
6802                       "shall have the same kind type parameter",
6803                       &e->where, &code->expr3->where);
6804           goto failure;
6805         }
6806
6807       /* Check F2008, C642.  */
6808       if (code->expr3->ts.type == BT_DERIVED
6809           && ((codimension &&  gfc_expr_attr (code->expr3).lock_comp)
6810               || (code->expr3->ts.u.derived->from_intmod
6811                      == INTMOD_ISO_FORTRAN_ENV
6812                   && code->expr3->ts.u.derived->intmod_sym_id
6813                      == ISOFORTRAN_LOCK_TYPE)))
6814         {
6815           gfc_error ("The source-expr at %L shall neither be of type "
6816                      "LOCK_TYPE nor have a LOCK_TYPE component if "
6817                       "allocate-object at %L is a coarray",
6818                       &code->expr3->where, &e->where);
6819           goto failure;
6820         }
6821     }
6822
6823   /* Check F08:C629.  */
6824   if (is_abstract && code->ext.alloc.ts.type == BT_UNKNOWN
6825       && !code->expr3)
6826     {
6827       gcc_assert (e->ts.type == BT_CLASS);
6828       gfc_error ("Allocating %s of ABSTRACT base type at %L requires a "
6829                  "type-spec or source-expr", sym->name, &e->where);
6830       goto failure;
6831     }
6832
6833   /* In the variable definition context checks, gfc_expr_attr is used
6834      on the expression.  This is fooled by the array specification
6835      present in e, thus we have to eliminate that one temporarily.  */
6836   e2 = remove_last_array_ref (e);
6837   t = SUCCESS;
6838   if (t == SUCCESS && pointer)
6839     t = gfc_check_vardef_context (e2, true, true, _("ALLOCATE object"));
6840   if (t == SUCCESS)
6841     t = gfc_check_vardef_context (e2, false, true, _("ALLOCATE object"));
6842   gfc_free_expr (e2);
6843   if (t == FAILURE)
6844     goto failure;
6845
6846   if (!code->expr3)
6847     {
6848       /* Set up default initializer if needed.  */
6849       gfc_typespec ts;
6850       gfc_expr *init_e;
6851
6852       if (code->ext.alloc.ts.type == BT_DERIVED)
6853         ts = code->ext.alloc.ts;
6854       else
6855         ts = e->ts;
6856
6857       if (ts.type == BT_CLASS)
6858         ts = ts.u.derived->components->ts;
6859
6860       if (ts.type == BT_DERIVED && (init_e = gfc_default_initializer (&ts)))
6861         {
6862           gfc_code *init_st = gfc_get_code ();
6863           init_st->loc = code->loc;
6864           init_st->op = EXEC_INIT_ASSIGN;
6865           init_st->expr1 = gfc_expr_to_initialize (e);
6866           init_st->expr2 = init_e;
6867           init_st->next = code->next;
6868           code->next = init_st;
6869         }
6870     }
6871   else if (code->expr3->mold && code->expr3->ts.type == BT_DERIVED)
6872     {
6873       /* Default initialization via MOLD (non-polymorphic).  */
6874       gfc_expr *rhs = gfc_default_initializer (&code->expr3->ts);
6875       gfc_resolve_expr (rhs);
6876       gfc_free_expr (code->expr3);
6877       code->expr3 = rhs;
6878     }
6879
6880   if (e->ts.type == BT_CLASS)
6881     {
6882       /* Make sure the vtab symbol is present when
6883          the module variables are generated.  */
6884       gfc_typespec ts = e->ts;
6885       if (code->expr3)
6886         ts = code->expr3->ts;
6887       else if (code->ext.alloc.ts.type == BT_DERIVED)
6888         ts = code->ext.alloc.ts;
6889       gfc_find_derived_vtab (ts.u.derived);
6890     }
6891
6892   if (dimension == 0 && codimension == 0)
6893     goto success;
6894
6895   /* Make sure the last reference node is an array specifiction.  */
6896
6897   if (!ref2 || ref2->type != REF_ARRAY || ref2->u.ar.type == AR_FULL
6898       || (dimension && ref2->u.ar.dimen == 0))
6899     {
6900       gfc_error ("Array specification required in ALLOCATE statement "
6901                  "at %L", &e->where);
6902       goto failure;
6903     }
6904
6905   /* Make sure that the array section reference makes sense in the
6906     context of an ALLOCATE specification.  */
6907
6908   ar = &ref2->u.ar;
6909
6910   if (codimension)
6911     for (i = ar->dimen; i < ar->dimen + ar->codimen; i++)
6912       if (ar->dimen_type[i] == DIMEN_THIS_IMAGE)
6913         {
6914           gfc_error ("Coarray specification required in ALLOCATE statement "
6915                      "at %L", &e->where);
6916           goto failure;
6917         }
6918
6919   for (i = 0; i < ar->dimen; i++)
6920     {
6921       if (ref2->u.ar.type == AR_ELEMENT)
6922         goto check_symbols;
6923
6924       switch (ar->dimen_type[i])
6925         {
6926         case DIMEN_ELEMENT:
6927           break;
6928
6929         case DIMEN_RANGE:
6930           if (ar->start[i] != NULL
6931               && ar->end[i] != NULL
6932               && ar->stride[i] == NULL)
6933             break;
6934
6935           /* Fall Through...  */
6936
6937         case DIMEN_UNKNOWN:
6938         case DIMEN_VECTOR:
6939         case DIMEN_STAR:
6940         case DIMEN_THIS_IMAGE:
6941           gfc_error ("Bad array specification in ALLOCATE statement at %L",
6942                      &e->where);
6943           goto failure;
6944         }
6945
6946 check_symbols:
6947       for (a = code->ext.alloc.list; a; a = a->next)
6948         {
6949           sym = a->expr->symtree->n.sym;
6950
6951           /* TODO - check derived type components.  */
6952           if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
6953             continue;
6954
6955           if ((ar->start[i] != NULL
6956                && gfc_find_sym_in_expr (sym, ar->start[i]))
6957               || (ar->end[i] != NULL
6958                   && gfc_find_sym_in_expr (sym, ar->end[i])))
6959             {
6960               gfc_error ("'%s' must not appear in the array specification at "
6961                          "%L in the same ALLOCATE statement where it is "
6962                          "itself allocated", sym->name, &ar->where);
6963               goto failure;
6964             }
6965         }
6966     }
6967
6968   for (i = ar->dimen; i < ar->codimen + ar->dimen; i++)
6969     {
6970       if (ar->dimen_type[i] == DIMEN_ELEMENT
6971           || ar->dimen_type[i] == DIMEN_RANGE)
6972         {
6973           if (i == (ar->dimen + ar->codimen - 1))
6974             {
6975               gfc_error ("Expected '*' in coindex specification in ALLOCATE "
6976                          "statement at %L", &e->where);
6977               goto failure;
6978             }
6979           break;
6980         }
6981
6982       if (ar->dimen_type[i] == DIMEN_STAR && i == (ar->dimen + ar->codimen - 1)
6983           && ar->stride[i] == NULL)
6984         break;
6985
6986       gfc_error ("Bad coarray specification in ALLOCATE statement at %L",
6987                  &e->where);
6988       goto failure;
6989     }
6990
6991 success:
6992   return SUCCESS;
6993
6994 failure:
6995   return FAILURE;
6996 }
6997
6998 static void
6999 resolve_allocate_deallocate (gfc_code *code, const char *fcn)
7000 {
7001   gfc_expr *stat, *errmsg, *pe, *qe;
7002   gfc_alloc *a, *p, *q;
7003
7004   stat = code->expr1;
7005   errmsg = code->expr2;
7006
7007   /* Check the stat variable.  */
7008   if (stat)
7009     {
7010       gfc_check_vardef_context (stat, false, false, _("STAT variable"));
7011
7012       if ((stat->ts.type != BT_INTEGER
7013            && !(stat->ref && (stat->ref->type == REF_ARRAY
7014                               || stat->ref->type == REF_COMPONENT)))
7015           || stat->rank > 0)
7016         gfc_error ("Stat-variable at %L must be a scalar INTEGER "
7017                    "variable", &stat->where);
7018
7019       for (p = code->ext.alloc.list; p; p = p->next)
7020         if (p->expr->symtree->n.sym->name == stat->symtree->n.sym->name)
7021           {
7022             gfc_ref *ref1, *ref2;
7023             bool found = true;
7024
7025             for (ref1 = p->expr->ref, ref2 = stat->ref; ref1 && ref2;
7026                  ref1 = ref1->next, ref2 = ref2->next)
7027               {
7028                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7029                   continue;
7030                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7031                   {
7032                     found = false;
7033                     break;
7034                   }
7035               }
7036
7037             if (found)
7038               {
7039                 gfc_error ("Stat-variable at %L shall not be %sd within "
7040                            "the same %s statement", &stat->where, fcn, fcn);
7041                 break;
7042               }
7043           }
7044     }
7045
7046   /* Check the errmsg variable.  */
7047   if (errmsg)
7048     {
7049       if (!stat)
7050         gfc_warning ("ERRMSG at %L is useless without a STAT tag",
7051                      &errmsg->where);
7052
7053       gfc_check_vardef_context (errmsg, false, false, _("ERRMSG variable"));
7054
7055       if ((errmsg->ts.type != BT_CHARACTER
7056            && !(errmsg->ref
7057                 && (errmsg->ref->type == REF_ARRAY
7058                     || errmsg->ref->type == REF_COMPONENT)))
7059           || errmsg->rank > 0 )
7060         gfc_error ("Errmsg-variable at %L must be a scalar CHARACTER "
7061                    "variable", &errmsg->where);
7062
7063       for (p = code->ext.alloc.list; p; p = p->next)
7064         if (p->expr->symtree->n.sym->name == errmsg->symtree->n.sym->name)
7065           {
7066             gfc_ref *ref1, *ref2;
7067             bool found = true;
7068
7069             for (ref1 = p->expr->ref, ref2 = errmsg->ref; ref1 && ref2;
7070                  ref1 = ref1->next, ref2 = ref2->next)
7071               {
7072                 if (ref1->type != REF_COMPONENT || ref2->type != REF_COMPONENT)
7073                   continue;
7074                 if (ref1->u.c.component->name != ref2->u.c.component->name)
7075                   {
7076                     found = false;
7077                     break;
7078                   }
7079               }
7080
7081             if (found)
7082               {
7083                 gfc_error ("Errmsg-variable at %L shall not be %sd within "
7084                            "the same %s statement", &errmsg->where, fcn, fcn);
7085                 break;
7086               }
7087           }
7088     }
7089
7090   /* Check that an allocate-object appears only once in the statement.  
7091      FIXME: Checking derived types is disabled.  */
7092   for (p = code->ext.alloc.list; p; p = p->next)
7093     {
7094       pe = p->expr;
7095       for (q = p->next; q; q = q->next)
7096         {
7097           qe = q->expr;
7098           if (pe->symtree->n.sym->name == qe->symtree->n.sym->name)
7099             {
7100               /* This is a potential collision.  */
7101               gfc_ref *pr = pe->ref;
7102               gfc_ref *qr = qe->ref;
7103               
7104               /* Follow the references  until
7105                  a) They start to differ, in which case there is no error;
7106                  you can deallocate a%b and a%c in a single statement
7107                  b) Both of them stop, which is an error
7108                  c) One of them stops, which is also an error.  */
7109               while (1)
7110                 {
7111                   if (pr == NULL && qr == NULL)
7112                     {
7113                       gfc_error ("Allocate-object at %L also appears at %L",
7114                                  &pe->where, &qe->where);
7115                       break;
7116                     }
7117                   else if (pr != NULL && qr == NULL)
7118                     {
7119                       gfc_error ("Allocate-object at %L is subobject of"
7120                                  " object at %L", &pe->where, &qe->where);
7121                       break;
7122                     }
7123                   else if (pr == NULL && qr != NULL)
7124                     {
7125                       gfc_error ("Allocate-object at %L is subobject of"
7126                                  " object at %L", &qe->where, &pe->where);
7127                       break;
7128                     }
7129                   /* Here, pr != NULL && qr != NULL  */
7130                   gcc_assert(pr->type == qr->type);
7131                   if (pr->type == REF_ARRAY)
7132                     {
7133                       /* Handle cases like allocate(v(3)%x(3), v(2)%x(3)),
7134                          which are legal.  */
7135                       gcc_assert (qr->type == REF_ARRAY);
7136
7137                       if (pr->next && qr->next)
7138                         {
7139                           gfc_array_ref *par = &(pr->u.ar);
7140                           gfc_array_ref *qar = &(qr->u.ar);
7141                           if (gfc_dep_compare_expr (par->start[0],
7142                                                     qar->start[0]) != 0)
7143                               break;
7144                         }
7145                     }
7146                   else
7147                     {
7148                       if (pr->u.c.component->name != qr->u.c.component->name)
7149                         break;
7150                     }
7151                   
7152                   pr = pr->next;
7153                   qr = qr->next;
7154                 }
7155             }
7156         }
7157     }
7158
7159   if (strcmp (fcn, "ALLOCATE") == 0)
7160     {
7161       for (a = code->ext.alloc.list; a; a = a->next)
7162         resolve_allocate_expr (a->expr, code);
7163     }
7164   else
7165     {
7166       for (a = code->ext.alloc.list; a; a = a->next)
7167         resolve_deallocate_expr (a->expr);
7168     }
7169 }
7170
7171
7172 /************ SELECT CASE resolution subroutines ************/
7173
7174 /* Callback function for our mergesort variant.  Determines interval
7175    overlaps for CASEs. Return <0 if op1 < op2, 0 for overlap, >0 for
7176    op1 > op2.  Assumes we're not dealing with the default case.  
7177    We have op1 = (:L), (K:L) or (K:) and op2 = (:N), (M:N) or (M:).
7178    There are nine situations to check.  */
7179
7180 static int
7181 compare_cases (const gfc_case *op1, const gfc_case *op2)
7182 {
7183   int retval;
7184
7185   if (op1->low == NULL) /* op1 = (:L)  */
7186     {
7187       /* op2 = (:N), so overlap.  */
7188       retval = 0;
7189       /* op2 = (M:) or (M:N),  L < M  */
7190       if (op2->low != NULL
7191           && gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7192         retval = -1;
7193     }
7194   else if (op1->high == NULL) /* op1 = (K:)  */
7195     {
7196       /* op2 = (M:), so overlap.  */
7197       retval = 0;
7198       /* op2 = (:N) or (M:N), K > N  */
7199       if (op2->high != NULL
7200           && gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7201         retval = 1;
7202     }
7203   else /* op1 = (K:L)  */
7204     {
7205       if (op2->low == NULL)       /* op2 = (:N), K > N  */
7206         retval = (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7207                  ? 1 : 0;
7208       else if (op2->high == NULL) /* op2 = (M:), L < M  */
7209         retval = (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7210                  ? -1 : 0;
7211       else                      /* op2 = (M:N)  */
7212         {
7213           retval =  0;
7214           /* L < M  */
7215           if (gfc_compare_expr (op1->high, op2->low, INTRINSIC_LT) < 0)
7216             retval =  -1;
7217           /* K > N  */
7218           else if (gfc_compare_expr (op1->low, op2->high, INTRINSIC_GT) > 0)
7219             retval =  1;
7220         }
7221     }
7222
7223   return retval;
7224 }
7225
7226
7227 /* Merge-sort a double linked case list, detecting overlap in the
7228    process.  LIST is the head of the double linked case list before it
7229    is sorted.  Returns the head of the sorted list if we don't see any
7230    overlap, or NULL otherwise.  */
7231
7232 static gfc_case *
7233 check_case_overlap (gfc_case *list)
7234 {
7235   gfc_case *p, *q, *e, *tail;
7236   int insize, nmerges, psize, qsize, cmp, overlap_seen;
7237
7238   /* If the passed list was empty, return immediately.  */
7239   if (!list)
7240     return NULL;
7241
7242   overlap_seen = 0;
7243   insize = 1;
7244
7245   /* Loop unconditionally.  The only exit from this loop is a return
7246      statement, when we've finished sorting the case list.  */
7247   for (;;)
7248     {
7249       p = list;
7250       list = NULL;
7251       tail = NULL;
7252
7253       /* Count the number of merges we do in this pass.  */
7254       nmerges = 0;
7255
7256       /* Loop while there exists a merge to be done.  */
7257       while (p)
7258         {
7259           int i;
7260
7261           /* Count this merge.  */
7262           nmerges++;
7263
7264           /* Cut the list in two pieces by stepping INSIZE places
7265              forward in the list, starting from P.  */
7266           psize = 0;
7267           q = p;
7268           for (i = 0; i < insize; i++)
7269             {
7270               psize++;
7271               q = q->right;
7272               if (!q)
7273                 break;
7274             }
7275           qsize = insize;
7276
7277           /* Now we have two lists.  Merge them!  */
7278           while (psize > 0 || (qsize > 0 && q != NULL))
7279             {
7280               /* See from which the next case to merge comes from.  */
7281               if (psize == 0)
7282                 {
7283                   /* P is empty so the next case must come from Q.  */
7284                   e = q;
7285                   q = q->right;
7286                   qsize--;
7287                 }
7288               else if (qsize == 0 || q == NULL)
7289                 {
7290                   /* Q is empty.  */
7291                   e = p;
7292                   p = p->right;
7293                   psize--;
7294                 }
7295               else
7296                 {
7297                   cmp = compare_cases (p, q);
7298                   if (cmp < 0)
7299                     {
7300                       /* The whole case range for P is less than the
7301                          one for Q.  */
7302                       e = p;
7303                       p = p->right;
7304                       psize--;
7305                     }
7306                   else if (cmp > 0)
7307                     {
7308                       /* The whole case range for Q is greater than
7309                          the case range for P.  */
7310                       e = q;
7311                       q = q->right;
7312                       qsize--;
7313                     }
7314                   else
7315                     {
7316                       /* The cases overlap, or they are the same
7317                          element in the list.  Either way, we must
7318                          issue an error and get the next case from P.  */
7319                       /* FIXME: Sort P and Q by line number.  */
7320                       gfc_error ("CASE label at %L overlaps with CASE "
7321                                  "label at %L", &p->where, &q->where);
7322                       overlap_seen = 1;
7323                       e = p;
7324                       p = p->right;
7325                       psize--;
7326                     }
7327                 }
7328
7329                 /* Add the next element to the merged list.  */
7330               if (tail)
7331                 tail->right = e;
7332               else
7333                 list = e;
7334               e->left = tail;
7335               tail = e;
7336             }
7337
7338           /* P has now stepped INSIZE places along, and so has Q.  So
7339              they're the same.  */
7340           p = q;
7341         }
7342       tail->right = NULL;
7343
7344       /* If we have done only one merge or none at all, we've
7345          finished sorting the cases.  */
7346       if (nmerges <= 1)
7347         {
7348           if (!overlap_seen)
7349             return list;
7350           else
7351             return NULL;
7352         }
7353
7354       /* Otherwise repeat, merging lists twice the size.  */
7355       insize *= 2;
7356     }
7357 }
7358
7359
7360 /* Check to see if an expression is suitable for use in a CASE statement.
7361    Makes sure that all case expressions are scalar constants of the same
7362    type.  Return FAILURE if anything is wrong.  */
7363
7364 static gfc_try
7365 validate_case_label_expr (gfc_expr *e, gfc_expr *case_expr)
7366 {
7367   if (e == NULL) return SUCCESS;
7368
7369   if (e->ts.type != case_expr->ts.type)
7370     {
7371       gfc_error ("Expression in CASE statement at %L must be of type %s",
7372                  &e->where, gfc_basic_typename (case_expr->ts.type));
7373       return FAILURE;
7374     }
7375
7376   /* C805 (R808) For a given case-construct, each case-value shall be of
7377      the same type as case-expr.  For character type, length differences
7378      are allowed, but the kind type parameters shall be the same.  */
7379
7380   if (case_expr->ts.type == BT_CHARACTER && e->ts.kind != case_expr->ts.kind)
7381     {
7382       gfc_error ("Expression in CASE statement at %L must be of kind %d",
7383                  &e->where, case_expr->ts.kind);
7384       return FAILURE;
7385     }
7386
7387   /* Convert the case value kind to that of case expression kind,
7388      if needed */
7389
7390   if (e->ts.kind != case_expr->ts.kind)
7391     gfc_convert_type_warn (e, &case_expr->ts, 2, 0);
7392
7393   if (e->rank != 0)
7394     {
7395       gfc_error ("Expression in CASE statement at %L must be scalar",
7396                  &e->where);
7397       return FAILURE;
7398     }
7399
7400   return SUCCESS;
7401 }
7402
7403
7404 /* Given a completely parsed select statement, we:
7405
7406      - Validate all expressions and code within the SELECT.
7407      - Make sure that the selection expression is not of the wrong type.
7408      - Make sure that no case ranges overlap.
7409      - Eliminate unreachable cases and unreachable code resulting from
7410        removing case labels.
7411
7412    The standard does allow unreachable cases, e.g. CASE (5:3).  But
7413    they are a hassle for code generation, and to prevent that, we just
7414    cut them out here.  This is not necessary for overlapping cases
7415    because they are illegal and we never even try to generate code.
7416
7417    We have the additional caveat that a SELECT construct could have
7418    been a computed GOTO in the source code. Fortunately we can fairly
7419    easily work around that here: The case_expr for a "real" SELECT CASE
7420    is in code->expr1, but for a computed GOTO it is in code->expr2. All
7421    we have to do is make sure that the case_expr is a scalar integer
7422    expression.  */
7423
7424 static void
7425 resolve_select (gfc_code *code)
7426 {
7427   gfc_code *body;
7428   gfc_expr *case_expr;
7429   gfc_case *cp, *default_case, *tail, *head;
7430   int seen_unreachable;
7431   int seen_logical;
7432   int ncases;
7433   bt type;
7434   gfc_try t;
7435
7436   if (code->expr1 == NULL)
7437     {
7438       /* This was actually a computed GOTO statement.  */
7439       case_expr = code->expr2;
7440       if (case_expr->ts.type != BT_INTEGER|| case_expr->rank != 0)
7441         gfc_error ("Selection expression in computed GOTO statement "
7442                    "at %L must be a scalar integer expression",
7443                    &case_expr->where);
7444
7445       /* Further checking is not necessary because this SELECT was built
7446          by the compiler, so it should always be OK.  Just move the
7447          case_expr from expr2 to expr so that we can handle computed
7448          GOTOs as normal SELECTs from here on.  */
7449       code->expr1 = code->expr2;
7450       code->expr2 = NULL;
7451       return;
7452     }
7453
7454   case_expr = code->expr1;
7455
7456   type = case_expr->ts.type;
7457   if (type != BT_LOGICAL && type != BT_INTEGER && type != BT_CHARACTER)
7458     {
7459       gfc_error ("Argument of SELECT statement at %L cannot be %s",
7460                  &case_expr->where, gfc_typename (&case_expr->ts));
7461
7462       /* Punt. Going on here just produce more garbage error messages.  */
7463       return;
7464     }
7465
7466   if (case_expr->rank != 0)
7467     {
7468       gfc_error ("Argument of SELECT statement at %L must be a scalar "
7469                  "expression", &case_expr->where);
7470
7471       /* Punt.  */
7472       return;
7473     }
7474
7475
7476   /* Raise a warning if an INTEGER case value exceeds the range of
7477      the case-expr. Later, all expressions will be promoted to the
7478      largest kind of all case-labels.  */
7479
7480   if (type == BT_INTEGER)
7481     for (body = code->block; body; body = body->block)
7482       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7483         {
7484           if (cp->low
7485               && gfc_check_integer_range (cp->low->value.integer,
7486                                           case_expr->ts.kind) != ARITH_OK)
7487             gfc_warning ("Expression in CASE statement at %L is "
7488                          "not in the range of %s", &cp->low->where,
7489                          gfc_typename (&case_expr->ts));
7490
7491           if (cp->high
7492               && cp->low != cp->high
7493               && gfc_check_integer_range (cp->high->value.integer,
7494                                           case_expr->ts.kind) != ARITH_OK)
7495             gfc_warning ("Expression in CASE statement at %L is "
7496                          "not in the range of %s", &cp->high->where,
7497                          gfc_typename (&case_expr->ts));
7498         }
7499
7500   /* PR 19168 has a long discussion concerning a mismatch of the kinds
7501      of the SELECT CASE expression and its CASE values.  Walk the lists
7502      of case values, and if we find a mismatch, promote case_expr to
7503      the appropriate kind.  */
7504
7505   if (type == BT_LOGICAL || type == BT_INTEGER)
7506     {
7507       for (body = code->block; body; body = body->block)
7508         {
7509           /* Walk the case label list.  */
7510           for (cp = body->ext.block.case_list; cp; cp = cp->next)
7511             {
7512               /* Intercept the DEFAULT case.  It does not have a kind.  */
7513               if (cp->low == NULL && cp->high == NULL)
7514                 continue;
7515
7516               /* Unreachable case ranges are discarded, so ignore.  */
7517               if (cp->low != NULL && cp->high != NULL
7518                   && cp->low != cp->high
7519                   && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7520                 continue;
7521
7522               if (cp->low != NULL
7523                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->low))
7524                 gfc_convert_type_warn (case_expr, &cp->low->ts, 2, 0);
7525
7526               if (cp->high != NULL
7527                   && case_expr->ts.kind != gfc_kind_max(case_expr, cp->high))
7528                 gfc_convert_type_warn (case_expr, &cp->high->ts, 2, 0);
7529             }
7530          }
7531     }
7532
7533   /* Assume there is no DEFAULT case.  */
7534   default_case = NULL;
7535   head = tail = NULL;
7536   ncases = 0;
7537   seen_logical = 0;
7538
7539   for (body = code->block; body; body = body->block)
7540     {
7541       /* Assume the CASE list is OK, and all CASE labels can be matched.  */
7542       t = SUCCESS;
7543       seen_unreachable = 0;
7544
7545       /* Walk the case label list, making sure that all case labels
7546          are legal.  */
7547       for (cp = body->ext.block.case_list; cp; cp = cp->next)
7548         {
7549           /* Count the number of cases in the whole construct.  */
7550           ncases++;
7551
7552           /* Intercept the DEFAULT case.  */
7553           if (cp->low == NULL && cp->high == NULL)
7554             {
7555               if (default_case != NULL)
7556                 {
7557                   gfc_error ("The DEFAULT CASE at %L cannot be followed "
7558                              "by a second DEFAULT CASE at %L",
7559                              &default_case->where, &cp->where);
7560                   t = FAILURE;
7561                   break;
7562                 }
7563               else
7564                 {
7565                   default_case = cp;
7566                   continue;
7567                 }
7568             }
7569
7570           /* Deal with single value cases and case ranges.  Errors are
7571              issued from the validation function.  */
7572           if (validate_case_label_expr (cp->low, case_expr) != SUCCESS
7573               || validate_case_label_expr (cp->high, case_expr) != SUCCESS)
7574             {
7575               t = FAILURE;
7576               break;
7577             }
7578
7579           if (type == BT_LOGICAL
7580               && ((cp->low == NULL || cp->high == NULL)
7581                   || cp->low != cp->high))
7582             {
7583               gfc_error ("Logical range in CASE statement at %L is not "
7584                          "allowed", &cp->low->where);
7585               t = FAILURE;
7586               break;
7587             }
7588
7589           if (type == BT_LOGICAL && cp->low->expr_type == EXPR_CONSTANT)
7590             {
7591               int value;
7592               value = cp->low->value.logical == 0 ? 2 : 1;
7593               if (value & seen_logical)
7594                 {
7595                   gfc_error ("Constant logical value in CASE statement "
7596                              "is repeated at %L",
7597                              &cp->low->where);
7598                   t = FAILURE;
7599                   break;
7600                 }
7601               seen_logical |= value;
7602             }
7603
7604           if (cp->low != NULL && cp->high != NULL
7605               && cp->low != cp->high
7606               && gfc_compare_expr (cp->low, cp->high, INTRINSIC_GT) > 0)
7607             {
7608               if (gfc_option.warn_surprising)
7609                 gfc_warning ("Range specification at %L can never "
7610                              "be matched", &cp->where);
7611
7612               cp->unreachable = 1;
7613               seen_unreachable = 1;
7614             }
7615           else
7616             {
7617               /* If the case range can be matched, it can also overlap with
7618                  other cases.  To make sure it does not, we put it in a
7619                  double linked list here.  We sort that with a merge sort
7620                  later on to detect any overlapping cases.  */
7621               if (!head)
7622                 {
7623                   head = tail = cp;
7624                   head->right = head->left = NULL;
7625                 }
7626               else
7627                 {
7628                   tail->right = cp;
7629                   tail->right->left = tail;
7630                   tail = tail->right;
7631                   tail->right = NULL;
7632                 }
7633             }
7634         }
7635
7636       /* It there was a failure in the previous case label, give up
7637          for this case label list.  Continue with the next block.  */
7638       if (t == FAILURE)
7639         continue;
7640
7641       /* See if any case labels that are unreachable have been seen.
7642          If so, we eliminate them.  This is a bit of a kludge because
7643          the case lists for a single case statement (label) is a
7644          single forward linked lists.  */
7645       if (seen_unreachable)
7646       {
7647         /* Advance until the first case in the list is reachable.  */
7648         while (body->ext.block.case_list != NULL
7649                && body->ext.block.case_list->unreachable)
7650           {
7651             gfc_case *n = body->ext.block.case_list;
7652             body->ext.block.case_list = body->ext.block.case_list->next;
7653             n->next = NULL;
7654             gfc_free_case_list (n);
7655           }
7656
7657         /* Strip all other unreachable cases.  */
7658         if (body->ext.block.case_list)
7659           {
7660             for (cp = body->ext.block.case_list; cp->next; cp = cp->next)
7661               {
7662                 if (cp->next->unreachable)
7663                   {
7664                     gfc_case *n = cp->next;
7665                     cp->next = cp->next->next;
7666                     n->next = NULL;
7667                     gfc_free_case_list (n);
7668                   }
7669               }
7670           }
7671       }
7672     }
7673
7674   /* See if there were overlapping cases.  If the check returns NULL,
7675      there was overlap.  In that case we don't do anything.  If head
7676      is non-NULL, we prepend the DEFAULT case.  The sorted list can
7677      then used during code generation for SELECT CASE constructs with
7678      a case expression of a CHARACTER type.  */
7679   if (head)
7680     {
7681       head = check_case_overlap (head);
7682
7683       /* Prepend the default_case if it is there.  */
7684       if (head != NULL && default_case)
7685         {
7686           default_case->left = NULL;
7687           default_case->right = head;
7688           head->left = default_case;
7689         }
7690     }
7691
7692   /* Eliminate dead blocks that may be the result if we've seen
7693      unreachable case labels for a block.  */
7694   for (body = code; body && body->block; body = body->block)
7695     {
7696       if (body->block->ext.block.case_list == NULL)
7697         {
7698           /* Cut the unreachable block from the code chain.  */
7699           gfc_code *c = body->block;
7700           body->block = c->block;
7701
7702           /* Kill the dead block, but not the blocks below it.  */
7703           c->block = NULL;
7704           gfc_free_statements (c);
7705         }
7706     }
7707
7708   /* More than two cases is legal but insane for logical selects.
7709      Issue a warning for it.  */
7710   if (gfc_option.warn_surprising && type == BT_LOGICAL
7711       && ncases > 2)
7712     gfc_warning ("Logical SELECT CASE block at %L has more that two cases",
7713                  &code->loc);
7714 }
7715
7716
7717 /* Check if a derived type is extensible.  */
7718
7719 bool
7720 gfc_type_is_extensible (gfc_symbol *sym)
7721 {
7722   return !(sym->attr.is_bind_c || sym->attr.sequence);
7723 }
7724
7725
7726 /* Resolve an associate name:  Resolve target and ensure the type-spec is
7727    correct as well as possibly the array-spec.  */
7728
7729 static void
7730 resolve_assoc_var (gfc_symbol* sym, bool resolve_target)
7731 {
7732   gfc_expr* target;
7733
7734   gcc_assert (sym->assoc);
7735   gcc_assert (sym->attr.flavor == FL_VARIABLE);
7736
7737   /* If this is for SELECT TYPE, the target may not yet be set.  In that
7738      case, return.  Resolution will be called later manually again when
7739      this is done.  */
7740   target = sym->assoc->target;
7741   if (!target)
7742     return;
7743   gcc_assert (!sym->assoc->dangling);
7744
7745   if (resolve_target && gfc_resolve_expr (target) != SUCCESS)
7746     return;
7747
7748   /* For variable targets, we get some attributes from the target.  */
7749   if (target->expr_type == EXPR_VARIABLE)
7750     {
7751       gfc_symbol* tsym;
7752
7753       gcc_assert (target->symtree);
7754       tsym = target->symtree->n.sym;
7755
7756       sym->attr.asynchronous = tsym->attr.asynchronous;
7757       sym->attr.volatile_ = tsym->attr.volatile_;
7758
7759       sym->attr.target = (tsym->attr.target || tsym->attr.pointer);
7760     }
7761
7762   /* Get type if this was not already set.  Note that it can be
7763      some other type than the target in case this is a SELECT TYPE
7764      selector!  So we must not update when the type is already there.  */
7765   if (sym->ts.type == BT_UNKNOWN)
7766     sym->ts = target->ts;
7767   gcc_assert (sym->ts.type != BT_UNKNOWN);
7768
7769   /* See if this is a valid association-to-variable.  */
7770   sym->assoc->variable = (target->expr_type == EXPR_VARIABLE
7771                           && !gfc_has_vector_subscript (target));
7772
7773   /* Finally resolve if this is an array or not.  */
7774   if (sym->attr.dimension && target->rank == 0)
7775     {
7776       gfc_error ("Associate-name '%s' at %L is used as array",
7777                  sym->name, &sym->declared_at);
7778       sym->attr.dimension = 0;
7779       return;
7780     }
7781   if (target->rank > 0)
7782     sym->attr.dimension = 1;
7783
7784   if (sym->attr.dimension)
7785     {
7786       sym->as = gfc_get_array_spec ();
7787       sym->as->rank = target->rank;
7788       sym->as->type = AS_DEFERRED;
7789
7790       /* Target must not be coindexed, thus the associate-variable
7791          has no corank.  */
7792       sym->as->corank = 0;
7793     }
7794 }
7795
7796
7797 /* Resolve a SELECT TYPE statement.  */
7798
7799 static void
7800 resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
7801 {
7802   gfc_symbol *selector_type;
7803   gfc_code *body, *new_st, *if_st, *tail;
7804   gfc_code *class_is = NULL, *default_case = NULL;
7805   gfc_case *c;
7806   gfc_symtree *st;
7807   char name[GFC_MAX_SYMBOL_LEN];
7808   gfc_namespace *ns;
7809   int error = 0;
7810
7811   ns = code->ext.block.ns;
7812   gfc_resolve (ns);
7813
7814   /* Check for F03:C813.  */
7815   if (code->expr1->ts.type != BT_CLASS
7816       && !(code->expr2 && code->expr2->ts.type == BT_CLASS))
7817     {
7818       gfc_error ("Selector shall be polymorphic in SELECT TYPE statement "
7819                  "at %L", &code->loc);
7820       return;
7821     }
7822
7823   if (code->expr2)
7824     {
7825       if (code->expr1->symtree->n.sym->attr.untyped)
7826         code->expr1->symtree->n.sym->ts = code->expr2->ts;
7827       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
7828     }
7829   else
7830     selector_type = CLASS_DATA (code->expr1)->ts.u.derived;
7831
7832   /* Loop over TYPE IS / CLASS IS cases.  */
7833   for (body = code->block; body; body = body->block)
7834     {
7835       c = body->ext.block.case_list;
7836
7837       /* Check F03:C815.  */
7838       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7839           && !gfc_type_is_extensible (c->ts.u.derived))
7840         {
7841           gfc_error ("Derived type '%s' at %L must be extensible",
7842                      c->ts.u.derived->name, &c->where);
7843           error++;
7844           continue;
7845         }
7846
7847       /* Check F03:C816.  */
7848       if ((c->ts.type == BT_DERIVED || c->ts.type == BT_CLASS)
7849           && !gfc_type_is_extension_of (selector_type, c->ts.u.derived))
7850         {
7851           gfc_error ("Derived type '%s' at %L must be an extension of '%s'",
7852                      c->ts.u.derived->name, &c->where, selector_type->name);
7853           error++;
7854           continue;
7855         }
7856
7857       /* Intercept the DEFAULT case.  */
7858       if (c->ts.type == BT_UNKNOWN)
7859         {
7860           /* Check F03:C818.  */
7861           if (default_case)
7862             {
7863               gfc_error ("The DEFAULT CASE at %L cannot be followed "
7864                          "by a second DEFAULT CASE at %L",
7865                          &default_case->ext.block.case_list->where, &c->where);
7866               error++;
7867               continue;
7868             }
7869
7870           default_case = body;
7871         }
7872     }
7873     
7874   if (error > 0)
7875     return;
7876
7877   /* Transform SELECT TYPE statement to BLOCK and associate selector to
7878      target if present.  If there are any EXIT statements referring to the
7879      SELECT TYPE construct, this is no problem because the gfc_code
7880      reference stays the same and EXIT is equally possible from the BLOCK
7881      it is changed to.  */
7882   code->op = EXEC_BLOCK;
7883   if (code->expr2)
7884     {
7885       gfc_association_list* assoc;
7886
7887       assoc = gfc_get_association_list ();
7888       assoc->st = code->expr1->symtree;
7889       assoc->target = gfc_copy_expr (code->expr2);
7890       /* assoc->variable will be set by resolve_assoc_var.  */
7891       
7892       code->ext.block.assoc = assoc;
7893       code->expr1->symtree->n.sym->assoc = assoc;
7894
7895       resolve_assoc_var (code->expr1->symtree->n.sym, false);
7896     }
7897   else
7898     code->ext.block.assoc = NULL;
7899
7900   /* Add EXEC_SELECT to switch on type.  */
7901   new_st = gfc_get_code ();
7902   new_st->op = code->op;
7903   new_st->expr1 = code->expr1;
7904   new_st->expr2 = code->expr2;
7905   new_st->block = code->block;
7906   code->expr1 = code->expr2 =  NULL;
7907   code->block = NULL;
7908   if (!ns->code)
7909     ns->code = new_st;
7910   else
7911     ns->code->next = new_st;
7912   code = new_st;
7913   code->op = EXEC_SELECT;
7914   gfc_add_vptr_component (code->expr1);
7915   gfc_add_hash_component (code->expr1);
7916
7917   /* Loop over TYPE IS / CLASS IS cases.  */
7918   for (body = code->block; body; body = body->block)
7919     {
7920       c = body->ext.block.case_list;
7921
7922       if (c->ts.type == BT_DERIVED)
7923         c->low = c->high = gfc_get_int_expr (gfc_default_integer_kind, NULL,
7924                                              c->ts.u.derived->hash_value);
7925
7926       else if (c->ts.type == BT_UNKNOWN)
7927         continue;
7928
7929       /* Associate temporary to selector.  This should only be done
7930          when this case is actually true, so build a new ASSOCIATE
7931          that does precisely this here (instead of using the
7932          'global' one).  */
7933
7934       if (c->ts.type == BT_CLASS)
7935         sprintf (name, "__tmp_class_%s", c->ts.u.derived->name);
7936       else
7937         sprintf (name, "__tmp_type_%s", c->ts.u.derived->name);
7938       st = gfc_find_symtree (ns->sym_root, name);
7939       gcc_assert (st->n.sym->assoc);
7940       st->n.sym->assoc->target = gfc_get_variable_expr (code->expr1->symtree);
7941       if (c->ts.type == BT_DERIVED)
7942         gfc_add_data_component (st->n.sym->assoc->target);
7943
7944       new_st = gfc_get_code ();
7945       new_st->op = EXEC_BLOCK;
7946       new_st->ext.block.ns = gfc_build_block_ns (ns);
7947       new_st->ext.block.ns->code = body->next;
7948       body->next = new_st;
7949
7950       /* Chain in the new list only if it is marked as dangling.  Otherwise
7951          there is a CASE label overlap and this is already used.  Just ignore,
7952          the error is diagonsed elsewhere.  */
7953       if (st->n.sym->assoc->dangling)
7954         {
7955           new_st->ext.block.assoc = st->n.sym->assoc;
7956           st->n.sym->assoc->dangling = 0;
7957         }
7958
7959       resolve_assoc_var (st->n.sym, false);
7960     }
7961     
7962   /* Take out CLASS IS cases for separate treatment.  */
7963   body = code;
7964   while (body && body->block)
7965     {
7966       if (body->block->ext.block.case_list->ts.type == BT_CLASS)
7967         {
7968           /* Add to class_is list.  */
7969           if (class_is == NULL)
7970             { 
7971               class_is = body->block;
7972               tail = class_is;
7973             }
7974           else
7975             {
7976               for (tail = class_is; tail->block; tail = tail->block) ;
7977               tail->block = body->block;
7978               tail = tail->block;
7979             }
7980           /* Remove from EXEC_SELECT list.  */
7981           body->block = body->block->block;
7982           tail->block = NULL;
7983         }
7984       else
7985         body = body->block;
7986     }
7987
7988   if (class_is)
7989     {
7990       gfc_symbol *vtab;
7991       
7992       if (!default_case)
7993         {
7994           /* Add a default case to hold the CLASS IS cases.  */
7995           for (tail = code; tail->block; tail = tail->block) ;
7996           tail->block = gfc_get_code ();
7997           tail = tail->block;
7998           tail->op = EXEC_SELECT_TYPE;
7999           tail->ext.block.case_list = gfc_get_case ();
8000           tail->ext.block.case_list->ts.type = BT_UNKNOWN;
8001           tail->next = NULL;
8002           default_case = tail;
8003         }
8004
8005       /* More than one CLASS IS block?  */
8006       if (class_is->block)
8007         {
8008           gfc_code **c1,*c2;
8009           bool swapped;
8010           /* Sort CLASS IS blocks by extension level.  */
8011           do
8012             {
8013               swapped = false;
8014               for (c1 = &class_is; (*c1) && (*c1)->block; c1 = &((*c1)->block))
8015                 {
8016                   c2 = (*c1)->block;
8017                   /* F03:C817 (check for doubles).  */
8018                   if ((*c1)->ext.block.case_list->ts.u.derived->hash_value
8019                       == c2->ext.block.case_list->ts.u.derived->hash_value)
8020                     {
8021                       gfc_error ("Double CLASS IS block in SELECT TYPE "
8022                                  "statement at %L",
8023                                  &c2->ext.block.case_list->where);
8024                       return;
8025                     }
8026                   if ((*c1)->ext.block.case_list->ts.u.derived->attr.extension
8027                       < c2->ext.block.case_list->ts.u.derived->attr.extension)
8028                     {
8029                       /* Swap.  */
8030                       (*c1)->block = c2->block;
8031                       c2->block = *c1;
8032                       *c1 = c2;
8033                       swapped = true;
8034                     }
8035                 }
8036             }
8037           while (swapped);
8038         }
8039         
8040       /* Generate IF chain.  */
8041       if_st = gfc_get_code ();
8042       if_st->op = EXEC_IF;
8043       new_st = if_st;
8044       for (body = class_is; body; body = body->block)
8045         {
8046           new_st->block = gfc_get_code ();
8047           new_st = new_st->block;
8048           new_st->op = EXEC_IF;
8049           /* Set up IF condition: Call _gfortran_is_extension_of.  */
8050           new_st->expr1 = gfc_get_expr ();
8051           new_st->expr1->expr_type = EXPR_FUNCTION;
8052           new_st->expr1->ts.type = BT_LOGICAL;
8053           new_st->expr1->ts.kind = 4;
8054           new_st->expr1->value.function.name = gfc_get_string (PREFIX ("is_extension_of"));
8055           new_st->expr1->value.function.isym = XCNEW (gfc_intrinsic_sym);
8056           new_st->expr1->value.function.isym->id = GFC_ISYM_EXTENDS_TYPE_OF;
8057           /* Set up arguments.  */
8058           new_st->expr1->value.function.actual = gfc_get_actual_arglist ();
8059           new_st->expr1->value.function.actual->expr = gfc_get_variable_expr (code->expr1->symtree);
8060           new_st->expr1->value.function.actual->expr->where = code->loc;
8061           gfc_add_vptr_component (new_st->expr1->value.function.actual->expr);
8062           vtab = gfc_find_derived_vtab (body->ext.block.case_list->ts.u.derived);
8063           st = gfc_find_symtree (vtab->ns->sym_root, vtab->name);
8064           new_st->expr1->value.function.actual->next = gfc_get_actual_arglist ();
8065           new_st->expr1->value.function.actual->next->expr = gfc_get_variable_expr (st);
8066           new_st->next = body->next;
8067         }
8068         if (default_case->next)
8069           {
8070             new_st->block = gfc_get_code ();
8071             new_st = new_st->block;
8072             new_st->op = EXEC_IF;
8073             new_st->next = default_case->next;
8074           }
8075           
8076         /* Replace CLASS DEFAULT code by the IF chain.  */
8077         default_case->next = if_st;
8078     }
8079
8080   /* Resolve the internal code.  This can not be done earlier because
8081      it requires that the sym->assoc of selectors is set already.  */
8082   gfc_current_ns = ns;
8083   gfc_resolve_blocks (code->block, gfc_current_ns);
8084   gfc_current_ns = old_ns;
8085
8086   resolve_select (code);
8087 }
8088
8089
8090 /* Resolve a transfer statement. This is making sure that:
8091    -- a derived type being transferred has only non-pointer components
8092    -- a derived type being transferred doesn't have private components, unless 
8093       it's being transferred from the module where the type was defined
8094    -- we're not trying to transfer a whole assumed size array.  */
8095
8096 static void
8097 resolve_transfer (gfc_code *code)
8098 {
8099   gfc_typespec *ts;
8100   gfc_symbol *sym;
8101   gfc_ref *ref;
8102   gfc_expr *exp;
8103
8104   exp = code->expr1;
8105
8106   while (exp != NULL && exp->expr_type == EXPR_OP
8107          && exp->value.op.op == INTRINSIC_PARENTHESES)
8108     exp = exp->value.op.op1;
8109
8110   if (exp == NULL || (exp->expr_type != EXPR_VARIABLE
8111                       && exp->expr_type != EXPR_FUNCTION))
8112     return;
8113
8114   /* If we are reading, the variable will be changed.  Note that
8115      code->ext.dt may be NULL if the TRANSFER is related to
8116      an INQUIRE statement -- but in this case, we are not reading, either.  */
8117   if (code->ext.dt && code->ext.dt->dt_io_kind->value.iokind == M_READ
8118       && gfc_check_vardef_context (exp, false, false, _("item in READ"))
8119          == FAILURE)
8120     return;
8121
8122   sym = exp->symtree->n.sym;
8123   ts = &sym->ts;
8124
8125   /* Go to actual component transferred.  */
8126   for (ref = exp->ref; ref; ref = ref->next)
8127     if (ref->type == REF_COMPONENT)
8128       ts = &ref->u.c.component->ts;
8129
8130   if (ts->type == BT_CLASS)
8131     {
8132       /* FIXME: Test for defined input/output.  */
8133       gfc_error ("Data transfer element at %L cannot be polymorphic unless "
8134                 "it is processed by a defined input/output procedure",
8135                 &code->loc);
8136       return;
8137     }
8138
8139   if (ts->type == BT_DERIVED)
8140     {
8141       /* Check that transferred derived type doesn't contain POINTER
8142          components.  */
8143       if (ts->u.derived->attr.pointer_comp)
8144         {
8145           gfc_error ("Data transfer element at %L cannot have POINTER "
8146                      "components unless it is processed by a defined "
8147                      "input/output procedure", &code->loc);
8148           return;
8149         }
8150
8151       /* F08:C935.  */
8152       if (ts->u.derived->attr.proc_pointer_comp)
8153         {
8154           gfc_error ("Data transfer element at %L cannot have "
8155                      "procedure pointer components", &code->loc);
8156           return;
8157         }
8158
8159       if (ts->u.derived->attr.alloc_comp)
8160         {
8161           gfc_error ("Data transfer element at %L cannot have ALLOCATABLE "
8162                      "components unless it is processed by a defined "
8163                      "input/output procedure", &code->loc);
8164           return;
8165         }
8166
8167       if (derived_inaccessible (ts->u.derived))
8168         {
8169           gfc_error ("Data transfer element at %L cannot have "
8170                      "PRIVATE components",&code->loc);
8171           return;
8172         }
8173     }
8174
8175   if (sym->as != NULL && sym->as->type == AS_ASSUMED_SIZE
8176       && exp->ref->type == REF_ARRAY && exp->ref->u.ar.type == AR_FULL)
8177     {
8178       gfc_error ("Data transfer element at %L cannot be a full reference to "
8179                  "an assumed-size array", &code->loc);
8180       return;
8181     }
8182 }
8183
8184
8185 /*********** Toplevel code resolution subroutines ***********/
8186
8187 /* Find the set of labels that are reachable from this block.  We also
8188    record the last statement in each block.  */
8189      
8190 static void
8191 find_reachable_labels (gfc_code *block)
8192 {
8193   gfc_code *c;
8194
8195   if (!block)
8196     return;
8197
8198   cs_base->reachable_labels = bitmap_obstack_alloc (&labels_obstack);
8199
8200   /* Collect labels in this block.  We don't keep those corresponding
8201      to END {IF|SELECT}, these are checked in resolve_branch by going
8202      up through the code_stack.  */
8203   for (c = block; c; c = c->next)
8204     {
8205       if (c->here && c->op != EXEC_END_BLOCK)
8206         bitmap_set_bit (cs_base->reachable_labels, c->here->value);
8207     }
8208
8209   /* Merge with labels from parent block.  */
8210   if (cs_base->prev)
8211     {
8212       gcc_assert (cs_base->prev->reachable_labels);
8213       bitmap_ior_into (cs_base->reachable_labels,
8214                        cs_base->prev->reachable_labels);
8215     }
8216 }
8217
8218
8219 static void
8220 resolve_lock_unlock (gfc_code *code)
8221 {
8222   if (code->expr1->ts.type != BT_DERIVED
8223       || code->expr1->expr_type != EXPR_VARIABLE
8224       || code->expr1->ts.u.derived->from_intmod != INTMOD_ISO_FORTRAN_ENV
8225       || code->expr1->ts.u.derived->intmod_sym_id != ISOFORTRAN_LOCK_TYPE
8226       || code->expr1->rank != 0
8227       || !(gfc_expr_attr (code->expr1).codimension
8228            || gfc_is_coindexed (code->expr1)))
8229     gfc_error ("Lock variable at %L must be a scalar coarray of type "
8230                "LOCK_TYPE", &code->expr1->where);
8231
8232   /* Check STAT.  */
8233   if (code->expr2
8234       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8235           || code->expr2->expr_type != EXPR_VARIABLE))
8236     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8237                &code->expr2->where);
8238
8239   if (code->expr2
8240       && gfc_check_vardef_context (code->expr2, false, false,
8241                                    _("STAT variable")) == FAILURE)
8242     return;
8243
8244   /* Check ERRMSG.  */
8245   if (code->expr3
8246       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8247           || code->expr3->expr_type != EXPR_VARIABLE))
8248     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8249                &code->expr3->where);
8250
8251   if (code->expr3
8252       && gfc_check_vardef_context (code->expr3, false, false,
8253                                    _("ERRMSG variable")) == FAILURE)
8254     return;
8255
8256   /* Check ACQUIRED_LOCK.  */
8257   if (code->expr4
8258       && (code->expr4->ts.type != BT_LOGICAL || code->expr4->rank != 0
8259           || code->expr4->expr_type != EXPR_VARIABLE))
8260     gfc_error ("ACQUIRED_LOCK= argument at %L must be a scalar LOGICAL "
8261                "variable", &code->expr4->where);
8262
8263   if (code->expr4
8264       && gfc_check_vardef_context (code->expr4, false, false,
8265                                    _("ACQUIRED_LOCK variable")) == FAILURE)
8266     return;
8267 }
8268
8269
8270 static void
8271 resolve_sync (gfc_code *code)
8272 {
8273   /* Check imageset. The * case matches expr1 == NULL.  */
8274   if (code->expr1)
8275     {
8276       if (code->expr1->ts.type != BT_INTEGER || code->expr1->rank > 1)
8277         gfc_error ("Imageset argument at %L must be a scalar or rank-1 "
8278                    "INTEGER expression", &code->expr1->where);
8279       if (code->expr1->expr_type == EXPR_CONSTANT && code->expr1->rank == 0
8280           && mpz_cmp_si (code->expr1->value.integer, 1) < 0)
8281         gfc_error ("Imageset argument at %L must between 1 and num_images()",
8282                    &code->expr1->where);
8283       else if (code->expr1->expr_type == EXPR_ARRAY
8284                && gfc_simplify_expr (code->expr1, 0) == SUCCESS)
8285         {
8286            gfc_constructor *cons;
8287            cons = gfc_constructor_first (code->expr1->value.constructor);
8288            for (; cons; cons = gfc_constructor_next (cons))
8289              if (cons->expr->expr_type == EXPR_CONSTANT
8290                  &&  mpz_cmp_si (cons->expr->value.integer, 1) < 0)
8291                gfc_error ("Imageset argument at %L must between 1 and "
8292                           "num_images()", &cons->expr->where);
8293         }
8294     }
8295
8296   /* Check STAT.  */
8297   if (code->expr2
8298       && (code->expr2->ts.type != BT_INTEGER || code->expr2->rank != 0
8299           || code->expr2->expr_type != EXPR_VARIABLE))
8300     gfc_error ("STAT= argument at %L must be a scalar INTEGER variable",
8301                &code->expr2->where);
8302
8303   /* Check ERRMSG.  */
8304   if (code->expr3
8305       && (code->expr3->ts.type != BT_CHARACTER || code->expr3->rank != 0
8306           || code->expr3->expr_type != EXPR_VARIABLE))
8307     gfc_error ("ERRMSG= argument at %L must be a scalar CHARACTER variable",
8308                &code->expr3->where);
8309 }
8310
8311
8312 /* Given a branch to a label, see if the branch is conforming.
8313    The code node describes where the branch is located.  */
8314
8315 static void
8316 resolve_branch (gfc_st_label *label, gfc_code *code)
8317 {
8318   code_stack *stack;
8319
8320   if (label == NULL)
8321     return;
8322
8323   /* Step one: is this a valid branching target?  */
8324
8325   if (label->defined == ST_LABEL_UNKNOWN)
8326     {
8327       gfc_error ("Label %d referenced at %L is never defined", label->value,
8328                  &label->where);
8329       return;
8330     }
8331
8332   if (label->defined != ST_LABEL_TARGET)
8333     {
8334       gfc_error ("Statement at %L is not a valid branch target statement "
8335                  "for the branch statement at %L", &label->where, &code->loc);
8336       return;
8337     }
8338
8339   /* Step two: make sure this branch is not a branch to itself ;-)  */
8340
8341   if (code->here == label)
8342     {
8343       gfc_warning ("Branch at %L may result in an infinite loop", &code->loc);
8344       return;
8345     }
8346
8347   /* Step three:  See if the label is in the same block as the
8348      branching statement.  The hard work has been done by setting up
8349      the bitmap reachable_labels.  */
8350
8351   if (bitmap_bit_p (cs_base->reachable_labels, label->value))
8352     {
8353       /* Check now whether there is a CRITICAL construct; if so, check
8354          whether the label is still visible outside of the CRITICAL block,
8355          which is invalid.  */
8356       for (stack = cs_base; stack; stack = stack->prev)
8357         if (stack->current->op == EXEC_CRITICAL
8358             && bitmap_bit_p (stack->reachable_labels, label->value))
8359           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8360                       " at %L", &code->loc, &label->where);
8361
8362       return;
8363     }
8364
8365   /* Step four:  If we haven't found the label in the bitmap, it may
8366     still be the label of the END of the enclosing block, in which
8367     case we find it by going up the code_stack.  */
8368
8369   for (stack = cs_base; stack; stack = stack->prev)
8370     {
8371       if (stack->current->next && stack->current->next->here == label)
8372         break;
8373       if (stack->current->op == EXEC_CRITICAL)
8374         {
8375           /* Note: A label at END CRITICAL does not leave the CRITICAL
8376              construct as END CRITICAL is still part of it.  */
8377           gfc_error ("GOTO statement at %L leaves CRITICAL construct for label"
8378                       " at %L", &code->loc, &label->where);
8379           return;
8380         }
8381     }
8382
8383   if (stack)
8384     {
8385       gcc_assert (stack->current->next->op == EXEC_END_BLOCK);
8386       return;
8387     }
8388
8389   /* The label is not in an enclosing block, so illegal.  This was
8390      allowed in Fortran 66, so we allow it as extension.  No
8391      further checks are necessary in this case.  */
8392   gfc_notify_std (GFC_STD_LEGACY, "Label at %L is not in the same block "
8393                   "as the GOTO statement at %L", &label->where,
8394                   &code->loc);
8395   return;
8396 }
8397
8398
8399 /* Check whether EXPR1 has the same shape as EXPR2.  */
8400
8401 static gfc_try
8402 resolve_where_shape (gfc_expr *expr1, gfc_expr *expr2)
8403 {
8404   mpz_t shape[GFC_MAX_DIMENSIONS];
8405   mpz_t shape2[GFC_MAX_DIMENSIONS];
8406   gfc_try result = FAILURE;
8407   int i;
8408
8409   /* Compare the rank.  */
8410   if (expr1->rank != expr2->rank)
8411     return result;
8412
8413   /* Compare the size of each dimension.  */
8414   for (i=0; i<expr1->rank; i++)
8415     {
8416       if (gfc_array_dimen_size (expr1, i, &shape[i]) == FAILURE)
8417         goto ignore;
8418
8419       if (gfc_array_dimen_size (expr2, i, &shape2[i]) == FAILURE)
8420         goto ignore;
8421
8422       if (mpz_cmp (shape[i], shape2[i]))
8423         goto over;
8424     }
8425
8426   /* When either of the two expression is an assumed size array, we
8427      ignore the comparison of dimension sizes.  */
8428 ignore:
8429   result = SUCCESS;
8430
8431 over:
8432   for (i--; i >= 0; i--)
8433     {
8434       mpz_clear (shape[i]);
8435       mpz_clear (shape2[i]);
8436     }
8437   return result;
8438 }
8439
8440
8441 /* Check whether a WHERE assignment target or a WHERE mask expression
8442    has the same shape as the outmost WHERE mask expression.  */
8443
8444 static void
8445 resolve_where (gfc_code *code, gfc_expr *mask)
8446 {
8447   gfc_code *cblock;
8448   gfc_code *cnext;
8449   gfc_expr *e = NULL;
8450
8451   cblock = code->block;
8452
8453   /* Store the first WHERE mask-expr of the WHERE statement or construct.
8454      In case of nested WHERE, only the outmost one is stored.  */
8455   if (mask == NULL) /* outmost WHERE */
8456     e = cblock->expr1;
8457   else /* inner WHERE */
8458     e = mask;
8459
8460   while (cblock)
8461     {
8462       if (cblock->expr1)
8463         {
8464           /* Check if the mask-expr has a consistent shape with the
8465              outmost WHERE mask-expr.  */
8466           if (resolve_where_shape (cblock->expr1, e) == FAILURE)
8467             gfc_error ("WHERE mask at %L has inconsistent shape",
8468                        &cblock->expr1->where);
8469          }
8470
8471       /* the assignment statement of a WHERE statement, or the first
8472          statement in where-body-construct of a WHERE construct */
8473       cnext = cblock->next;
8474       while (cnext)
8475         {
8476           switch (cnext->op)
8477             {
8478             /* WHERE assignment statement */
8479             case EXEC_ASSIGN:
8480
8481               /* Check shape consistent for WHERE assignment target.  */
8482               if (e && resolve_where_shape (cnext->expr1, e) == FAILURE)
8483                gfc_error ("WHERE assignment target at %L has "
8484                           "inconsistent shape", &cnext->expr1->where);
8485               break;
8486
8487   
8488             case EXEC_ASSIGN_CALL:
8489               resolve_call (cnext);
8490               if (!cnext->resolved_sym->attr.elemental)
8491                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8492                           &cnext->ext.actual->expr->where);
8493               break;
8494
8495             /* WHERE or WHERE construct is part of a where-body-construct */
8496             case EXEC_WHERE:
8497               resolve_where (cnext, e);
8498               break;
8499
8500             default:
8501               gfc_error ("Unsupported statement inside WHERE at %L",
8502                          &cnext->loc);
8503             }
8504          /* the next statement within the same where-body-construct */
8505          cnext = cnext->next;
8506        }
8507     /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8508     cblock = cblock->block;
8509   }
8510 }
8511
8512
8513 /* Resolve assignment in FORALL construct.
8514    NVAR is the number of FORALL index variables, and VAR_EXPR records the
8515    FORALL index variables.  */
8516
8517 static void
8518 gfc_resolve_assign_in_forall (gfc_code *code, int nvar, gfc_expr **var_expr)
8519 {
8520   int n;
8521
8522   for (n = 0; n < nvar; n++)
8523     {
8524       gfc_symbol *forall_index;
8525
8526       forall_index = var_expr[n]->symtree->n.sym;
8527
8528       /* Check whether the assignment target is one of the FORALL index
8529          variable.  */
8530       if ((code->expr1->expr_type == EXPR_VARIABLE)
8531           && (code->expr1->symtree->n.sym == forall_index))
8532         gfc_error ("Assignment to a FORALL index variable at %L",
8533                    &code->expr1->where);
8534       else
8535         {
8536           /* If one of the FORALL index variables doesn't appear in the
8537              assignment variable, then there could be a many-to-one
8538              assignment.  Emit a warning rather than an error because the
8539              mask could be resolving this problem.  */
8540           if (find_forall_index (code->expr1, forall_index, 0) == FAILURE)
8541             gfc_warning ("The FORALL with index '%s' is not used on the "
8542                          "left side of the assignment at %L and so might "
8543                          "cause multiple assignment to this object",
8544                          var_expr[n]->symtree->name, &code->expr1->where);
8545         }
8546     }
8547 }
8548
8549
8550 /* Resolve WHERE statement in FORALL construct.  */
8551
8552 static void
8553 gfc_resolve_where_code_in_forall (gfc_code *code, int nvar,
8554                                   gfc_expr **var_expr)
8555 {
8556   gfc_code *cblock;
8557   gfc_code *cnext;
8558
8559   cblock = code->block;
8560   while (cblock)
8561     {
8562       /* the assignment statement of a WHERE statement, or the first
8563          statement in where-body-construct of a WHERE construct */
8564       cnext = cblock->next;
8565       while (cnext)
8566         {
8567           switch (cnext->op)
8568             {
8569             /* WHERE assignment statement */
8570             case EXEC_ASSIGN:
8571               gfc_resolve_assign_in_forall (cnext, nvar, var_expr);
8572               break;
8573   
8574             /* WHERE operator assignment statement */
8575             case EXEC_ASSIGN_CALL:
8576               resolve_call (cnext);
8577               if (!cnext->resolved_sym->attr.elemental)
8578                 gfc_error("Non-ELEMENTAL user-defined assignment in WHERE at %L",
8579                           &cnext->ext.actual->expr->where);
8580               break;
8581
8582             /* WHERE or WHERE construct is part of a where-body-construct */
8583             case EXEC_WHERE:
8584               gfc_resolve_where_code_in_forall (cnext, nvar, var_expr);
8585               break;
8586
8587             default:
8588               gfc_error ("Unsupported statement inside WHERE at %L",
8589                          &cnext->loc);
8590             }
8591           /* the next statement within the same where-body-construct */
8592           cnext = cnext->next;
8593         }
8594       /* the next masked-elsewhere-stmt, elsewhere-stmt, or end-where-stmt */
8595       cblock = cblock->block;
8596     }
8597 }
8598
8599
8600 /* Traverse the FORALL body to check whether the following errors exist:
8601    1. For assignment, check if a many-to-one assignment happens.
8602    2. For WHERE statement, check the WHERE body to see if there is any
8603       many-to-one assignment.  */
8604
8605 static void
8606 gfc_resolve_forall_body (gfc_code *code, int nvar, gfc_expr **var_expr)
8607 {
8608   gfc_code *c;
8609
8610   c = code->block->next;
8611   while (c)
8612     {
8613       switch (c->op)
8614         {
8615         case EXEC_ASSIGN:
8616         case EXEC_POINTER_ASSIGN:
8617           gfc_resolve_assign_in_forall (c, nvar, var_expr);
8618           break;
8619
8620         case EXEC_ASSIGN_CALL:
8621           resolve_call (c);
8622           break;
8623
8624         /* Because the gfc_resolve_blocks() will handle the nested FORALL,
8625            there is no need to handle it here.  */
8626         case EXEC_FORALL:
8627           break;
8628         case EXEC_WHERE:
8629           gfc_resolve_where_code_in_forall(c, nvar, var_expr);
8630           break;
8631         default:
8632           break;
8633         }
8634       /* The next statement in the FORALL body.  */
8635       c = c->next;
8636     }
8637 }
8638
8639
8640 /* Counts the number of iterators needed inside a forall construct, including
8641    nested forall constructs. This is used to allocate the needed memory 
8642    in gfc_resolve_forall.  */
8643
8644 static int 
8645 gfc_count_forall_iterators (gfc_code *code)
8646 {
8647   int max_iters, sub_iters, current_iters;
8648   gfc_forall_iterator *fa;
8649
8650   gcc_assert(code->op == EXEC_FORALL);
8651   max_iters = 0;
8652   current_iters = 0;
8653
8654   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8655     current_iters ++;
8656   
8657   code = code->block->next;
8658
8659   while (code)
8660     {          
8661       if (code->op == EXEC_FORALL)
8662         {
8663           sub_iters = gfc_count_forall_iterators (code);
8664           if (sub_iters > max_iters)
8665             max_iters = sub_iters;
8666         }
8667       code = code->next;
8668     }
8669
8670   return current_iters + max_iters;
8671 }
8672
8673
8674 /* Given a FORALL construct, first resolve the FORALL iterator, then call
8675    gfc_resolve_forall_body to resolve the FORALL body.  */
8676
8677 static void
8678 gfc_resolve_forall (gfc_code *code, gfc_namespace *ns, int forall_save)
8679 {
8680   static gfc_expr **var_expr;
8681   static int total_var = 0;
8682   static int nvar = 0;
8683   int old_nvar, tmp;
8684   gfc_forall_iterator *fa;
8685   int i;
8686
8687   old_nvar = nvar;
8688
8689   /* Start to resolve a FORALL construct   */
8690   if (forall_save == 0)
8691     {
8692       /* Count the total number of FORALL index in the nested FORALL
8693          construct in order to allocate the VAR_EXPR with proper size.  */
8694       total_var = gfc_count_forall_iterators (code);
8695
8696       /* Allocate VAR_EXPR with NUMBER_OF_FORALL_INDEX elements.  */
8697       var_expr = XCNEWVEC (gfc_expr *, total_var);
8698     }
8699
8700   /* The information about FORALL iterator, including FORALL index start, end
8701      and stride. The FORALL index can not appear in start, end or stride.  */
8702   for (fa = code->ext.forall_iterator; fa; fa = fa->next)
8703     {
8704       /* Check if any outer FORALL index name is the same as the current
8705          one.  */
8706       for (i = 0; i < nvar; i++)
8707         {
8708           if (fa->var->symtree->n.sym == var_expr[i]->symtree->n.sym)
8709             {
8710               gfc_error ("An outer FORALL construct already has an index "
8711                          "with this name %L", &fa->var->where);
8712             }
8713         }
8714
8715       /* Record the current FORALL index.  */
8716       var_expr[nvar] = gfc_copy_expr (fa->var);
8717
8718       nvar++;
8719
8720       /* No memory leak.  */
8721       gcc_assert (nvar <= total_var);
8722     }
8723
8724   /* Resolve the FORALL body.  */
8725   gfc_resolve_forall_body (code, nvar, var_expr);
8726
8727   /* May call gfc_resolve_forall to resolve the inner FORALL loop.  */
8728   gfc_resolve_blocks (code->block, ns);
8729
8730   tmp = nvar;
8731   nvar = old_nvar;
8732   /* Free only the VAR_EXPRs allocated in this frame.  */
8733   for (i = nvar; i < tmp; i++)
8734      gfc_free_expr (var_expr[i]);
8735
8736   if (nvar == 0)
8737     {
8738       /* We are in the outermost FORALL construct.  */
8739       gcc_assert (forall_save == 0);
8740
8741       /* VAR_EXPR is not needed any more.  */
8742       free (var_expr);
8743       total_var = 0;
8744     }
8745 }
8746
8747
8748 /* Resolve a BLOCK construct statement.  */
8749
8750 static void
8751 resolve_block_construct (gfc_code* code)
8752 {
8753   /* Resolve the BLOCK's namespace.  */
8754   gfc_resolve (code->ext.block.ns);
8755
8756   /* For an ASSOCIATE block, the associations (and their targets) are already
8757      resolved during resolve_symbol.  */
8758 }
8759
8760
8761 /* Resolve lists of blocks found in IF, SELECT CASE, WHERE, FORALL, GOTO and
8762    DO code nodes.  */
8763
8764 static void resolve_code (gfc_code *, gfc_namespace *);
8765
8766 void
8767 gfc_resolve_blocks (gfc_code *b, gfc_namespace *ns)
8768 {
8769   gfc_try t;
8770
8771   for (; b; b = b->block)
8772     {
8773       t = gfc_resolve_expr (b->expr1);
8774       if (gfc_resolve_expr (b->expr2) == FAILURE)
8775         t = FAILURE;
8776
8777       switch (b->op)
8778         {
8779         case EXEC_IF:
8780           if (t == SUCCESS && b->expr1 != NULL
8781               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank != 0))
8782             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
8783                        &b->expr1->where);
8784           break;
8785
8786         case EXEC_WHERE:
8787           if (t == SUCCESS
8788               && b->expr1 != NULL
8789               && (b->expr1->ts.type != BT_LOGICAL || b->expr1->rank == 0))
8790             gfc_error ("WHERE/ELSEWHERE clause at %L requires a LOGICAL array",
8791                        &b->expr1->where);
8792           break;
8793
8794         case EXEC_GOTO:
8795           resolve_branch (b->label1, b);
8796           break;
8797
8798         case EXEC_BLOCK:
8799           resolve_block_construct (b);
8800           break;
8801
8802         case EXEC_SELECT:
8803         case EXEC_SELECT_TYPE:
8804         case EXEC_FORALL:
8805         case EXEC_DO:
8806         case EXEC_DO_WHILE:
8807         case EXEC_CRITICAL:
8808         case EXEC_READ:
8809         case EXEC_WRITE:
8810         case EXEC_IOLENGTH:
8811         case EXEC_WAIT:
8812           break;
8813
8814         case EXEC_OMP_ATOMIC:
8815         case EXEC_OMP_CRITICAL:
8816         case EXEC_OMP_DO:
8817         case EXEC_OMP_MASTER:
8818         case EXEC_OMP_ORDERED:
8819         case EXEC_OMP_PARALLEL:
8820         case EXEC_OMP_PARALLEL_DO:
8821         case EXEC_OMP_PARALLEL_SECTIONS:
8822         case EXEC_OMP_PARALLEL_WORKSHARE:
8823         case EXEC_OMP_SECTIONS:
8824         case EXEC_OMP_SINGLE:
8825         case EXEC_OMP_TASK:
8826         case EXEC_OMP_TASKWAIT:
8827         case EXEC_OMP_TASKYIELD:
8828         case EXEC_OMP_WORKSHARE:
8829           break;
8830
8831         default:
8832           gfc_internal_error ("gfc_resolve_blocks(): Bad block type");
8833         }
8834
8835       resolve_code (b->next, ns);
8836     }
8837 }
8838
8839
8840 /* Does everything to resolve an ordinary assignment.  Returns true
8841    if this is an interface assignment.  */
8842 static bool
8843 resolve_ordinary_assign (gfc_code *code, gfc_namespace *ns)
8844 {
8845   bool rval = false;
8846   gfc_expr *lhs;
8847   gfc_expr *rhs;
8848   int llen = 0;
8849   int rlen = 0;
8850   int n;
8851   gfc_ref *ref;
8852
8853   if (gfc_extend_assign (code, ns) == SUCCESS)
8854     {
8855       gfc_expr** rhsptr;
8856
8857       if (code->op == EXEC_ASSIGN_CALL)
8858         {
8859           lhs = code->ext.actual->expr;
8860           rhsptr = &code->ext.actual->next->expr;
8861         }
8862       else
8863         {
8864           gfc_actual_arglist* args;
8865           gfc_typebound_proc* tbp;
8866
8867           gcc_assert (code->op == EXEC_COMPCALL);
8868
8869           args = code->expr1->value.compcall.actual;
8870           lhs = args->expr;
8871           rhsptr = &args->next->expr;
8872
8873           tbp = code->expr1->value.compcall.tbp;
8874           gcc_assert (!tbp->is_generic);
8875         }
8876
8877       /* Make a temporary rhs when there is a default initializer
8878          and rhs is the same symbol as the lhs.  */
8879       if ((*rhsptr)->expr_type == EXPR_VARIABLE
8880             && (*rhsptr)->symtree->n.sym->ts.type == BT_DERIVED
8881             && gfc_has_default_initializer ((*rhsptr)->symtree->n.sym->ts.u.derived)
8882             && (lhs->symtree->n.sym == (*rhsptr)->symtree->n.sym))
8883         *rhsptr = gfc_get_parentheses (*rhsptr);
8884
8885       return true;
8886     }
8887
8888   lhs = code->expr1;
8889   rhs = code->expr2;
8890
8891   if (rhs->is_boz
8892       && gfc_notify_std (GFC_STD_GNU, "Extension: BOZ literal at %L outside "
8893                          "a DATA statement and outside INT/REAL/DBLE/CMPLX",
8894                          &code->loc) == FAILURE)
8895     return false;
8896
8897   /* Handle the case of a BOZ literal on the RHS.  */
8898   if (rhs->is_boz && lhs->ts.type != BT_INTEGER)
8899     {
8900       int rc;
8901       if (gfc_option.warn_surprising)
8902         gfc_warning ("BOZ literal at %L is bitwise transferred "
8903                      "non-integer symbol '%s'", &code->loc,
8904                      lhs->symtree->n.sym->name);
8905
8906       if (!gfc_convert_boz (rhs, &lhs->ts))
8907         return false;
8908       if ((rc = gfc_range_check (rhs)) != ARITH_OK)
8909         {
8910           if (rc == ARITH_UNDERFLOW)
8911             gfc_error ("Arithmetic underflow of bit-wise transferred BOZ at %L"
8912                        ". This check can be disabled with the option "
8913                        "-fno-range-check", &rhs->where);
8914           else if (rc == ARITH_OVERFLOW)
8915             gfc_error ("Arithmetic overflow of bit-wise transferred BOZ at %L"
8916                        ". This check can be disabled with the option "
8917                        "-fno-range-check", &rhs->where);
8918           else if (rc == ARITH_NAN)
8919             gfc_error ("Arithmetic NaN of bit-wise transferred BOZ at %L"
8920                        ". This check can be disabled with the option "
8921                        "-fno-range-check", &rhs->where);
8922           return false;
8923         }
8924     }
8925
8926   if (lhs->ts.type == BT_CHARACTER
8927         && gfc_option.warn_character_truncation)
8928     {
8929       if (lhs->ts.u.cl != NULL
8930             && lhs->ts.u.cl->length != NULL
8931             && lhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8932         llen = mpz_get_si (lhs->ts.u.cl->length->value.integer);
8933
8934       if (rhs->expr_type == EXPR_CONSTANT)
8935         rlen = rhs->value.character.length;
8936
8937       else if (rhs->ts.u.cl != NULL
8938                  && rhs->ts.u.cl->length != NULL
8939                  && rhs->ts.u.cl->length->expr_type == EXPR_CONSTANT)
8940         rlen = mpz_get_si (rhs->ts.u.cl->length->value.integer);
8941
8942       if (rlen && llen && rlen > llen)
8943         gfc_warning_now ("CHARACTER expression will be truncated "
8944                          "in assignment (%d/%d) at %L",
8945                          llen, rlen, &code->loc);
8946     }
8947
8948   /* Ensure that a vector index expression for the lvalue is evaluated
8949      to a temporary if the lvalue symbol is referenced in it.  */
8950   if (lhs->rank)
8951     {
8952       for (ref = lhs->ref; ref; ref= ref->next)
8953         if (ref->type == REF_ARRAY)
8954           {
8955             for (n = 0; n < ref->u.ar.dimen; n++)
8956               if (ref->u.ar.dimen_type[n] == DIMEN_VECTOR
8957                   && gfc_find_sym_in_expr (lhs->symtree->n.sym,
8958                                            ref->u.ar.start[n]))
8959                 ref->u.ar.start[n]
8960                         = gfc_get_parentheses (ref->u.ar.start[n]);
8961           }
8962     }
8963
8964   if (gfc_pure (NULL))
8965     {
8966       if (lhs->ts.type == BT_DERIVED
8967             && lhs->expr_type == EXPR_VARIABLE
8968             && lhs->ts.u.derived->attr.pointer_comp
8969             && rhs->expr_type == EXPR_VARIABLE
8970             && (gfc_impure_variable (rhs->symtree->n.sym)
8971                 || gfc_is_coindexed (rhs)))
8972         {
8973           /* F2008, C1283.  */
8974           if (gfc_is_coindexed (rhs))
8975             gfc_error ("Coindexed expression at %L is assigned to "
8976                         "a derived type variable with a POINTER "
8977                         "component in a PURE procedure",
8978                         &rhs->where);
8979           else
8980             gfc_error ("The impure variable at %L is assigned to "
8981                         "a derived type variable with a POINTER "
8982                         "component in a PURE procedure (12.6)",
8983                         &rhs->where);
8984           return rval;
8985         }
8986
8987       /* Fortran 2008, C1283.  */
8988       if (gfc_is_coindexed (lhs))
8989         {
8990           gfc_error ("Assignment to coindexed variable at %L in a PURE "
8991                      "procedure", &rhs->where);
8992           return rval;
8993         }
8994     }
8995
8996   if (gfc_implicit_pure (NULL))
8997     {
8998       if (lhs->expr_type == EXPR_VARIABLE
8999             && lhs->symtree->n.sym != gfc_current_ns->proc_name
9000             && lhs->symtree->n.sym->ns != gfc_current_ns)
9001         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9002
9003       if (lhs->ts.type == BT_DERIVED
9004             && lhs->expr_type == EXPR_VARIABLE
9005             && lhs->ts.u.derived->attr.pointer_comp
9006             && rhs->expr_type == EXPR_VARIABLE
9007             && (gfc_impure_variable (rhs->symtree->n.sym)
9008                 || gfc_is_coindexed (rhs)))
9009         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9010
9011       /* Fortran 2008, C1283.  */
9012       if (gfc_is_coindexed (lhs))
9013         gfc_current_ns->proc_name->attr.implicit_pure = 0;
9014     }
9015
9016   /* F03:7.4.1.2.  */
9017   /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
9018      and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
9019   if (lhs->ts.type == BT_CLASS)
9020     {
9021       gfc_error ("Variable must not be polymorphic in assignment at %L",
9022                  &lhs->where);
9023       return false;
9024     }
9025
9026   /* F2008, Section 7.2.1.2.  */
9027   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
9028     {
9029       gfc_error ("Coindexed variable must not be have an allocatable ultimate "
9030                  "component in assignment at %L", &lhs->where);
9031       return false;
9032     }
9033
9034   gfc_check_assign (lhs, rhs, 1);
9035   return false;
9036 }
9037
9038
9039 /* Given a block of code, recursively resolve everything pointed to by this
9040    code block.  */
9041
9042 static void
9043 resolve_code (gfc_code *code, gfc_namespace *ns)
9044 {
9045   int omp_workshare_save;
9046   int forall_save;
9047   code_stack frame;
9048   gfc_try t;
9049
9050   frame.prev = cs_base;
9051   frame.head = code;
9052   cs_base = &frame;
9053
9054   find_reachable_labels (code);
9055
9056   for (; code; code = code->next)
9057     {
9058       frame.current = code;
9059       forall_save = forall_flag;
9060
9061       if (code->op == EXEC_FORALL)
9062         {
9063           forall_flag = 1;
9064           gfc_resolve_forall (code, ns, forall_save);
9065           forall_flag = 2;
9066         }
9067       else if (code->block)
9068         {
9069           omp_workshare_save = -1;
9070           switch (code->op)
9071             {
9072             case EXEC_OMP_PARALLEL_WORKSHARE:
9073               omp_workshare_save = omp_workshare_flag;
9074               omp_workshare_flag = 1;
9075               gfc_resolve_omp_parallel_blocks (code, ns);
9076               break;
9077             case EXEC_OMP_PARALLEL:
9078             case EXEC_OMP_PARALLEL_DO:
9079             case EXEC_OMP_PARALLEL_SECTIONS:
9080             case EXEC_OMP_TASK:
9081               omp_workshare_save = omp_workshare_flag;
9082               omp_workshare_flag = 0;
9083               gfc_resolve_omp_parallel_blocks (code, ns);
9084               break;
9085             case EXEC_OMP_DO:
9086               gfc_resolve_omp_do_blocks (code, ns);
9087               break;
9088             case EXEC_SELECT_TYPE:
9089               /* Blocks are handled in resolve_select_type because we have
9090                  to transform the SELECT TYPE into ASSOCIATE first.  */
9091               break;
9092             case EXEC_OMP_WORKSHARE:
9093               omp_workshare_save = omp_workshare_flag;
9094               omp_workshare_flag = 1;
9095               /* FALLTHROUGH */
9096             default:
9097               gfc_resolve_blocks (code->block, ns);
9098               break;
9099             }
9100
9101           if (omp_workshare_save != -1)
9102             omp_workshare_flag = omp_workshare_save;
9103         }
9104
9105       t = SUCCESS;
9106       if (code->op != EXEC_COMPCALL && code->op != EXEC_CALL_PPC)
9107         t = gfc_resolve_expr (code->expr1);
9108       forall_flag = forall_save;
9109
9110       if (gfc_resolve_expr (code->expr2) == FAILURE)
9111         t = FAILURE;
9112
9113       if (code->op == EXEC_ALLOCATE
9114           && gfc_resolve_expr (code->expr3) == FAILURE)
9115         t = FAILURE;
9116
9117       switch (code->op)
9118         {
9119         case EXEC_NOP:
9120         case EXEC_END_BLOCK:
9121         case EXEC_CYCLE:
9122         case EXEC_PAUSE:
9123         case EXEC_STOP:
9124         case EXEC_ERROR_STOP:
9125         case EXEC_EXIT:
9126         case EXEC_CONTINUE:
9127         case EXEC_DT_END:
9128         case EXEC_ASSIGN_CALL:
9129         case EXEC_CRITICAL:
9130           break;
9131
9132         case EXEC_SYNC_ALL:
9133         case EXEC_SYNC_IMAGES:
9134         case EXEC_SYNC_MEMORY:
9135           resolve_sync (code);
9136           break;
9137
9138         case EXEC_LOCK:
9139         case EXEC_UNLOCK:
9140           resolve_lock_unlock (code);
9141           break;
9142
9143         case EXEC_ENTRY:
9144           /* Keep track of which entry we are up to.  */
9145           current_entry_id = code->ext.entry->id;
9146           break;
9147
9148         case EXEC_WHERE:
9149           resolve_where (code, NULL);
9150           break;
9151
9152         case EXEC_GOTO:
9153           if (code->expr1 != NULL)
9154             {
9155               if (code->expr1->ts.type != BT_INTEGER)
9156                 gfc_error ("ASSIGNED GOTO statement at %L requires an "
9157                            "INTEGER variable", &code->expr1->where);
9158               else if (code->expr1->symtree->n.sym->attr.assign != 1)
9159                 gfc_error ("Variable '%s' has not been assigned a target "
9160                            "label at %L", code->expr1->symtree->n.sym->name,
9161                            &code->expr1->where);
9162             }
9163           else
9164             resolve_branch (code->label1, code);
9165           break;
9166
9167         case EXEC_RETURN:
9168           if (code->expr1 != NULL
9169                 && (code->expr1->ts.type != BT_INTEGER || code->expr1->rank))
9170             gfc_error ("Alternate RETURN statement at %L requires a SCALAR-"
9171                        "INTEGER return specifier", &code->expr1->where);
9172           break;
9173
9174         case EXEC_INIT_ASSIGN:
9175         case EXEC_END_PROCEDURE:
9176           break;
9177
9178         case EXEC_ASSIGN:
9179           if (t == FAILURE)
9180             break;
9181
9182           if (gfc_check_vardef_context (code->expr1, false, false,
9183                                         _("assignment")) == FAILURE)
9184             break;
9185
9186           if (resolve_ordinary_assign (code, ns))
9187             {
9188               if (code->op == EXEC_COMPCALL)
9189                 goto compcall;
9190               else
9191                 goto call;
9192             }
9193           break;
9194
9195         case EXEC_LABEL_ASSIGN:
9196           if (code->label1->defined == ST_LABEL_UNKNOWN)
9197             gfc_error ("Label %d referenced at %L is never defined",
9198                        code->label1->value, &code->label1->where);
9199           if (t == SUCCESS
9200               && (code->expr1->expr_type != EXPR_VARIABLE
9201                   || code->expr1->symtree->n.sym->ts.type != BT_INTEGER
9202                   || code->expr1->symtree->n.sym->ts.kind
9203                      != gfc_default_integer_kind
9204                   || code->expr1->symtree->n.sym->as != NULL))
9205             gfc_error ("ASSIGN statement at %L requires a scalar "
9206                        "default INTEGER variable", &code->expr1->where);
9207           break;
9208
9209         case EXEC_POINTER_ASSIGN:
9210           {
9211             gfc_expr* e;
9212
9213             if (t == FAILURE)
9214               break;
9215
9216             /* This is both a variable definition and pointer assignment
9217                context, so check both of them.  For rank remapping, a final
9218                array ref may be present on the LHS and fool gfc_expr_attr
9219                used in gfc_check_vardef_context.  Remove it.  */
9220             e = remove_last_array_ref (code->expr1);
9221             t = gfc_check_vardef_context (e, true, false,
9222                                           _("pointer assignment"));
9223             if (t == SUCCESS)
9224               t = gfc_check_vardef_context (e, false, false,
9225                                             _("pointer assignment"));
9226             gfc_free_expr (e);
9227             if (t == FAILURE)
9228               break;
9229
9230             gfc_check_pointer_assign (code->expr1, code->expr2);
9231             break;
9232           }
9233
9234         case EXEC_ARITHMETIC_IF:
9235           if (t == SUCCESS
9236               && code->expr1->ts.type != BT_INTEGER
9237               && code->expr1->ts.type != BT_REAL)
9238             gfc_error ("Arithmetic IF statement at %L requires a numeric "
9239                        "expression", &code->expr1->where);
9240
9241           resolve_branch (code->label1, code);
9242           resolve_branch (code->label2, code);
9243           resolve_branch (code->label3, code);
9244           break;
9245
9246         case EXEC_IF:
9247           if (t == SUCCESS && code->expr1 != NULL
9248               && (code->expr1->ts.type != BT_LOGICAL
9249                   || code->expr1->rank != 0))
9250             gfc_error ("IF clause at %L requires a scalar LOGICAL expression",
9251                        &code->expr1->where);
9252           break;
9253
9254         case EXEC_CALL:
9255         call:
9256           resolve_call (code);
9257           break;
9258
9259         case EXEC_COMPCALL:
9260         compcall:
9261           resolve_typebound_subroutine (code);
9262           break;
9263
9264         case EXEC_CALL_PPC:
9265           resolve_ppc_call (code);
9266           break;
9267
9268         case EXEC_SELECT:
9269           /* Select is complicated. Also, a SELECT construct could be
9270              a transformed computed GOTO.  */
9271           resolve_select (code);
9272           break;
9273
9274         case EXEC_SELECT_TYPE:
9275           resolve_select_type (code, ns);
9276           break;
9277
9278         case EXEC_BLOCK:
9279           resolve_block_construct (code);
9280           break;
9281
9282         case EXEC_DO:
9283           if (code->ext.iterator != NULL)
9284             {
9285               gfc_iterator *iter = code->ext.iterator;
9286               if (gfc_resolve_iterator (iter, true) != FAILURE)
9287                 gfc_resolve_do_iterator (code, iter->var->symtree->n.sym);
9288             }
9289           break;
9290
9291         case EXEC_DO_WHILE:
9292           if (code->expr1 == NULL)
9293             gfc_internal_error ("resolve_code(): No expression on DO WHILE");
9294           if (t == SUCCESS
9295               && (code->expr1->rank != 0
9296                   || code->expr1->ts.type != BT_LOGICAL))
9297             gfc_error ("Exit condition of DO WHILE loop at %L must be "
9298                        "a scalar LOGICAL expression", &code->expr1->where);
9299           break;
9300
9301         case EXEC_ALLOCATE:
9302           if (t == SUCCESS)
9303             resolve_allocate_deallocate (code, "ALLOCATE");
9304
9305           break;
9306
9307         case EXEC_DEALLOCATE:
9308           if (t == SUCCESS)
9309             resolve_allocate_deallocate (code, "DEALLOCATE");
9310
9311           break;
9312
9313         case EXEC_OPEN:
9314           if (gfc_resolve_open (code->ext.open) == FAILURE)
9315             break;
9316
9317           resolve_branch (code->ext.open->err, code);
9318           break;
9319
9320         case EXEC_CLOSE:
9321           if (gfc_resolve_close (code->ext.close) == FAILURE)
9322             break;
9323
9324           resolve_branch (code->ext.close->err, code);
9325           break;
9326
9327         case EXEC_BACKSPACE:
9328         case EXEC_ENDFILE:
9329         case EXEC_REWIND:
9330         case EXEC_FLUSH:
9331           if (gfc_resolve_filepos (code->ext.filepos) == FAILURE)
9332             break;
9333
9334           resolve_branch (code->ext.filepos->err, code);
9335           break;
9336
9337         case EXEC_INQUIRE:
9338           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9339               break;
9340
9341           resolve_branch (code->ext.inquire->err, code);
9342           break;
9343
9344         case EXEC_IOLENGTH:
9345           gcc_assert (code->ext.inquire != NULL);
9346           if (gfc_resolve_inquire (code->ext.inquire) == FAILURE)
9347             break;
9348
9349           resolve_branch (code->ext.inquire->err, code);
9350           break;
9351
9352         case EXEC_WAIT:
9353           if (gfc_resolve_wait (code->ext.wait) == FAILURE)
9354             break;
9355
9356           resolve_branch (code->ext.wait->err, code);
9357           resolve_branch (code->ext.wait->end, code);
9358           resolve_branch (code->ext.wait->eor, code);
9359           break;
9360
9361         case EXEC_READ:
9362         case EXEC_WRITE:
9363           if (gfc_resolve_dt (code->ext.dt, &code->loc) == FAILURE)
9364             break;
9365
9366           resolve_branch (code->ext.dt->err, code);
9367           resolve_branch (code->ext.dt->end, code);
9368           resolve_branch (code->ext.dt->eor, code);
9369           break;
9370
9371         case EXEC_TRANSFER:
9372           resolve_transfer (code);
9373           break;
9374
9375         case EXEC_FORALL:
9376           resolve_forall_iterators (code->ext.forall_iterator);
9377
9378           if (code->expr1 != NULL
9379               && (code->expr1->ts.type != BT_LOGICAL || code->expr1->rank))
9380             gfc_error ("FORALL mask clause at %L requires a scalar LOGICAL "
9381                        "expression", &code->expr1->where);
9382           break;
9383
9384         case EXEC_OMP_ATOMIC:
9385         case EXEC_OMP_BARRIER:
9386         case EXEC_OMP_CRITICAL:
9387         case EXEC_OMP_FLUSH:
9388         case EXEC_OMP_DO:
9389         case EXEC_OMP_MASTER:
9390         case EXEC_OMP_ORDERED:
9391         case EXEC_OMP_SECTIONS:
9392         case EXEC_OMP_SINGLE:
9393         case EXEC_OMP_TASKWAIT:
9394         case EXEC_OMP_TASKYIELD:
9395         case EXEC_OMP_WORKSHARE:
9396           gfc_resolve_omp_directive (code, ns);
9397           break;
9398
9399         case EXEC_OMP_PARALLEL:
9400         case EXEC_OMP_PARALLEL_DO:
9401         case EXEC_OMP_PARALLEL_SECTIONS:
9402         case EXEC_OMP_PARALLEL_WORKSHARE:
9403         case EXEC_OMP_TASK:
9404           omp_workshare_save = omp_workshare_flag;
9405           omp_workshare_flag = 0;
9406           gfc_resolve_omp_directive (code, ns);
9407           omp_workshare_flag = omp_workshare_save;
9408           break;
9409
9410         default:
9411           gfc_internal_error ("resolve_code(): Bad statement code");
9412         }
9413     }
9414
9415   cs_base = frame.prev;
9416 }
9417
9418
9419 /* Resolve initial values and make sure they are compatible with
9420    the variable.  */
9421
9422 static void
9423 resolve_values (gfc_symbol *sym)
9424 {
9425   gfc_try t;
9426
9427   if (sym->value == NULL)
9428     return;
9429
9430   if (sym->value->expr_type == EXPR_STRUCTURE)
9431     t= resolve_structure_cons (sym->value, 1);
9432   else 
9433     t = gfc_resolve_expr (sym->value);
9434
9435   if (t == FAILURE)
9436     return;
9437
9438   gfc_check_assign_symbol (sym, sym->value);
9439 }
9440
9441
9442 /* Verify the binding labels for common blocks that are BIND(C).  The label
9443    for a BIND(C) common block must be identical in all scoping units in which
9444    the common block is declared.  Further, the binding label can not collide
9445    with any other global entity in the program.  */
9446
9447 static void
9448 resolve_bind_c_comms (gfc_symtree *comm_block_tree)
9449 {
9450   if (comm_block_tree->n.common->is_bind_c == 1)
9451     {
9452       gfc_gsymbol *binding_label_gsym;
9453       gfc_gsymbol *comm_name_gsym;
9454
9455       /* See if a global symbol exists by the common block's name.  It may
9456          be NULL if the common block is use-associated.  */
9457       comm_name_gsym = gfc_find_gsymbol (gfc_gsym_root,
9458                                          comm_block_tree->n.common->name);
9459       if (comm_name_gsym != NULL && comm_name_gsym->type != GSYM_COMMON)
9460         gfc_error ("Binding label '%s' for common block '%s' at %L collides "
9461                    "with the global entity '%s' at %L",
9462                    comm_block_tree->n.common->binding_label,
9463                    comm_block_tree->n.common->name,
9464                    &(comm_block_tree->n.common->where),
9465                    comm_name_gsym->name, &(comm_name_gsym->where));
9466       else if (comm_name_gsym != NULL
9467                && strcmp (comm_name_gsym->name,
9468                           comm_block_tree->n.common->name) == 0)
9469         {
9470           /* TODO: Need to make sure the fields of gfc_gsymbol are initialized
9471              as expected.  */
9472           if (comm_name_gsym->binding_label == NULL)
9473             /* No binding label for common block stored yet; save this one.  */
9474             comm_name_gsym->binding_label =
9475               comm_block_tree->n.common->binding_label;
9476           else
9477             if (strcmp (comm_name_gsym->binding_label,
9478                         comm_block_tree->n.common->binding_label) != 0)
9479               {
9480                 /* Common block names match but binding labels do not.  */
9481                 gfc_error ("Binding label '%s' for common block '%s' at %L "
9482                            "does not match the binding label '%s' for common "
9483                            "block '%s' at %L",
9484                            comm_block_tree->n.common->binding_label,
9485                            comm_block_tree->n.common->name,
9486                            &(comm_block_tree->n.common->where),
9487                            comm_name_gsym->binding_label,
9488                            comm_name_gsym->name,
9489                            &(comm_name_gsym->where));
9490                 return;
9491               }
9492         }
9493
9494       /* There is no binding label (NAME="") so we have nothing further to
9495          check and nothing to add as a global symbol for the label.  */
9496       if (comm_block_tree->n.common->binding_label[0] == '\0' )
9497         return;
9498       
9499       binding_label_gsym =
9500         gfc_find_gsymbol (gfc_gsym_root,
9501                           comm_block_tree->n.common->binding_label);
9502       if (binding_label_gsym == NULL)
9503         {
9504           /* Need to make a global symbol for the binding label to prevent
9505              it from colliding with another.  */
9506           binding_label_gsym =
9507             gfc_get_gsymbol (comm_block_tree->n.common->binding_label);
9508           binding_label_gsym->sym_name = comm_block_tree->n.common->name;
9509           binding_label_gsym->type = GSYM_COMMON;
9510         }
9511       else
9512         {
9513           /* If comm_name_gsym is NULL, the name common block is use
9514              associated and the name could be colliding.  */
9515           if (binding_label_gsym->type != GSYM_COMMON)
9516             gfc_error ("Binding label '%s' for common block '%s' at %L "
9517                        "collides with the global entity '%s' at %L",
9518                        comm_block_tree->n.common->binding_label,
9519                        comm_block_tree->n.common->name,
9520                        &(comm_block_tree->n.common->where),
9521                        binding_label_gsym->name,
9522                        &(binding_label_gsym->where));
9523           else if (comm_name_gsym != NULL
9524                    && (strcmp (binding_label_gsym->name,
9525                                comm_name_gsym->binding_label) != 0)
9526                    && (strcmp (binding_label_gsym->sym_name,
9527                                comm_name_gsym->name) != 0))
9528             gfc_error ("Binding label '%s' for common block '%s' at %L "
9529                        "collides with global entity '%s' at %L",
9530                        binding_label_gsym->name, binding_label_gsym->sym_name,
9531                        &(comm_block_tree->n.common->where),
9532                        comm_name_gsym->name, &(comm_name_gsym->where));
9533         }
9534     }
9535   
9536   return;
9537 }
9538
9539
9540 /* Verify any BIND(C) derived types in the namespace so we can report errors
9541    for them once, rather than for each variable declared of that type.  */
9542
9543 static void
9544 resolve_bind_c_derived_types (gfc_symbol *derived_sym)
9545 {
9546   if (derived_sym != NULL && derived_sym->attr.flavor == FL_DERIVED
9547       && derived_sym->attr.is_bind_c == 1)
9548     verify_bind_c_derived_type (derived_sym);
9549   
9550   return;
9551 }
9552
9553
9554 /* Verify that any binding labels used in a given namespace do not collide 
9555    with the names or binding labels of any global symbols.  */
9556
9557 static void
9558 gfc_verify_binding_labels (gfc_symbol *sym)
9559 {
9560   int has_error = 0;
9561   
9562   if (sym != NULL && sym->attr.is_bind_c && sym->attr.is_iso_c == 0 
9563       && sym->attr.flavor != FL_DERIVED && sym->binding_label[0] != '\0')
9564     {
9565       gfc_gsymbol *bind_c_sym;
9566
9567       bind_c_sym = gfc_find_gsymbol (gfc_gsym_root, sym->binding_label);
9568       if (bind_c_sym != NULL 
9569           && strcmp (bind_c_sym->name, sym->binding_label) == 0)
9570         {
9571           if (sym->attr.if_source == IFSRC_DECL 
9572               && (bind_c_sym->type != GSYM_SUBROUTINE 
9573                   && bind_c_sym->type != GSYM_FUNCTION) 
9574               && ((sym->attr.contained == 1 
9575                    && strcmp (bind_c_sym->sym_name, sym->name) != 0) 
9576                   || (sym->attr.use_assoc == 1 
9577                       && (strcmp (bind_c_sym->mod_name, sym->module) != 0))))
9578             {
9579               /* Make sure global procedures don't collide with anything.  */
9580               gfc_error ("Binding label '%s' at %L collides with the global "
9581                          "entity '%s' at %L", sym->binding_label,
9582                          &(sym->declared_at), bind_c_sym->name,
9583                          &(bind_c_sym->where));
9584               has_error = 1;
9585             }
9586           else if (sym->attr.contained == 0 
9587                    && (sym->attr.if_source == IFSRC_IFBODY 
9588                        && sym->attr.flavor == FL_PROCEDURE) 
9589                    && (bind_c_sym->sym_name != NULL 
9590                        && strcmp (bind_c_sym->sym_name, sym->name) != 0))
9591             {
9592               /* Make sure procedures in interface bodies don't collide.  */
9593               gfc_error ("Binding label '%s' in interface body at %L collides "
9594                          "with the global entity '%s' at %L",
9595                          sym->binding_label,
9596                          &(sym->declared_at), bind_c_sym->name,
9597                          &(bind_c_sym->where));
9598               has_error = 1;
9599             }
9600           else if (sym->attr.contained == 0 
9601                    && sym->attr.if_source == IFSRC_UNKNOWN)
9602             if ((sym->attr.use_assoc && bind_c_sym->mod_name
9603                  && strcmp (bind_c_sym->mod_name, sym->module) != 0) 
9604                 || sym->attr.use_assoc == 0)
9605               {
9606                 gfc_error ("Binding label '%s' at %L collides with global "
9607                            "entity '%s' at %L", sym->binding_label,
9608                            &(sym->declared_at), bind_c_sym->name,
9609                            &(bind_c_sym->where));
9610                 has_error = 1;
9611               }
9612
9613           if (has_error != 0)
9614             /* Clear the binding label to prevent checking multiple times.  */
9615             sym->binding_label[0] = '\0';
9616         }
9617       else if (bind_c_sym == NULL)
9618         {
9619           bind_c_sym = gfc_get_gsymbol (sym->binding_label);
9620           bind_c_sym->where = sym->declared_at;
9621           bind_c_sym->sym_name = sym->name;
9622
9623           if (sym->attr.use_assoc == 1)
9624             bind_c_sym->mod_name = sym->module;
9625           else
9626             if (sym->ns->proc_name != NULL)
9627               bind_c_sym->mod_name = sym->ns->proc_name->name;
9628
9629           if (sym->attr.contained == 0)
9630             {
9631               if (sym->attr.subroutine)
9632                 bind_c_sym->type = GSYM_SUBROUTINE;
9633               else if (sym->attr.function)
9634                 bind_c_sym->type = GSYM_FUNCTION;
9635             }
9636         }
9637     }
9638   return;
9639 }
9640
9641
9642 /* Resolve an index expression.  */
9643
9644 static gfc_try
9645 resolve_index_expr (gfc_expr *e)
9646 {
9647   if (gfc_resolve_expr (e) == FAILURE)
9648     return FAILURE;
9649
9650   if (gfc_simplify_expr (e, 0) == FAILURE)
9651     return FAILURE;
9652
9653   if (gfc_specification_expr (e) == FAILURE)
9654     return FAILURE;
9655
9656   return SUCCESS;
9657 }
9658
9659
9660 /* Resolve a charlen structure.  */
9661
9662 static gfc_try
9663 resolve_charlen (gfc_charlen *cl)
9664 {
9665   int i, k;
9666
9667   if (cl->resolved)
9668     return SUCCESS;
9669
9670   cl->resolved = 1;
9671
9672   specification_expr = 1;
9673
9674   if (resolve_index_expr (cl->length) == FAILURE)
9675     {
9676       specification_expr = 0;
9677       return FAILURE;
9678     }
9679
9680   /* "If the character length parameter value evaluates to a negative
9681      value, the length of character entities declared is zero."  */
9682   if (cl->length && !gfc_extract_int (cl->length, &i) && i < 0)
9683     {
9684       if (gfc_option.warn_surprising)
9685         gfc_warning_now ("CHARACTER variable at %L has negative length %d,"
9686                          " the length has been set to zero",
9687                          &cl->length->where, i);
9688       gfc_replace_expr (cl->length,
9689                         gfc_get_int_expr (gfc_default_integer_kind, NULL, 0));
9690     }
9691
9692   /* Check that the character length is not too large.  */
9693   k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);
9694   if (cl->length && cl->length->expr_type == EXPR_CONSTANT
9695       && cl->length->ts.type == BT_INTEGER
9696       && mpz_cmp (cl->length->value.integer, gfc_integer_kinds[k].huge) > 0)
9697     {
9698       gfc_error ("String length at %L is too large", &cl->length->where);
9699       return FAILURE;
9700     }
9701
9702   return SUCCESS;
9703 }
9704
9705
9706 /* Test for non-constant shape arrays.  */
9707
9708 static bool
9709 is_non_constant_shape_array (gfc_symbol *sym)
9710 {
9711   gfc_expr *e;
9712   int i;
9713   bool not_constant;
9714
9715   not_constant = false;
9716   if (sym->as != NULL)
9717     {
9718       /* Unfortunately, !gfc_is_compile_time_shape hits a legal case that
9719          has not been simplified; parameter array references.  Do the
9720          simplification now.  */
9721       for (i = 0; i < sym->as->rank + sym->as->corank; i++)
9722         {
9723           e = sym->as->lower[i];
9724           if (e && (resolve_index_expr (e) == FAILURE
9725                     || !gfc_is_constant_expr (e)))
9726             not_constant = true;
9727           e = sym->as->upper[i];
9728           if (e && (resolve_index_expr (e) == FAILURE
9729                     || !gfc_is_constant_expr (e)))
9730             not_constant = true;
9731         }
9732     }
9733   return not_constant;
9734 }
9735
9736 /* Given a symbol and an initialization expression, add code to initialize
9737    the symbol to the function entry.  */
9738 static void
9739 build_init_assign (gfc_symbol *sym, gfc_expr *init)
9740 {
9741   gfc_expr *lval;
9742   gfc_code *init_st;
9743   gfc_namespace *ns = sym->ns;
9744
9745   /* Search for the function namespace if this is a contained
9746      function without an explicit result.  */
9747   if (sym->attr.function && sym == sym->result
9748       && sym->name != sym->ns->proc_name->name)
9749     {
9750       ns = ns->contained;
9751       for (;ns; ns = ns->sibling)
9752         if (strcmp (ns->proc_name->name, sym->name) == 0)
9753           break;
9754     }
9755
9756   if (ns == NULL)
9757     {
9758       gfc_free_expr (init);
9759       return;
9760     }
9761
9762   /* Build an l-value expression for the result.  */
9763   lval = gfc_lval_expr_from_sym (sym);
9764
9765   /* Add the code at scope entry.  */
9766   init_st = gfc_get_code ();
9767   init_st->next = ns->code;
9768   ns->code = init_st;
9769
9770   /* Assign the default initializer to the l-value.  */
9771   init_st->loc = sym->declared_at;
9772   init_st->op = EXEC_INIT_ASSIGN;
9773   init_st->expr1 = lval;
9774   init_st->expr2 = init;
9775 }
9776
9777 /* Assign the default initializer to a derived type variable or result.  */
9778
9779 static void
9780 apply_default_init (gfc_symbol *sym)
9781 {
9782   gfc_expr *init = NULL;
9783
9784   if (sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9785     return;
9786
9787   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived)
9788     init = gfc_default_initializer (&sym->ts);
9789
9790   if (init == NULL && sym->ts.type != BT_CLASS)
9791     return;
9792
9793   build_init_assign (sym, init);
9794   sym->attr.referenced = 1;
9795 }
9796
9797 /* Build an initializer for a local integer, real, complex, logical, or
9798    character variable, based on the command line flags finit-local-zero,
9799    finit-integer=, finit-real=, finit-logical=, and finit-runtime.  Returns 
9800    null if the symbol should not have a default initialization.  */
9801 static gfc_expr *
9802 build_default_init_expr (gfc_symbol *sym)
9803 {
9804   int char_len;
9805   gfc_expr *init_expr;
9806   int i;
9807
9808   /* These symbols should never have a default initialization.  */
9809   if ((sym->attr.dimension && !gfc_is_compile_time_shape (sym->as))
9810       || sym->attr.external
9811       || sym->attr.dummy
9812       || sym->attr.pointer
9813       || sym->attr.in_equivalence
9814       || sym->attr.in_common
9815       || sym->attr.data
9816       || sym->module
9817       || sym->attr.cray_pointee
9818       || sym->attr.cray_pointer)
9819     return NULL;
9820
9821   /* Now we'll try to build an initializer expression.  */
9822   init_expr = gfc_get_constant_expr (sym->ts.type, sym->ts.kind,
9823                                      &sym->declared_at);
9824
9825   /* We will only initialize integers, reals, complex, logicals, and
9826      characters, and only if the corresponding command-line flags
9827      were set.  Otherwise, we free init_expr and return null.  */
9828   switch (sym->ts.type)
9829     {    
9830     case BT_INTEGER:
9831       if (gfc_option.flag_init_integer != GFC_INIT_INTEGER_OFF)
9832         mpz_set_si (init_expr->value.integer, 
9833                          gfc_option.flag_init_integer_value);
9834       else
9835         {
9836           gfc_free_expr (init_expr);
9837           init_expr = NULL;
9838         }
9839       break;
9840
9841     case BT_REAL:
9842       switch (gfc_option.flag_init_real)
9843         {
9844         case GFC_INIT_REAL_SNAN:
9845           init_expr->is_snan = 1;
9846           /* Fall through.  */
9847         case GFC_INIT_REAL_NAN:
9848           mpfr_set_nan (init_expr->value.real);
9849           break;
9850
9851         case GFC_INIT_REAL_INF:
9852           mpfr_set_inf (init_expr->value.real, 1);
9853           break;
9854
9855         case GFC_INIT_REAL_NEG_INF:
9856           mpfr_set_inf (init_expr->value.real, -1);
9857           break;
9858
9859         case GFC_INIT_REAL_ZERO:
9860           mpfr_set_ui (init_expr->value.real, 0.0, GFC_RND_MODE);
9861           break;
9862
9863         default:
9864           gfc_free_expr (init_expr);
9865           init_expr = NULL;
9866           break;
9867         }
9868       break;
9869           
9870     case BT_COMPLEX:
9871       switch (gfc_option.flag_init_real)
9872         {
9873         case GFC_INIT_REAL_SNAN:
9874           init_expr->is_snan = 1;
9875           /* Fall through.  */
9876         case GFC_INIT_REAL_NAN:
9877           mpfr_set_nan (mpc_realref (init_expr->value.complex));
9878           mpfr_set_nan (mpc_imagref (init_expr->value.complex));
9879           break;
9880
9881         case GFC_INIT_REAL_INF:
9882           mpfr_set_inf (mpc_realref (init_expr->value.complex), 1);
9883           mpfr_set_inf (mpc_imagref (init_expr->value.complex), 1);
9884           break;
9885
9886         case GFC_INIT_REAL_NEG_INF:
9887           mpfr_set_inf (mpc_realref (init_expr->value.complex), -1);
9888           mpfr_set_inf (mpc_imagref (init_expr->value.complex), -1);
9889           break;
9890
9891         case GFC_INIT_REAL_ZERO:
9892           mpc_set_ui (init_expr->value.complex, 0, GFC_MPC_RND_MODE);
9893           break;
9894
9895         default:
9896           gfc_free_expr (init_expr);
9897           init_expr = NULL;
9898           break;
9899         }
9900       break;
9901           
9902     case BT_LOGICAL:
9903       if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_FALSE)
9904         init_expr->value.logical = 0;
9905       else if (gfc_option.flag_init_logical == GFC_INIT_LOGICAL_TRUE)
9906         init_expr->value.logical = 1;
9907       else
9908         {
9909           gfc_free_expr (init_expr);
9910           init_expr = NULL;
9911         }
9912       break;
9913           
9914     case BT_CHARACTER:
9915       /* For characters, the length must be constant in order to 
9916          create a default initializer.  */
9917       if (gfc_option.flag_init_character == GFC_INIT_CHARACTER_ON
9918           && sym->ts.u.cl->length
9919           && sym->ts.u.cl->length->expr_type == EXPR_CONSTANT)
9920         {
9921           char_len = mpz_get_si (sym->ts.u.cl->length->value.integer);
9922           init_expr->value.character.length = char_len;
9923           init_expr->value.character.string = gfc_get_wide_string (char_len+1);
9924           for (i = 0; i < char_len; i++)
9925             init_expr->value.character.string[i]
9926               = (unsigned char) gfc_option.flag_init_character_value;
9927         }
9928       else
9929         {
9930           gfc_free_expr (init_expr);
9931           init_expr = NULL;
9932         }
9933       break;
9934           
9935     default:
9936      gfc_free_expr (init_expr);
9937      init_expr = NULL;
9938     }
9939   return init_expr;
9940 }
9941
9942 /* Add an initialization expression to a local variable.  */
9943 static void
9944 apply_default_init_local (gfc_symbol *sym)
9945 {
9946   gfc_expr *init = NULL;
9947
9948   /* The symbol should be a variable or a function return value.  */
9949   if ((sym->attr.flavor != FL_VARIABLE && !sym->attr.function)
9950       || (sym->attr.function && sym->result != sym))
9951     return;
9952
9953   /* Try to build the initializer expression.  If we can't initialize
9954      this symbol, then init will be NULL.  */
9955   init = build_default_init_expr (sym);
9956   if (init == NULL)
9957     return;
9958
9959   /* For saved variables, we don't want to add an initializer at 
9960      function entry, so we just add a static initializer.  */
9961   if (sym->attr.save || sym->ns->save_all 
9962       || gfc_option.flag_max_stack_var_size == 0)
9963     {
9964       /* Don't clobber an existing initializer!  */
9965       gcc_assert (sym->value == NULL);
9966       sym->value = init;
9967       return;
9968     }
9969
9970   build_init_assign (sym, init);
9971 }
9972
9973
9974 /* Resolution of common features of flavors variable and procedure.  */
9975
9976 static gfc_try
9977 resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
9978 {
9979   /* Avoid double diagnostics for function result symbols.  */
9980   if ((sym->result || sym->attr.result) && !sym->attr.dummy
9981       && (sym->ns != gfc_current_ns))
9982     return SUCCESS;
9983
9984   /* Constraints on deferred shape variable.  */
9985   if (sym->as == NULL || sym->as->type != AS_DEFERRED)
9986     {
9987       if (sym->attr.allocatable)
9988         {
9989           if (sym->attr.dimension)
9990             {
9991               gfc_error ("Allocatable array '%s' at %L must have "
9992                          "a deferred shape", sym->name, &sym->declared_at);
9993               return FAILURE;
9994             }
9995           else if (gfc_notify_std (GFC_STD_F2003, "Scalar object '%s' at %L "
9996                                    "may not be ALLOCATABLE", sym->name,
9997                                    &sym->declared_at) == FAILURE)
9998             return FAILURE;
9999         }
10000
10001       if (sym->attr.pointer && sym->attr.dimension)
10002         {
10003           gfc_error ("Array pointer '%s' at %L must have a deferred shape",
10004                      sym->name, &sym->declared_at);
10005           return FAILURE;
10006         }
10007     }
10008   else
10009     {
10010       if (!mp_flag && !sym->attr.allocatable && !sym->attr.pointer
10011           && sym->ts.type != BT_CLASS && !sym->assoc)
10012         {
10013           gfc_error ("Array '%s' at %L cannot have a deferred shape",
10014                      sym->name, &sym->declared_at);
10015           return FAILURE;
10016          }
10017     }
10018
10019   /* Constraints on polymorphic variables.  */
10020   if (sym->ts.type == BT_CLASS && !(sym->result && sym->result != sym))
10021     {
10022       /* F03:C502.  */
10023       if (sym->attr.class_ok
10024           && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
10025         {
10026           gfc_error ("Type '%s' of CLASS variable '%s' at %L is not extensible",
10027                      CLASS_DATA (sym)->ts.u.derived->name, sym->name,
10028                      &sym->declared_at);
10029           return FAILURE;
10030         }
10031
10032       /* F03:C509.  */
10033       /* Assume that use associated symbols were checked in the module ns.
10034          Class-variables that are associate-names are also something special
10035          and excepted from the test.  */
10036       if (!sym->attr.class_ok && !sym->attr.use_assoc && !sym->assoc)
10037         {
10038           gfc_error ("CLASS variable '%s' at %L must be dummy, allocatable "
10039                      "or pointer", sym->name, &sym->declared_at);
10040           return FAILURE;
10041         }
10042     }
10043     
10044   return SUCCESS;
10045 }
10046
10047
10048 /* Additional checks for symbols with flavor variable and derived
10049    type.  To be called from resolve_fl_variable.  */
10050
10051 static gfc_try
10052 resolve_fl_variable_derived (gfc_symbol *sym, int no_init_flag)
10053 {
10054   gcc_assert (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS);
10055
10056   /* Check to see if a derived type is blocked from being host
10057      associated by the presence of another class I symbol in the same
10058      namespace.  14.6.1.3 of the standard and the discussion on
10059      comp.lang.fortran.  */
10060   if (sym->ns != sym->ts.u.derived->ns
10061       && sym->ns->proc_name->attr.if_source != IFSRC_IFBODY)
10062     {
10063       gfc_symbol *s;
10064       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 0, &s);
10065       if (s && s->attr.flavor != FL_DERIVED)
10066         {
10067           gfc_error ("The type '%s' cannot be host associated at %L "
10068                      "because it is blocked by an incompatible object "
10069                      "of the same name declared at %L",
10070                      sym->ts.u.derived->name, &sym->declared_at,
10071                      &s->declared_at);
10072           return FAILURE;
10073         }
10074     }
10075
10076   /* 4th constraint in section 11.3: "If an object of a type for which
10077      component-initialization is specified (R429) appears in the
10078      specification-part of a module and does not have the ALLOCATABLE
10079      or POINTER attribute, the object shall have the SAVE attribute."
10080
10081      The check for initializers is performed with
10082      gfc_has_default_initializer because gfc_default_initializer generates
10083      a hidden default for allocatable components.  */
10084   if (!(sym->value || no_init_flag) && sym->ns->proc_name
10085       && sym->ns->proc_name->attr.flavor == FL_MODULE
10086       && !sym->ns->save_all && !sym->attr.save
10087       && !sym->attr.pointer && !sym->attr.allocatable
10088       && gfc_has_default_initializer (sym->ts.u.derived)
10089       && gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Implied SAVE for "
10090                          "module variable '%s' at %L, needed due to "
10091                          "the default initialization", sym->name,
10092                          &sym->declared_at) == FAILURE)
10093     return FAILURE;
10094
10095   /* Assign default initializer.  */
10096   if (!(sym->value || sym->attr.pointer || sym->attr.allocatable)
10097       && (!no_init_flag || sym->attr.intent == INTENT_OUT))
10098     {
10099       sym->value = gfc_default_initializer (&sym->ts);
10100     }
10101
10102   return SUCCESS;
10103 }
10104
10105
10106 /* Resolve symbols with flavor variable.  */
10107
10108 static gfc_try
10109 resolve_fl_variable (gfc_symbol *sym, int mp_flag)
10110 {
10111   int no_init_flag, automatic_flag;
10112   gfc_expr *e;
10113   const char *auto_save_msg;
10114
10115   auto_save_msg = "Automatic object '%s' at %L cannot have the "
10116                   "SAVE attribute";
10117
10118   if (resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10119     return FAILURE;
10120
10121   /* Set this flag to check that variables are parameters of all entries.
10122      This check is effected by the call to gfc_resolve_expr through
10123      is_non_constant_shape_array.  */
10124   specification_expr = 1;
10125
10126   if (sym->ns->proc_name
10127       && (sym->ns->proc_name->attr.flavor == FL_MODULE
10128           || sym->ns->proc_name->attr.is_main_program)
10129       && !sym->attr.use_assoc
10130       && !sym->attr.allocatable
10131       && !sym->attr.pointer
10132       && is_non_constant_shape_array (sym))
10133     {
10134       /* The shape of a main program or module array needs to be
10135          constant.  */
10136       gfc_error ("The module or main program array '%s' at %L must "
10137                  "have constant shape", sym->name, &sym->declared_at);
10138       specification_expr = 0;
10139       return FAILURE;
10140     }
10141
10142   /* Constraints on deferred type parameter.  */
10143   if (sym->ts.deferred && !(sym->attr.pointer || sym->attr.allocatable))
10144     {
10145       gfc_error ("Entity '%s' at %L has a deferred type parameter and "
10146                  "requires either the pointer or allocatable attribute",
10147                      sym->name, &sym->declared_at);
10148       return FAILURE;
10149     }
10150
10151   if (sym->ts.type == BT_CHARACTER)
10152     {
10153       /* Make sure that character string variables with assumed length are
10154          dummy arguments.  */
10155       e = sym->ts.u.cl->length;
10156       if (e == NULL && !sym->attr.dummy && !sym->attr.result
10157           && !sym->ts.deferred)
10158         {
10159           gfc_error ("Entity with assumed character length at %L must be a "
10160                      "dummy argument or a PARAMETER", &sym->declared_at);
10161           return FAILURE;
10162         }
10163
10164       if (e && sym->attr.save == SAVE_EXPLICIT && !gfc_is_constant_expr (e))
10165         {
10166           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10167           return FAILURE;
10168         }
10169
10170       if (!gfc_is_constant_expr (e)
10171           && !(e->expr_type == EXPR_VARIABLE
10172                && e->symtree->n.sym->attr.flavor == FL_PARAMETER)
10173           && sym->ns->proc_name
10174           && (sym->ns->proc_name->attr.flavor == FL_MODULE
10175               || sym->ns->proc_name->attr.is_main_program)
10176           && !sym->attr.use_assoc)
10177         {
10178           gfc_error ("'%s' at %L must have constant character length "
10179                      "in this context", sym->name, &sym->declared_at);
10180           return FAILURE;
10181         }
10182     }
10183
10184   if (sym->value == NULL && sym->attr.referenced)
10185     apply_default_init_local (sym); /* Try to apply a default initialization.  */
10186
10187   /* Determine if the symbol may not have an initializer.  */
10188   no_init_flag = automatic_flag = 0;
10189   if (sym->attr.allocatable || sym->attr.external || sym->attr.dummy
10190       || sym->attr.intrinsic || sym->attr.result)
10191     no_init_flag = 1;
10192   else if ((sym->attr.dimension || sym->attr.codimension) && !sym->attr.pointer
10193            && is_non_constant_shape_array (sym))
10194     {
10195       no_init_flag = automatic_flag = 1;
10196
10197       /* Also, they must not have the SAVE attribute.
10198          SAVE_IMPLICIT is checked below.  */
10199       if (sym->as && sym->attr.codimension)
10200         {
10201           int corank = sym->as->corank;
10202           sym->as->corank = 0;
10203           no_init_flag = automatic_flag = is_non_constant_shape_array (sym);
10204           sym->as->corank = corank;
10205         }
10206       if (automatic_flag && sym->attr.save == SAVE_EXPLICIT)
10207         {
10208           gfc_error (auto_save_msg, sym->name, &sym->declared_at);
10209           return FAILURE;
10210         }
10211     }
10212
10213   /* Ensure that any initializer is simplified.  */
10214   if (sym->value)
10215     gfc_simplify_expr (sym->value, 1);
10216
10217   /* Reject illegal initializers.  */
10218   if (!sym->mark && sym->value)
10219     {
10220       if (sym->attr.allocatable || (sym->ts.type == BT_CLASS
10221                                     && CLASS_DATA (sym)->attr.allocatable))
10222         gfc_error ("Allocatable '%s' at %L cannot have an initializer",
10223                    sym->name, &sym->declared_at);
10224       else if (sym->attr.external)
10225         gfc_error ("External '%s' at %L cannot have an initializer",
10226                    sym->name, &sym->declared_at);
10227       else if (sym->attr.dummy
10228         && !(sym->ts.type == BT_DERIVED && sym->attr.intent == INTENT_OUT))
10229         gfc_error ("Dummy '%s' at %L cannot have an initializer",
10230                    sym->name, &sym->declared_at);
10231       else if (sym->attr.intrinsic)
10232         gfc_error ("Intrinsic '%s' at %L cannot have an initializer",
10233                    sym->name, &sym->declared_at);
10234       else if (sym->attr.result)
10235         gfc_error ("Function result '%s' at %L cannot have an initializer",
10236                    sym->name, &sym->declared_at);
10237       else if (automatic_flag)
10238         gfc_error ("Automatic array '%s' at %L cannot have an initializer",
10239                    sym->name, &sym->declared_at);
10240       else
10241         goto no_init_error;
10242       return FAILURE;
10243     }
10244
10245 no_init_error:
10246   if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
10247     return resolve_fl_variable_derived (sym, no_init_flag);
10248
10249   return SUCCESS;
10250 }
10251
10252
10253 /* Resolve a procedure.  */
10254
10255 static gfc_try
10256 resolve_fl_procedure (gfc_symbol *sym, int mp_flag)
10257 {
10258   gfc_formal_arglist *arg;
10259
10260   if (sym->attr.function
10261       && resolve_fl_var_and_proc (sym, mp_flag) == FAILURE)
10262     return FAILURE;
10263
10264   if (sym->ts.type == BT_CHARACTER)
10265     {
10266       gfc_charlen *cl = sym->ts.u.cl;
10267
10268       if (cl && cl->length && gfc_is_constant_expr (cl->length)
10269              && resolve_charlen (cl) == FAILURE)
10270         return FAILURE;
10271
10272       if ((!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
10273           && sym->attr.proc == PROC_ST_FUNCTION)
10274         {
10275           gfc_error ("Character-valued statement function '%s' at %L must "
10276                      "have constant length", sym->name, &sym->declared_at);
10277           return FAILURE;
10278         }
10279     }
10280
10281   /* Ensure that derived type for are not of a private type.  Internal
10282      module procedures are excluded by 2.2.3.3 - i.e., they are not
10283      externally accessible and can access all the objects accessible in
10284      the host.  */
10285   if (!(sym->ns->parent
10286         && sym->ns->parent->proc_name->attr.flavor == FL_MODULE)
10287       && gfc_check_symbol_access (sym))
10288     {
10289       gfc_interface *iface;
10290
10291       for (arg = sym->formal; arg; arg = arg->next)
10292         {
10293           if (arg->sym
10294               && arg->sym->ts.type == BT_DERIVED
10295               && !arg->sym->ts.u.derived->attr.use_assoc
10296               && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10297               && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: '%s' is of a "
10298                                  "PRIVATE type and cannot be a dummy argument"
10299                                  " of '%s', which is PUBLIC at %L",
10300                                  arg->sym->name, sym->name, &sym->declared_at)
10301                  == FAILURE)
10302             {
10303               /* Stop this message from recurring.  */
10304               arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10305               return FAILURE;
10306             }
10307         }
10308
10309       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10310          PRIVATE to the containing module.  */
10311       for (iface = sym->generic; iface; iface = iface->next)
10312         {
10313           for (arg = iface->sym->formal; arg; arg = arg->next)
10314             {
10315               if (arg->sym
10316                   && arg->sym->ts.type == BT_DERIVED
10317                   && !arg->sym->ts.u.derived->attr.use_assoc
10318                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10319                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10320                                      "'%s' in PUBLIC interface '%s' at %L "
10321                                      "takes dummy arguments of '%s' which is "
10322                                      "PRIVATE", iface->sym->name, sym->name,
10323                                      &iface->sym->declared_at,
10324                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10325                 {
10326                   /* Stop this message from recurring.  */
10327                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10328                   return FAILURE;
10329                 }
10330              }
10331         }
10332
10333       /* PUBLIC interfaces may expose PRIVATE procedures that take types
10334          PRIVATE to the containing module.  */
10335       for (iface = sym->generic; iface; iface = iface->next)
10336         {
10337           for (arg = iface->sym->formal; arg; arg = arg->next)
10338             {
10339               if (arg->sym
10340                   && arg->sym->ts.type == BT_DERIVED
10341                   && !arg->sym->ts.u.derived->attr.use_assoc
10342                   && !gfc_check_symbol_access (arg->sym->ts.u.derived)
10343                   && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: Procedure "
10344                                      "'%s' in PUBLIC interface '%s' at %L "
10345                                      "takes dummy arguments of '%s' which is "
10346                                      "PRIVATE", iface->sym->name, sym->name,
10347                                      &iface->sym->declared_at,
10348                                      gfc_typename (&arg->sym->ts)) == FAILURE)
10349                 {
10350                   /* Stop this message from recurring.  */
10351                   arg->sym->ts.u.derived->attr.access = ACCESS_PUBLIC;
10352                   return FAILURE;
10353                 }
10354              }
10355         }
10356     }
10357
10358   if (sym->attr.function && sym->value && sym->attr.proc != PROC_ST_FUNCTION
10359       && !sym->attr.proc_pointer)
10360     {
10361       gfc_error ("Function '%s' at %L cannot have an initializer",
10362                  sym->name, &sym->declared_at);
10363       return FAILURE;
10364     }
10365
10366   /* An external symbol may not have an initializer because it is taken to be
10367      a procedure. Exception: Procedure Pointers.  */
10368   if (sym->attr.external && sym->value && !sym->attr.proc_pointer)
10369     {
10370       gfc_error ("External object '%s' at %L may not have an initializer",
10371                  sym->name, &sym->declared_at);
10372       return FAILURE;
10373     }
10374
10375   /* An elemental function is required to return a scalar 12.7.1  */
10376   if (sym->attr.elemental && sym->attr.function && sym->as)
10377     {
10378       gfc_error ("ELEMENTAL function '%s' at %L must have a scalar "
10379                  "result", sym->name, &sym->declared_at);
10380       /* Reset so that the error only occurs once.  */
10381       sym->attr.elemental = 0;
10382       return FAILURE;
10383     }
10384
10385   if (sym->attr.proc == PROC_ST_FUNCTION
10386       && (sym->attr.allocatable || sym->attr.pointer))
10387     {
10388       gfc_error ("Statement function '%s' at %L may not have pointer or "
10389                  "allocatable attribute", sym->name, &sym->declared_at);
10390       return FAILURE;
10391     }
10392
10393   /* 5.1.1.5 of the Standard: A function name declared with an asterisk
10394      char-len-param shall not be array-valued, pointer-valued, recursive
10395      or pure.  ....snip... A character value of * may only be used in the
10396      following ways: (i) Dummy arg of procedure - dummy associates with
10397      actual length; (ii) To declare a named constant; or (iii) External
10398      function - but length must be declared in calling scoping unit.  */
10399   if (sym->attr.function
10400       && sym->ts.type == BT_CHARACTER
10401       && sym->ts.u.cl && sym->ts.u.cl->length == NULL)
10402     {
10403       if ((sym->as && sym->as->rank) || (sym->attr.pointer)
10404           || (sym->attr.recursive) || (sym->attr.pure))
10405         {
10406           if (sym->as && sym->as->rank)
10407             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10408                        "array-valued", sym->name, &sym->declared_at);
10409
10410           if (sym->attr.pointer)
10411             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10412                        "pointer-valued", sym->name, &sym->declared_at);
10413
10414           if (sym->attr.pure)
10415             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10416                        "pure", sym->name, &sym->declared_at);
10417
10418           if (sym->attr.recursive)
10419             gfc_error ("CHARACTER(*) function '%s' at %L cannot be "
10420                        "recursive", sym->name, &sym->declared_at);
10421
10422           return FAILURE;
10423         }
10424
10425       /* Appendix B.2 of the standard.  Contained functions give an
10426          error anyway.  Fixed-form is likely to be F77/legacy. Deferred
10427          character length is an F2003 feature.  */
10428       if (!sym->attr.contained
10429             && gfc_current_form != FORM_FIXED
10430             && !sym->ts.deferred)
10431         gfc_notify_std (GFC_STD_F95_OBS, "Obsolescent feature: "
10432                         "CHARACTER(*) function '%s' at %L",
10433                         sym->name, &sym->declared_at);
10434     }
10435
10436   if (sym->attr.is_bind_c && sym->attr.is_c_interop != 1)
10437     {
10438       gfc_formal_arglist *curr_arg;
10439       int has_non_interop_arg = 0;
10440
10441       if (verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
10442                              sym->common_block) == FAILURE)
10443         {
10444           /* Clear these to prevent looking at them again if there was an
10445              error.  */
10446           sym->attr.is_bind_c = 0;
10447           sym->attr.is_c_interop = 0;
10448           sym->ts.is_c_interop = 0;
10449         }
10450       else
10451         {
10452           /* So far, no errors have been found.  */
10453           sym->attr.is_c_interop = 1;
10454           sym->ts.is_c_interop = 1;
10455         }
10456       
10457       curr_arg = sym->formal;
10458       while (curr_arg != NULL)
10459         {
10460           /* Skip implicitly typed dummy args here.  */
10461           if (curr_arg->sym->attr.implicit_type == 0)
10462             if (verify_c_interop_param (curr_arg->sym) == FAILURE)
10463               /* If something is found to fail, record the fact so we
10464                  can mark the symbol for the procedure as not being
10465                  BIND(C) to try and prevent multiple errors being
10466                  reported.  */
10467               has_non_interop_arg = 1;
10468           
10469           curr_arg = curr_arg->next;
10470         }
10471
10472       /* See if any of the arguments were not interoperable and if so, clear
10473          the procedure symbol to prevent duplicate error messages.  */
10474       if (has_non_interop_arg != 0)
10475         {
10476           sym->attr.is_c_interop = 0;
10477           sym->ts.is_c_interop = 0;
10478           sym->attr.is_bind_c = 0;
10479         }
10480     }
10481   
10482   if (!sym->attr.proc_pointer)
10483     {
10484       if (sym->attr.save == SAVE_EXPLICIT)
10485         {
10486           gfc_error ("PROCEDURE attribute conflicts with SAVE attribute "
10487                      "in '%s' at %L", sym->name, &sym->declared_at);
10488           return FAILURE;
10489         }
10490       if (sym->attr.intent)
10491         {
10492           gfc_error ("PROCEDURE attribute conflicts with INTENT attribute "
10493                      "in '%s' at %L", sym->name, &sym->declared_at);
10494           return FAILURE;
10495         }
10496       if (sym->attr.subroutine && sym->attr.result)
10497         {
10498           gfc_error ("PROCEDURE attribute conflicts with RESULT attribute "
10499                      "in '%s' at %L", sym->name, &sym->declared_at);
10500           return FAILURE;
10501         }
10502       if (sym->attr.external && sym->attr.function
10503           && ((sym->attr.if_source == IFSRC_DECL && !sym->attr.procedure)
10504               || sym->attr.contained))
10505         {
10506           gfc_error ("EXTERNAL attribute conflicts with FUNCTION attribute "
10507                      "in '%s' at %L", sym->name, &sym->declared_at);
10508           return FAILURE;
10509         }
10510       if (strcmp ("ppr@", sym->name) == 0)
10511         {
10512           gfc_error ("Procedure pointer result '%s' at %L "
10513                      "is missing the pointer attribute",
10514                      sym->ns->proc_name->name, &sym->declared_at);
10515           return FAILURE;
10516         }
10517     }
10518
10519   return SUCCESS;
10520 }
10521
10522
10523 /* Resolve a list of finalizer procedures.  That is, after they have hopefully
10524    been defined and we now know their defined arguments, check that they fulfill
10525    the requirements of the standard for procedures used as finalizers.  */
10526
10527 static gfc_try
10528 gfc_resolve_finalizers (gfc_symbol* derived)
10529 {
10530   gfc_finalizer* list;
10531   gfc_finalizer** prev_link; /* For removing wrong entries from the list.  */
10532   gfc_try result = SUCCESS;
10533   bool seen_scalar = false;
10534
10535   if (!derived->f2k_derived || !derived->f2k_derived->finalizers)
10536     return SUCCESS;
10537
10538   /* Walk over the list of finalizer-procedures, check them, and if any one
10539      does not fit in with the standard's definition, print an error and remove
10540      it from the list.  */
10541   prev_link = &derived->f2k_derived->finalizers;
10542   for (list = derived->f2k_derived->finalizers; list; list = *prev_link)
10543     {
10544       gfc_symbol* arg;
10545       gfc_finalizer* i;
10546       int my_rank;
10547
10548       /* Skip this finalizer if we already resolved it.  */
10549       if (list->proc_tree)
10550         {
10551           prev_link = &(list->next);
10552           continue;
10553         }
10554
10555       /* Check this exists and is a SUBROUTINE.  */
10556       if (!list->proc_sym->attr.subroutine)
10557         {
10558           gfc_error ("FINAL procedure '%s' at %L is not a SUBROUTINE",
10559                      list->proc_sym->name, &list->where);
10560           goto error;
10561         }
10562
10563       /* We should have exactly one argument.  */
10564       if (!list->proc_sym->formal || list->proc_sym->formal->next)
10565         {
10566           gfc_error ("FINAL procedure at %L must have exactly one argument",
10567                      &list->where);
10568           goto error;
10569         }
10570       arg = list->proc_sym->formal->sym;
10571
10572       /* This argument must be of our type.  */
10573       if (arg->ts.type != BT_DERIVED || arg->ts.u.derived != derived)
10574         {
10575           gfc_error ("Argument of FINAL procedure at %L must be of type '%s'",
10576                      &arg->declared_at, derived->name);
10577           goto error;
10578         }
10579
10580       /* It must neither be a pointer nor allocatable nor optional.  */
10581       if (arg->attr.pointer)
10582         {
10583           gfc_error ("Argument of FINAL procedure at %L must not be a POINTER",
10584                      &arg->declared_at);
10585           goto error;
10586         }
10587       if (arg->attr.allocatable)
10588         {
10589           gfc_error ("Argument of FINAL procedure at %L must not be"
10590                      " ALLOCATABLE", &arg->declared_at);
10591           goto error;
10592         }
10593       if (arg->attr.optional)
10594         {
10595           gfc_error ("Argument of FINAL procedure at %L must not be OPTIONAL",
10596                      &arg->declared_at);
10597           goto error;
10598         }
10599
10600       /* It must not be INTENT(OUT).  */
10601       if (arg->attr.intent == INTENT_OUT)
10602         {
10603           gfc_error ("Argument of FINAL procedure at %L must not be"
10604                      " INTENT(OUT)", &arg->declared_at);
10605           goto error;
10606         }
10607
10608       /* Warn if the procedure is non-scalar and not assumed shape.  */
10609       if (gfc_option.warn_surprising && arg->as && arg->as->rank > 0
10610           && arg->as->type != AS_ASSUMED_SHAPE)
10611         gfc_warning ("Non-scalar FINAL procedure at %L should have assumed"
10612                      " shape argument", &arg->declared_at);
10613
10614       /* Check that it does not match in kind and rank with a FINAL procedure
10615          defined earlier.  To really loop over the *earlier* declarations,
10616          we need to walk the tail of the list as new ones were pushed at the
10617          front.  */
10618       /* TODO: Handle kind parameters once they are implemented.  */
10619       my_rank = (arg->as ? arg->as->rank : 0);
10620       for (i = list->next; i; i = i->next)
10621         {
10622           /* Argument list might be empty; that is an error signalled earlier,
10623              but we nevertheless continued resolving.  */
10624           if (i->proc_sym->formal)
10625             {
10626               gfc_symbol* i_arg = i->proc_sym->formal->sym;
10627               const int i_rank = (i_arg->as ? i_arg->as->rank : 0);
10628               if (i_rank == my_rank)
10629                 {
10630                   gfc_error ("FINAL procedure '%s' declared at %L has the same"
10631                              " rank (%d) as '%s'",
10632                              list->proc_sym->name, &list->where, my_rank, 
10633                              i->proc_sym->name);
10634                   goto error;
10635                 }
10636             }
10637         }
10638
10639         /* Is this the/a scalar finalizer procedure?  */
10640         if (!arg->as || arg->as->rank == 0)
10641           seen_scalar = true;
10642
10643         /* Find the symtree for this procedure.  */
10644         gcc_assert (!list->proc_tree);
10645         list->proc_tree = gfc_find_sym_in_symtree (list->proc_sym);
10646
10647         prev_link = &list->next;
10648         continue;
10649
10650         /* Remove wrong nodes immediately from the list so we don't risk any
10651            troubles in the future when they might fail later expectations.  */
10652 error:
10653         result = FAILURE;
10654         i = list;
10655         *prev_link = list->next;
10656         gfc_free_finalizer (i);
10657     }
10658
10659   /* Warn if we haven't seen a scalar finalizer procedure (but we know there
10660      were nodes in the list, must have been for arrays.  It is surely a good
10661      idea to have a scalar version there if there's something to finalize.  */
10662   if (gfc_option.warn_surprising && result == SUCCESS && !seen_scalar)
10663     gfc_warning ("Only array FINAL procedures declared for derived type '%s'"
10664                  " defined at %L, suggest also scalar one",
10665                  derived->name, &derived->declared_at);
10666
10667   /* TODO:  Remove this error when finalization is finished.  */
10668   gfc_error ("Finalization at %L is not yet implemented",
10669              &derived->declared_at);
10670
10671   return result;
10672 }
10673
10674
10675 /* Check if two GENERIC targets are ambiguous and emit an error is they are.  */
10676
10677 static gfc_try
10678 check_generic_tbp_ambiguity (gfc_tbp_generic* t1, gfc_tbp_generic* t2,
10679                              const char* generic_name, locus where)
10680 {
10681   gfc_symbol* sym1;
10682   gfc_symbol* sym2;
10683
10684   gcc_assert (t1->specific && t2->specific);
10685   gcc_assert (!t1->specific->is_generic);
10686   gcc_assert (!t2->specific->is_generic);
10687
10688   sym1 = t1->specific->u.specific->n.sym;
10689   sym2 = t2->specific->u.specific->n.sym;
10690
10691   if (sym1 == sym2)
10692     return SUCCESS;
10693
10694   /* Both must be SUBROUTINEs or both must be FUNCTIONs.  */
10695   if (sym1->attr.subroutine != sym2->attr.subroutine
10696       || sym1->attr.function != sym2->attr.function)
10697     {
10698       gfc_error ("'%s' and '%s' can't be mixed FUNCTION/SUBROUTINE for"
10699                  " GENERIC '%s' at %L",
10700                  sym1->name, sym2->name, generic_name, &where);
10701       return FAILURE;
10702     }
10703
10704   /* Compare the interfaces.  */
10705   if (gfc_compare_interfaces (sym1, sym2, sym2->name, 1, 0, NULL, 0))
10706     {
10707       gfc_error ("'%s' and '%s' for GENERIC '%s' at %L are ambiguous",
10708                  sym1->name, sym2->name, generic_name, &where);
10709       return FAILURE;
10710     }
10711
10712   return SUCCESS;
10713 }
10714
10715
10716 /* Worker function for resolving a generic procedure binding; this is used to
10717    resolve GENERIC as well as user and intrinsic OPERATOR typebound procedures.
10718
10719    The difference between those cases is finding possible inherited bindings
10720    that are overridden, as one has to look for them in tb_sym_root,
10721    tb_uop_root or tb_op, respectively.  Thus the caller must already find
10722    the super-type and set p->overridden correctly.  */
10723
10724 static gfc_try
10725 resolve_tb_generic_targets (gfc_symbol* super_type,
10726                             gfc_typebound_proc* p, const char* name)
10727 {
10728   gfc_tbp_generic* target;
10729   gfc_symtree* first_target;
10730   gfc_symtree* inherited;
10731
10732   gcc_assert (p && p->is_generic);
10733
10734   /* Try to find the specific bindings for the symtrees in our target-list.  */
10735   gcc_assert (p->u.generic);
10736   for (target = p->u.generic; target; target = target->next)
10737     if (!target->specific)
10738       {
10739         gfc_typebound_proc* overridden_tbp;
10740         gfc_tbp_generic* g;
10741         const char* target_name;
10742
10743         target_name = target->specific_st->name;
10744
10745         /* Defined for this type directly.  */
10746         if (target->specific_st->n.tb && !target->specific_st->n.tb->error)
10747           {
10748             target->specific = target->specific_st->n.tb;
10749             goto specific_found;
10750           }
10751
10752         /* Look for an inherited specific binding.  */
10753         if (super_type)
10754           {
10755             inherited = gfc_find_typebound_proc (super_type, NULL, target_name,
10756                                                  true, NULL);
10757
10758             if (inherited)
10759               {
10760                 gcc_assert (inherited->n.tb);
10761                 target->specific = inherited->n.tb;
10762                 goto specific_found;
10763               }
10764           }
10765
10766         gfc_error ("Undefined specific binding '%s' as target of GENERIC '%s'"
10767                    " at %L", target_name, name, &p->where);
10768         return FAILURE;
10769
10770         /* Once we've found the specific binding, check it is not ambiguous with
10771            other specifics already found or inherited for the same GENERIC.  */
10772 specific_found:
10773         gcc_assert (target->specific);
10774
10775         /* This must really be a specific binding!  */
10776         if (target->specific->is_generic)
10777           {
10778             gfc_error ("GENERIC '%s' at %L must target a specific binding,"
10779                        " '%s' is GENERIC, too", name, &p->where, target_name);
10780             return FAILURE;
10781           }
10782
10783         /* Check those already resolved on this type directly.  */
10784         for (g = p->u.generic; g; g = g->next)
10785           if (g != target && g->specific
10786               && check_generic_tbp_ambiguity (target, g, name, p->where)
10787                   == FAILURE)
10788             return FAILURE;
10789
10790         /* Check for ambiguity with inherited specific targets.  */
10791         for (overridden_tbp = p->overridden; overridden_tbp;
10792              overridden_tbp = overridden_tbp->overridden)
10793           if (overridden_tbp->is_generic)
10794             {
10795               for (g = overridden_tbp->u.generic; g; g = g->next)
10796                 {
10797                   gcc_assert (g->specific);
10798                   if (check_generic_tbp_ambiguity (target, g,
10799                                                    name, p->where) == FAILURE)
10800                     return FAILURE;
10801                 }
10802             }
10803       }
10804
10805   /* If we attempt to "overwrite" a specific binding, this is an error.  */
10806   if (p->overridden && !p->overridden->is_generic)
10807     {
10808       gfc_error ("GENERIC '%s' at %L can't overwrite specific binding with"
10809                  " the same name", name, &p->where);
10810       return FAILURE;
10811     }
10812
10813   /* Take the SUBROUTINE/FUNCTION attributes of the first specific target, as
10814      all must have the same attributes here.  */
10815   first_target = p->u.generic->specific->u.specific;
10816   gcc_assert (first_target);
10817   p->subroutine = first_target->n.sym->attr.subroutine;
10818   p->function = first_target->n.sym->attr.function;
10819
10820   return SUCCESS;
10821 }
10822
10823
10824 /* Resolve a GENERIC procedure binding for a derived type.  */
10825
10826 static gfc_try
10827 resolve_typebound_generic (gfc_symbol* derived, gfc_symtree* st)
10828 {
10829   gfc_symbol* super_type;
10830
10831   /* Find the overridden binding if any.  */
10832   st->n.tb->overridden = NULL;
10833   super_type = gfc_get_derived_super_type (derived);
10834   if (super_type)
10835     {
10836       gfc_symtree* overridden;
10837       overridden = gfc_find_typebound_proc (super_type, NULL, st->name,
10838                                             true, NULL);
10839
10840       if (overridden && overridden->n.tb)
10841         st->n.tb->overridden = overridden->n.tb;
10842     }
10843
10844   /* Resolve using worker function.  */
10845   return resolve_tb_generic_targets (super_type, st->n.tb, st->name);
10846 }
10847
10848
10849 /* Retrieve the target-procedure of an operator binding and do some checks in
10850    common for intrinsic and user-defined type-bound operators.  */
10851
10852 static gfc_symbol*
10853 get_checked_tb_operator_target (gfc_tbp_generic* target, locus where)
10854 {
10855   gfc_symbol* target_proc;
10856
10857   gcc_assert (target->specific && !target->specific->is_generic);
10858   target_proc = target->specific->u.specific->n.sym;
10859   gcc_assert (target_proc);
10860
10861   /* All operator bindings must have a passed-object dummy argument.  */
10862   if (target->specific->nopass)
10863     {
10864       gfc_error ("Type-bound operator at %L can't be NOPASS", &where);
10865       return NULL;
10866     }
10867
10868   return target_proc;
10869 }
10870
10871
10872 /* Resolve a type-bound intrinsic operator.  */
10873
10874 static gfc_try
10875 resolve_typebound_intrinsic_op (gfc_symbol* derived, gfc_intrinsic_op op,
10876                                 gfc_typebound_proc* p)
10877 {
10878   gfc_symbol* super_type;
10879   gfc_tbp_generic* target;
10880   
10881   /* If there's already an error here, do nothing (but don't fail again).  */
10882   if (p->error)
10883     return SUCCESS;
10884
10885   /* Operators should always be GENERIC bindings.  */
10886   gcc_assert (p->is_generic);
10887
10888   /* Look for an overridden binding.  */
10889   super_type = gfc_get_derived_super_type (derived);
10890   if (super_type && super_type->f2k_derived)
10891     p->overridden = gfc_find_typebound_intrinsic_op (super_type, NULL,
10892                                                      op, true, NULL);
10893   else
10894     p->overridden = NULL;
10895
10896   /* Resolve general GENERIC properties using worker function.  */
10897   if (resolve_tb_generic_targets (super_type, p, gfc_op2string (op)) == FAILURE)
10898     goto error;
10899
10900   /* Check the targets to be procedures of correct interface.  */
10901   for (target = p->u.generic; target; target = target->next)
10902     {
10903       gfc_symbol* target_proc;
10904
10905       target_proc = get_checked_tb_operator_target (target, p->where);
10906       if (!target_proc)
10907         goto error;
10908
10909       if (!gfc_check_operator_interface (target_proc, op, p->where))
10910         goto error;
10911     }
10912
10913   return SUCCESS;
10914
10915 error:
10916   p->error = 1;
10917   return FAILURE;
10918 }
10919
10920
10921 /* Resolve a type-bound user operator (tree-walker callback).  */
10922
10923 static gfc_symbol* resolve_bindings_derived;
10924 static gfc_try resolve_bindings_result;
10925
10926 static gfc_try check_uop_procedure (gfc_symbol* sym, locus where);
10927
10928 static void
10929 resolve_typebound_user_op (gfc_symtree* stree)
10930 {
10931   gfc_symbol* super_type;
10932   gfc_tbp_generic* target;
10933
10934   gcc_assert (stree && stree->n.tb);
10935
10936   if (stree->n.tb->error)
10937     return;
10938
10939   /* Operators should always be GENERIC bindings.  */
10940   gcc_assert (stree->n.tb->is_generic);
10941
10942   /* Find overridden procedure, if any.  */
10943   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
10944   if (super_type && super_type->f2k_derived)
10945     {
10946       gfc_symtree* overridden;
10947       overridden = gfc_find_typebound_user_op (super_type, NULL,
10948                                                stree->name, true, NULL);
10949
10950       if (overridden && overridden->n.tb)
10951         stree->n.tb->overridden = overridden->n.tb;
10952     }
10953   else
10954     stree->n.tb->overridden = NULL;
10955
10956   /* Resolve basically using worker function.  */
10957   if (resolve_tb_generic_targets (super_type, stree->n.tb, stree->name)
10958         == FAILURE)
10959     goto error;
10960
10961   /* Check the targets to be functions of correct interface.  */
10962   for (target = stree->n.tb->u.generic; target; target = target->next)
10963     {
10964       gfc_symbol* target_proc;
10965
10966       target_proc = get_checked_tb_operator_target (target, stree->n.tb->where);
10967       if (!target_proc)
10968         goto error;
10969
10970       if (check_uop_procedure (target_proc, stree->n.tb->where) == FAILURE)
10971         goto error;
10972     }
10973
10974   return;
10975
10976 error:
10977   resolve_bindings_result = FAILURE;
10978   stree->n.tb->error = 1;
10979 }
10980
10981
10982 /* Resolve the type-bound procedures for a derived type.  */
10983
10984 static void
10985 resolve_typebound_procedure (gfc_symtree* stree)
10986 {
10987   gfc_symbol* proc;
10988   locus where;
10989   gfc_symbol* me_arg;
10990   gfc_symbol* super_type;
10991   gfc_component* comp;
10992
10993   gcc_assert (stree);
10994
10995   /* Undefined specific symbol from GENERIC target definition.  */
10996   if (!stree->n.tb)
10997     return;
10998
10999   if (stree->n.tb->error)
11000     return;
11001
11002   /* If this is a GENERIC binding, use that routine.  */
11003   if (stree->n.tb->is_generic)
11004     {
11005       if (resolve_typebound_generic (resolve_bindings_derived, stree)
11006             == FAILURE)
11007         goto error;
11008       return;
11009     }
11010
11011   /* Get the target-procedure to check it.  */
11012   gcc_assert (!stree->n.tb->is_generic);
11013   gcc_assert (stree->n.tb->u.specific);
11014   proc = stree->n.tb->u.specific->n.sym;
11015   where = stree->n.tb->where;
11016
11017   /* Default access should already be resolved from the parser.  */
11018   gcc_assert (stree->n.tb->access != ACCESS_UNKNOWN);
11019
11020   /* It should be a module procedure or an external procedure with explicit
11021      interface.  For DEFERRED bindings, abstract interfaces are ok as well.  */
11022   if ((!proc->attr.subroutine && !proc->attr.function)
11023       || (proc->attr.proc != PROC_MODULE
11024           && proc->attr.if_source != IFSRC_IFBODY)
11025       || (proc->attr.abstract && !stree->n.tb->deferred))
11026     {
11027       gfc_error ("'%s' must be a module procedure or an external procedure with"
11028                  " an explicit interface at %L", proc->name, &where);
11029       goto error;
11030     }
11031   stree->n.tb->subroutine = proc->attr.subroutine;
11032   stree->n.tb->function = proc->attr.function;
11033
11034   /* Find the super-type of the current derived type.  We could do this once and
11035      store in a global if speed is needed, but as long as not I believe this is
11036      more readable and clearer.  */
11037   super_type = gfc_get_derived_super_type (resolve_bindings_derived);
11038
11039   /* If PASS, resolve and check arguments if not already resolved / loaded
11040      from a .mod file.  */
11041   if (!stree->n.tb->nopass && stree->n.tb->pass_arg_num == 0)
11042     {
11043       if (stree->n.tb->pass_arg)
11044         {
11045           gfc_formal_arglist* i;
11046
11047           /* If an explicit passing argument name is given, walk the arg-list
11048              and look for it.  */
11049
11050           me_arg = NULL;
11051           stree->n.tb->pass_arg_num = 1;
11052           for (i = proc->formal; i; i = i->next)
11053             {
11054               if (!strcmp (i->sym->name, stree->n.tb->pass_arg))
11055                 {
11056                   me_arg = i->sym;
11057                   break;
11058                 }
11059               ++stree->n.tb->pass_arg_num;
11060             }
11061
11062           if (!me_arg)
11063             {
11064               gfc_error ("Procedure '%s' with PASS(%s) at %L has no"
11065                          " argument '%s'",
11066                          proc->name, stree->n.tb->pass_arg, &where,
11067                          stree->n.tb->pass_arg);
11068               goto error;
11069             }
11070         }
11071       else
11072         {
11073           /* Otherwise, take the first one; there should in fact be at least
11074              one.  */
11075           stree->n.tb->pass_arg_num = 1;
11076           if (!proc->formal)
11077             {
11078               gfc_error ("Procedure '%s' with PASS at %L must have at"
11079                          " least one argument", proc->name, &where);
11080               goto error;
11081             }
11082           me_arg = proc->formal->sym;
11083         }
11084
11085       /* Now check that the argument-type matches and the passed-object
11086          dummy argument is generally fine.  */
11087
11088       gcc_assert (me_arg);
11089
11090       if (me_arg->ts.type != BT_CLASS)
11091         {
11092           gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11093                      " at %L", proc->name, &where);
11094           goto error;
11095         }
11096
11097       if (CLASS_DATA (me_arg)->ts.u.derived
11098           != resolve_bindings_derived)
11099         {
11100           gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11101                      " the derived-type '%s'", me_arg->name, proc->name,
11102                      me_arg->name, &where, resolve_bindings_derived->name);
11103           goto error;
11104         }
11105   
11106       gcc_assert (me_arg->ts.type == BT_CLASS);
11107       if (CLASS_DATA (me_arg)->as && CLASS_DATA (me_arg)->as->rank > 0)
11108         {
11109           gfc_error ("Passed-object dummy argument of '%s' at %L must be"
11110                      " scalar", proc->name, &where);
11111           goto error;
11112         }
11113       if (CLASS_DATA (me_arg)->attr.allocatable)
11114         {
11115           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11116                      " be ALLOCATABLE", proc->name, &where);
11117           goto error;
11118         }
11119       if (CLASS_DATA (me_arg)->attr.class_pointer)
11120         {
11121           gfc_error ("Passed-object dummy argument of '%s' at %L must not"
11122                      " be POINTER", proc->name, &where);
11123           goto error;
11124         }
11125     }
11126
11127   /* If we are extending some type, check that we don't override a procedure
11128      flagged NON_OVERRIDABLE.  */
11129   stree->n.tb->overridden = NULL;
11130   if (super_type)
11131     {
11132       gfc_symtree* overridden;
11133       overridden = gfc_find_typebound_proc (super_type, NULL,
11134                                             stree->name, true, NULL);
11135
11136       if (overridden)
11137         {
11138           if (overridden->n.tb)
11139             stree->n.tb->overridden = overridden->n.tb;
11140
11141           if (gfc_check_typebound_override (stree, overridden) == FAILURE)
11142             goto error;
11143         }
11144     }
11145
11146   /* See if there's a name collision with a component directly in this type.  */
11147   for (comp = resolve_bindings_derived->components; comp; comp = comp->next)
11148     if (!strcmp (comp->name, stree->name))
11149       {
11150         gfc_error ("Procedure '%s' at %L has the same name as a component of"
11151                    " '%s'",
11152                    stree->name, &where, resolve_bindings_derived->name);
11153         goto error;
11154       }
11155
11156   /* Try to find a name collision with an inherited component.  */
11157   if (super_type && gfc_find_component (super_type, stree->name, true, true))
11158     {
11159       gfc_error ("Procedure '%s' at %L has the same name as an inherited"
11160                  " component of '%s'",
11161                  stree->name, &where, resolve_bindings_derived->name);
11162       goto error;
11163     }
11164
11165   stree->n.tb->error = 0;
11166   return;
11167
11168 error:
11169   resolve_bindings_result = FAILURE;
11170   stree->n.tb->error = 1;
11171 }
11172
11173
11174 static gfc_try
11175 resolve_typebound_procedures (gfc_symbol* derived)
11176 {
11177   int op;
11178   gfc_symbol* super_type;
11179
11180   if (!derived->f2k_derived || !derived->f2k_derived->tb_sym_root)
11181     return SUCCESS;
11182   
11183   super_type = gfc_get_derived_super_type (derived);
11184   if (super_type)
11185     resolve_typebound_procedures (super_type);
11186
11187   resolve_bindings_derived = derived;
11188   resolve_bindings_result = SUCCESS;
11189
11190   /* Make sure the vtab has been generated.  */
11191   gfc_find_derived_vtab (derived);
11192
11193   if (derived->f2k_derived->tb_sym_root)
11194     gfc_traverse_symtree (derived->f2k_derived->tb_sym_root,
11195                           &resolve_typebound_procedure);
11196
11197   if (derived->f2k_derived->tb_uop_root)
11198     gfc_traverse_symtree (derived->f2k_derived->tb_uop_root,
11199                           &resolve_typebound_user_op);
11200
11201   for (op = 0; op != GFC_INTRINSIC_OPS; ++op)
11202     {
11203       gfc_typebound_proc* p = derived->f2k_derived->tb_op[op];
11204       if (p && resolve_typebound_intrinsic_op (derived, (gfc_intrinsic_op) op,
11205                                                p) == FAILURE)
11206         resolve_bindings_result = FAILURE;
11207     }
11208
11209   return resolve_bindings_result;
11210 }
11211
11212
11213 /* Add a derived type to the dt_list.  The dt_list is used in trans-types.c
11214    to give all identical derived types the same backend_decl.  */
11215 static void
11216 add_dt_to_dt_list (gfc_symbol *derived)
11217 {
11218   gfc_dt_list *dt_list;
11219
11220   for (dt_list = gfc_derived_types; dt_list; dt_list = dt_list->next)
11221     if (derived == dt_list->derived)
11222       return;
11223
11224   dt_list = gfc_get_dt_list ();
11225   dt_list->next = gfc_derived_types;
11226   dt_list->derived = derived;
11227   gfc_derived_types = dt_list;
11228 }
11229
11230
11231 /* Ensure that a derived-type is really not abstract, meaning that every
11232    inherited DEFERRED binding is overridden by a non-DEFERRED one.  */
11233
11234 static gfc_try
11235 ensure_not_abstract_walker (gfc_symbol* sub, gfc_symtree* st)
11236 {
11237   if (!st)
11238     return SUCCESS;
11239
11240   if (ensure_not_abstract_walker (sub, st->left) == FAILURE)
11241     return FAILURE;
11242   if (ensure_not_abstract_walker (sub, st->right) == FAILURE)
11243     return FAILURE;
11244
11245   if (st->n.tb && st->n.tb->deferred)
11246     {
11247       gfc_symtree* overriding;
11248       overriding = gfc_find_typebound_proc (sub, NULL, st->name, true, NULL);
11249       if (!overriding)
11250         return FAILURE;
11251       gcc_assert (overriding->n.tb);
11252       if (overriding->n.tb->deferred)
11253         {
11254           gfc_error ("Derived-type '%s' declared at %L must be ABSTRACT because"
11255                      " '%s' is DEFERRED and not overridden",
11256                      sub->name, &sub->declared_at, st->name);
11257           return FAILURE;
11258         }
11259     }
11260
11261   return SUCCESS;
11262 }
11263
11264 static gfc_try
11265 ensure_not_abstract (gfc_symbol* sub, gfc_symbol* ancestor)
11266 {
11267   /* The algorithm used here is to recursively travel up the ancestry of sub
11268      and for each ancestor-type, check all bindings.  If any of them is
11269      DEFERRED, look it up starting from sub and see if the found (overriding)
11270      binding is not DEFERRED.
11271      This is not the most efficient way to do this, but it should be ok and is
11272      clearer than something sophisticated.  */
11273
11274   gcc_assert (ancestor && !sub->attr.abstract);
11275   
11276   if (!ancestor->attr.abstract)
11277     return SUCCESS;
11278
11279   /* Walk bindings of this ancestor.  */
11280   if (ancestor->f2k_derived)
11281     {
11282       gfc_try t;
11283       t = ensure_not_abstract_walker (sub, ancestor->f2k_derived->tb_sym_root);
11284       if (t == FAILURE)
11285         return FAILURE;
11286     }
11287
11288   /* Find next ancestor type and recurse on it.  */
11289   ancestor = gfc_get_derived_super_type (ancestor);
11290   if (ancestor)
11291     return ensure_not_abstract (sub, ancestor);
11292
11293   return SUCCESS;
11294 }
11295
11296
11297 /* Resolve the components of a derived type. This does not have to wait until
11298    resolution stage, but can be done as soon as the dt declaration has been
11299    parsed.  */
11300
11301 static gfc_try
11302 resolve_fl_derived0 (gfc_symbol *sym)
11303 {
11304   gfc_symbol* super_type;
11305   gfc_component *c;
11306
11307   super_type = gfc_get_derived_super_type (sym);
11308
11309   /* F2008, C432. */
11310   if (super_type && sym->attr.coarray_comp && !super_type->attr.coarray_comp)
11311     {
11312       gfc_error ("As extending type '%s' at %L has a coarray component, "
11313                  "parent type '%s' shall also have one", sym->name,
11314                  &sym->declared_at, super_type->name);
11315       return FAILURE;
11316     }
11317
11318   /* Ensure the extended type gets resolved before we do.  */
11319   if (super_type && resolve_fl_derived0 (super_type) == FAILURE)
11320     return FAILURE;
11321
11322   /* An ABSTRACT type must be extensible.  */
11323   if (sym->attr.abstract && !gfc_type_is_extensible (sym))
11324     {
11325       gfc_error ("Non-extensible derived-type '%s' at %L must not be ABSTRACT",
11326                  sym->name, &sym->declared_at);
11327       return FAILURE;
11328     }
11329
11330   for (c = sym->components; c != NULL; c = c->next)
11331     {
11332       /* F2008, C442.  */
11333       if (c->attr.codimension /* FIXME: c->as check due to PR 43412.  */
11334           && (!c->attr.allocatable || (c->as && c->as->type != AS_DEFERRED)))
11335         {
11336           gfc_error ("Coarray component '%s' at %L must be allocatable with "
11337                      "deferred shape", c->name, &c->loc);
11338           return FAILURE;
11339         }
11340
11341       /* F2008, C443.  */
11342       if (c->attr.codimension && c->ts.type == BT_DERIVED
11343           && c->ts.u.derived->ts.is_iso_c)
11344         {
11345           gfc_error ("Component '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
11346                      "shall not be a coarray", c->name, &c->loc);
11347           return FAILURE;
11348         }
11349
11350       /* F2008, C444.  */
11351       if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.coarray_comp
11352           && (c->attr.codimension || c->attr.pointer || c->attr.dimension
11353               || c->attr.allocatable))
11354         {
11355           gfc_error ("Component '%s' at %L with coarray component "
11356                      "shall be a nonpointer, nonallocatable scalar",
11357                      c->name, &c->loc);
11358           return FAILURE;
11359         }
11360
11361       /* F2008, C448.  */
11362       if (c->attr.contiguous && (!c->attr.dimension || !c->attr.pointer))
11363         {
11364           gfc_error ("Component '%s' at %L has the CONTIGUOUS attribute but "
11365                      "is not an array pointer", c->name, &c->loc);
11366           return FAILURE;
11367         }
11368
11369       if (c->attr.proc_pointer && c->ts.interface)
11370         {
11371           if (c->ts.interface->attr.procedure && !sym->attr.vtype)
11372             gfc_error ("Interface '%s', used by procedure pointer component "
11373                        "'%s' at %L, is declared in a later PROCEDURE statement",
11374                        c->ts.interface->name, c->name, &c->loc);
11375
11376           /* Get the attributes from the interface (now resolved).  */
11377           if (c->ts.interface->attr.if_source
11378               || c->ts.interface->attr.intrinsic)
11379             {
11380               gfc_symbol *ifc = c->ts.interface;
11381
11382               if (ifc->formal && !ifc->formal_ns)
11383                 resolve_symbol (ifc);
11384
11385               if (ifc->attr.intrinsic)
11386                 resolve_intrinsic (ifc, &ifc->declared_at);
11387
11388               if (ifc->result)
11389                 {
11390                   c->ts = ifc->result->ts;
11391                   c->attr.allocatable = ifc->result->attr.allocatable;
11392                   c->attr.pointer = ifc->result->attr.pointer;
11393                   c->attr.dimension = ifc->result->attr.dimension;
11394                   c->as = gfc_copy_array_spec (ifc->result->as);
11395                 }
11396               else
11397                 {   
11398                   c->ts = ifc->ts;
11399                   c->attr.allocatable = ifc->attr.allocatable;
11400                   c->attr.pointer = ifc->attr.pointer;
11401                   c->attr.dimension = ifc->attr.dimension;
11402                   c->as = gfc_copy_array_spec (ifc->as);
11403                 }
11404               c->ts.interface = ifc;
11405               c->attr.function = ifc->attr.function;
11406               c->attr.subroutine = ifc->attr.subroutine;
11407               gfc_copy_formal_args_ppc (c, ifc);
11408
11409               c->attr.pure = ifc->attr.pure;
11410               c->attr.elemental = ifc->attr.elemental;
11411               c->attr.recursive = ifc->attr.recursive;
11412               c->attr.always_explicit = ifc->attr.always_explicit;
11413               c->attr.ext_attr |= ifc->attr.ext_attr;
11414               /* Replace symbols in array spec.  */
11415               if (c->as)
11416                 {
11417                   int i;
11418                   for (i = 0; i < c->as->rank; i++)
11419                     {
11420                       gfc_expr_replace_comp (c->as->lower[i], c);
11421                       gfc_expr_replace_comp (c->as->upper[i], c);
11422                     }
11423                 }
11424               /* Copy char length.  */
11425               if (ifc->ts.type == BT_CHARACTER && ifc->ts.u.cl)
11426                 {
11427                   gfc_charlen *cl = gfc_new_charlen (sym->ns, ifc->ts.u.cl);
11428                   gfc_expr_replace_comp (cl->length, c);
11429                   if (cl->length && !cl->resolved
11430                         && gfc_resolve_expr (cl->length) == FAILURE)
11431                     return FAILURE;
11432                   c->ts.u.cl = cl;
11433                 }
11434             }
11435           else if (!sym->attr.vtype && c->ts.interface->name[0] != '\0')
11436             {
11437               gfc_error ("Interface '%s' of procedure pointer component "
11438                          "'%s' at %L must be explicit", c->ts.interface->name,
11439                          c->name, &c->loc);
11440               return FAILURE;
11441             }
11442         }
11443       else if (c->attr.proc_pointer && c->ts.type == BT_UNKNOWN)
11444         {
11445           /* Since PPCs are not implicitly typed, a PPC without an explicit
11446              interface must be a subroutine.  */
11447           gfc_add_subroutine (&c->attr, c->name, &c->loc);
11448         }
11449
11450       /* Procedure pointer components: Check PASS arg.  */
11451       if (c->attr.proc_pointer && !c->tb->nopass && c->tb->pass_arg_num == 0
11452           && !sym->attr.vtype)
11453         {
11454           gfc_symbol* me_arg;
11455
11456           if (c->tb->pass_arg)
11457             {
11458               gfc_formal_arglist* i;
11459
11460               /* If an explicit passing argument name is given, walk the arg-list
11461                 and look for it.  */
11462
11463               me_arg = NULL;
11464               c->tb->pass_arg_num = 1;
11465               for (i = c->formal; i; i = i->next)
11466                 {
11467                   if (!strcmp (i->sym->name, c->tb->pass_arg))
11468                     {
11469                       me_arg = i->sym;
11470                       break;
11471                     }
11472                   c->tb->pass_arg_num++;
11473                 }
11474
11475               if (!me_arg)
11476                 {
11477                   gfc_error ("Procedure pointer component '%s' with PASS(%s) "
11478                              "at %L has no argument '%s'", c->name,
11479                              c->tb->pass_arg, &c->loc, c->tb->pass_arg);
11480                   c->tb->error = 1;
11481                   return FAILURE;
11482                 }
11483             }
11484           else
11485             {
11486               /* Otherwise, take the first one; there should in fact be at least
11487                 one.  */
11488               c->tb->pass_arg_num = 1;
11489               if (!c->formal)
11490                 {
11491                   gfc_error ("Procedure pointer component '%s' with PASS at %L "
11492                              "must have at least one argument",
11493                              c->name, &c->loc);
11494                   c->tb->error = 1;
11495                   return FAILURE;
11496                 }
11497               me_arg = c->formal->sym;
11498             }
11499
11500           /* Now check that the argument-type matches.  */
11501           gcc_assert (me_arg);
11502           if ((me_arg->ts.type != BT_DERIVED && me_arg->ts.type != BT_CLASS)
11503               || (me_arg->ts.type == BT_DERIVED && me_arg->ts.u.derived != sym)
11504               || (me_arg->ts.type == BT_CLASS
11505                   && CLASS_DATA (me_arg)->ts.u.derived != sym))
11506             {
11507               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L must be of"
11508                          " the derived type '%s'", me_arg->name, c->name,
11509                          me_arg->name, &c->loc, sym->name);
11510               c->tb->error = 1;
11511               return FAILURE;
11512             }
11513
11514           /* Check for C453.  */
11515           if (me_arg->attr.dimension)
11516             {
11517               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11518                          "must be scalar", me_arg->name, c->name, me_arg->name,
11519                          &c->loc);
11520               c->tb->error = 1;
11521               return FAILURE;
11522             }
11523
11524           if (me_arg->attr.pointer)
11525             {
11526               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11527                          "may not have the POINTER attribute", me_arg->name,
11528                          c->name, me_arg->name, &c->loc);
11529               c->tb->error = 1;
11530               return FAILURE;
11531             }
11532
11533           if (me_arg->attr.allocatable)
11534             {
11535               gfc_error ("Argument '%s' of '%s' with PASS(%s) at %L "
11536                          "may not be ALLOCATABLE", me_arg->name, c->name,
11537                          me_arg->name, &c->loc);
11538               c->tb->error = 1;
11539               return FAILURE;
11540             }
11541
11542           if (gfc_type_is_extensible (sym) && me_arg->ts.type != BT_CLASS)
11543             gfc_error ("Non-polymorphic passed-object dummy argument of '%s'"
11544                        " at %L", c->name, &c->loc);
11545
11546         }
11547
11548       /* Check type-spec if this is not the parent-type component.  */
11549       if ((!sym->attr.extension || c != sym->components) && !sym->attr.vtype
11550           && resolve_typespec_used (&c->ts, &c->loc, c->name) == FAILURE)
11551         return FAILURE;
11552
11553       /* If this type is an extension, set the accessibility of the parent
11554          component.  */
11555       if (super_type && c == sym->components
11556           && strcmp (super_type->name, c->name) == 0)
11557         c->attr.access = super_type->attr.access;
11558       
11559       /* If this type is an extension, see if this component has the same name
11560          as an inherited type-bound procedure.  */
11561       if (super_type && !sym->attr.is_class
11562           && gfc_find_typebound_proc (super_type, NULL, c->name, true, NULL))
11563         {
11564           gfc_error ("Component '%s' of '%s' at %L has the same name as an"
11565                      " inherited type-bound procedure",
11566                      c->name, sym->name, &c->loc);
11567           return FAILURE;
11568         }
11569
11570       if (c->ts.type == BT_CHARACTER && !c->attr.proc_pointer
11571             && !c->ts.deferred)
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_CHARACTER && c->ts.deferred
11586           && !c->attr.pointer && !c->attr.allocatable)
11587         {
11588           gfc_error ("Character component '%s' of '%s' at %L with deferred "
11589                      "length must be a POINTER or ALLOCATABLE",
11590                      c->name, sym->name, &c->loc);
11591           return FAILURE;
11592         }
11593
11594       if (c->ts.type == BT_DERIVED
11595           && sym->component_access != ACCESS_PRIVATE
11596           && gfc_check_symbol_access (sym)
11597           && !is_sym_host_assoc (c->ts.u.derived, sym->ns)
11598           && !c->ts.u.derived->attr.use_assoc
11599           && !gfc_check_symbol_access (c->ts.u.derived)
11600           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: the component '%s' "
11601                              "is a PRIVATE type and cannot be a component of "
11602                              "'%s', which is PUBLIC at %L", c->name,
11603                              sym->name, &sym->declared_at) == FAILURE)
11604         return FAILURE;
11605
11606       if ((sym->attr.sequence || sym->attr.is_bind_c) && c->ts.type == BT_CLASS)
11607         {
11608           gfc_error ("Polymorphic component %s at %L in SEQUENCE or BIND(C) "
11609                      "type %s", c->name, &c->loc, sym->name);
11610           return FAILURE;
11611         }
11612
11613       if (sym->attr.sequence)
11614         {
11615           if (c->ts.type == BT_DERIVED && c->ts.u.derived->attr.sequence == 0)
11616             {
11617               gfc_error ("Component %s of SEQUENCE type declared at %L does "
11618                          "not have the SEQUENCE attribute",
11619                          c->ts.u.derived->name, &sym->declared_at);
11620               return FAILURE;
11621             }
11622         }
11623
11624       if (!sym->attr.is_class && c->ts.type == BT_DERIVED && !sym->attr.vtype
11625           && c->attr.pointer && c->ts.u.derived->components == NULL
11626           && !c->ts.u.derived->attr.zero_comp)
11627         {
11628           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11629                      "that has not been declared", c->name, sym->name,
11630                      &c->loc);
11631           return FAILURE;
11632         }
11633
11634       if (c->ts.type == BT_CLASS && c->attr.class_ok
11635           && CLASS_DATA (c)->attr.class_pointer
11636           && CLASS_DATA (c)->ts.u.derived->components == NULL
11637           && !CLASS_DATA (c)->ts.u.derived->attr.zero_comp)
11638         {
11639           gfc_error ("The pointer component '%s' of '%s' at %L is a type "
11640                      "that has not been declared", c->name, sym->name,
11641                      &c->loc);
11642           return FAILURE;
11643         }
11644
11645       /* C437.  */
11646       if (c->ts.type == BT_CLASS && c->attr.flavor != FL_PROCEDURE
11647           && (!c->attr.class_ok
11648               || !(CLASS_DATA (c)->attr.class_pointer
11649                    || CLASS_DATA (c)->attr.allocatable)))
11650         {
11651           gfc_error ("Component '%s' with CLASS at %L must be allocatable "
11652                      "or pointer", c->name, &c->loc);
11653           return FAILURE;
11654         }
11655
11656       /* Ensure that all the derived type components are put on the
11657          derived type list; even in formal namespaces, where derived type
11658          pointer components might not have been declared.  */
11659       if (c->ts.type == BT_DERIVED
11660             && c->ts.u.derived
11661             && c->ts.u.derived->components
11662             && c->attr.pointer
11663             && sym != c->ts.u.derived)
11664         add_dt_to_dt_list (c->ts.u.derived);
11665
11666       if (gfc_resolve_array_spec (c->as, !(c->attr.pointer
11667                                            || c->attr.proc_pointer
11668                                            || c->attr.allocatable)) == FAILURE)
11669         return FAILURE;
11670     }
11671
11672   /* If this is a non-ABSTRACT type extending an ABSTRACT one, ensure that
11673      all DEFERRED bindings are overridden.  */
11674   if (super_type && super_type->attr.abstract && !sym->attr.abstract
11675       && !sym->attr.is_class
11676       && ensure_not_abstract (sym, super_type) == FAILURE)
11677     return FAILURE;
11678
11679   /* Add derived type to the derived type list.  */
11680   add_dt_to_dt_list (sym);
11681
11682   return SUCCESS;
11683 }
11684
11685
11686 /* The following procedure does the full resolution of a derived type,
11687    including resolution of all type-bound procedures (if present). In contrast
11688    to 'resolve_fl_derived0' this can only be done after the module has been
11689    parsed completely.  */
11690
11691 static gfc_try
11692 resolve_fl_derived (gfc_symbol *sym)
11693 {
11694   if (sym->attr.is_class && sym->ts.u.derived == NULL)
11695     {
11696       /* Fix up incomplete CLASS symbols.  */
11697       gfc_component *data = gfc_find_component (sym, "_data", true, true);
11698       gfc_component *vptr = gfc_find_component (sym, "_vptr", true, true);
11699       if (vptr->ts.u.derived == NULL)
11700         {
11701           gfc_symbol *vtab = gfc_find_derived_vtab (data->ts.u.derived);
11702           gcc_assert (vtab);
11703           vptr->ts.u.derived = vtab->ts.u.derived;
11704         }
11705     }
11706   
11707   if (resolve_fl_derived0 (sym) == FAILURE)
11708     return FAILURE;
11709   
11710   /* Resolve the type-bound procedures.  */
11711   if (resolve_typebound_procedures (sym) == FAILURE)
11712     return FAILURE;
11713
11714   /* Resolve the finalizer procedures.  */
11715   if (gfc_resolve_finalizers (sym) == FAILURE)
11716     return FAILURE;
11717   
11718   return SUCCESS;
11719 }
11720
11721
11722 static gfc_try
11723 resolve_fl_namelist (gfc_symbol *sym)
11724 {
11725   gfc_namelist *nl;
11726   gfc_symbol *nlsym;
11727
11728   for (nl = sym->namelist; nl; nl = nl->next)
11729     {
11730       /* Check again, the check in match only works if NAMELIST comes
11731          after the decl.  */
11732       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SIZE)
11733         {
11734           gfc_error ("Assumed size array '%s' in namelist '%s' at %L is not "
11735                      "allowed", nl->sym->name, sym->name, &sym->declared_at);
11736           return FAILURE;
11737         }
11738
11739       if (nl->sym->as && nl->sym->as->type == AS_ASSUMED_SHAPE
11740           && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: NAMELIST array "
11741                              "object '%s' with assumed shape in namelist "
11742                              "'%s' at %L", nl->sym->name, sym->name,
11743                              &sym->declared_at) == FAILURE)
11744         return FAILURE;
11745
11746       if (is_non_constant_shape_array (nl->sym)
11747           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST array "
11748                              "object '%s' with nonconstant shape in namelist "
11749                              "'%s' at %L", nl->sym->name, sym->name,
11750                              &sym->declared_at) == FAILURE)
11751         return FAILURE;
11752
11753       if (nl->sym->ts.type == BT_CHARACTER
11754           && (nl->sym->ts.u.cl->length == NULL
11755               || !gfc_is_constant_expr (nl->sym->ts.u.cl->length))
11756           && gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
11757                              "'%s' with nonconstant character length in "
11758                              "namelist '%s' at %L", nl->sym->name, sym->name,
11759                              &sym->declared_at) == FAILURE)
11760         return FAILURE;
11761
11762       /* FIXME: Once UDDTIO is implemented, the following can be
11763          removed.  */
11764       if (nl->sym->ts.type == BT_CLASS)
11765         {
11766           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L is "
11767                      "polymorphic and requires a defined input/output "
11768                      "procedure", nl->sym->name, sym->name, &sym->declared_at);
11769           return FAILURE;
11770         }
11771
11772       if (nl->sym->ts.type == BT_DERIVED
11773           && (nl->sym->ts.u.derived->attr.alloc_comp
11774               || nl->sym->ts.u.derived->attr.pointer_comp))
11775         {
11776           if (gfc_notify_std (GFC_STD_F2003,  "Fortran 2003: NAMELIST object "
11777                               "'%s' in namelist '%s' at %L with ALLOCATABLE "
11778                               "or POINTER components", nl->sym->name,
11779                               sym->name, &sym->declared_at) == FAILURE)
11780             return FAILURE;
11781
11782          /* FIXME: Once UDDTIO is implemented, the following can be
11783             removed.  */
11784           gfc_error ("NAMELIST object '%s' in namelist '%s' at %L has "
11785                      "ALLOCATABLE or POINTER components and thus requires "
11786                      "a defined input/output procedure", nl->sym->name,
11787                      sym->name, &sym->declared_at);
11788           return FAILURE;
11789         }
11790     }
11791
11792   /* Reject PRIVATE objects in a PUBLIC namelist.  */
11793   if (gfc_check_symbol_access (sym))
11794     {
11795       for (nl = sym->namelist; nl; nl = nl->next)
11796         {
11797           if (!nl->sym->attr.use_assoc
11798               && !is_sym_host_assoc (nl->sym, sym->ns)
11799               && !gfc_check_symbol_access (nl->sym))
11800             {
11801               gfc_error ("NAMELIST object '%s' was declared PRIVATE and "
11802                          "cannot be member of PUBLIC namelist '%s' at %L",
11803                          nl->sym->name, sym->name, &sym->declared_at);
11804               return FAILURE;
11805             }
11806
11807           /* Types with private components that came here by USE-association.  */
11808           if (nl->sym->ts.type == BT_DERIVED
11809               && derived_inaccessible (nl->sym->ts.u.derived))
11810             {
11811               gfc_error ("NAMELIST object '%s' has use-associated PRIVATE "
11812                          "components and cannot be member of namelist '%s' at %L",
11813                          nl->sym->name, sym->name, &sym->declared_at);
11814               return FAILURE;
11815             }
11816
11817           /* Types with private components that are defined in the same module.  */
11818           if (nl->sym->ts.type == BT_DERIVED
11819               && !is_sym_host_assoc (nl->sym->ts.u.derived, sym->ns)
11820               && nl->sym->ts.u.derived->attr.private_comp)
11821             {
11822               gfc_error ("NAMELIST object '%s' has PRIVATE components and "
11823                          "cannot be a member of PUBLIC namelist '%s' at %L",
11824                          nl->sym->name, sym->name, &sym->declared_at);
11825               return FAILURE;
11826             }
11827         }
11828     }
11829
11830
11831   /* 14.1.2 A module or internal procedure represent local entities
11832      of the same type as a namelist member and so are not allowed.  */
11833   for (nl = sym->namelist; nl; nl = nl->next)
11834     {
11835       if (nl->sym->ts.kind != 0 && nl->sym->attr.flavor == FL_VARIABLE)
11836         continue;
11837
11838       if (nl->sym->attr.function && nl->sym == nl->sym->result)
11839         if ((nl->sym == sym->ns->proc_name)
11840                ||
11841             (sym->ns->parent && nl->sym == sym->ns->parent->proc_name))
11842           continue;
11843
11844       nlsym = NULL;
11845       if (nl->sym && nl->sym->name)
11846         gfc_find_symbol (nl->sym->name, sym->ns, 1, &nlsym);
11847       if (nlsym && nlsym->attr.flavor == FL_PROCEDURE)
11848         {
11849           gfc_error ("PROCEDURE attribute conflicts with NAMELIST "
11850                      "attribute in '%s' at %L", nlsym->name,
11851                      &sym->declared_at);
11852           return FAILURE;
11853         }
11854     }
11855
11856   return SUCCESS;
11857 }
11858
11859
11860 static gfc_try
11861 resolve_fl_parameter (gfc_symbol *sym)
11862 {
11863   /* A parameter array's shape needs to be constant.  */
11864   if (sym->as != NULL 
11865       && (sym->as->type == AS_DEFERRED
11866           || is_non_constant_shape_array (sym)))
11867     {
11868       gfc_error ("Parameter array '%s' at %L cannot be automatic "
11869                  "or of deferred shape", sym->name, &sym->declared_at);
11870       return FAILURE;
11871     }
11872
11873   /* Make sure a parameter that has been implicitly typed still
11874      matches the implicit type, since PARAMETER statements can precede
11875      IMPLICIT statements.  */
11876   if (sym->attr.implicit_type
11877       && !gfc_compare_types (&sym->ts, gfc_get_default_type (sym->name,
11878                                                              sym->ns)))
11879     {
11880       gfc_error ("Implicitly typed PARAMETER '%s' at %L doesn't match a "
11881                  "later IMPLICIT type", sym->name, &sym->declared_at);
11882       return FAILURE;
11883     }
11884
11885   /* Make sure the types of derived parameters are consistent.  This
11886      type checking is deferred until resolution because the type may
11887      refer to a derived type from the host.  */
11888   if (sym->ts.type == BT_DERIVED
11889       && !gfc_compare_types (&sym->ts, &sym->value->ts))
11890     {
11891       gfc_error ("Incompatible derived type in PARAMETER at %L",
11892                  &sym->value->where);
11893       return FAILURE;
11894     }
11895   return SUCCESS;
11896 }
11897
11898
11899 /* Do anything necessary to resolve a symbol.  Right now, we just
11900    assume that an otherwise unknown symbol is a variable.  This sort
11901    of thing commonly happens for symbols in module.  */
11902
11903 static void
11904 resolve_symbol (gfc_symbol *sym)
11905 {
11906   int check_constant, mp_flag;
11907   gfc_symtree *symtree;
11908   gfc_symtree *this_symtree;
11909   gfc_namespace *ns;
11910   gfc_component *c;
11911
11912   if (sym->attr.flavor == FL_UNKNOWN)
11913     {
11914
11915     /* If we find that a flavorless symbol is an interface in one of the
11916        parent namespaces, find its symtree in this namespace, free the
11917        symbol and set the symtree to point to the interface symbol.  */
11918       for (ns = gfc_current_ns->parent; ns; ns = ns->parent)
11919         {
11920           symtree = gfc_find_symtree (ns->sym_root, sym->name);
11921           if (symtree && (symtree->n.sym->generic ||
11922                           (symtree->n.sym->attr.flavor == FL_PROCEDURE
11923                            && sym->ns->construct_entities)))
11924             {
11925               this_symtree = gfc_find_symtree (gfc_current_ns->sym_root,
11926                                                sym->name);
11927               gfc_release_symbol (sym);
11928               symtree->n.sym->refs++;
11929               this_symtree->n.sym = symtree->n.sym;
11930               return;
11931             }
11932         }
11933
11934       /* Otherwise give it a flavor according to such attributes as
11935          it has.  */
11936       if (sym->attr.external == 0 && sym->attr.intrinsic == 0)
11937         sym->attr.flavor = FL_VARIABLE;
11938       else
11939         {
11940           sym->attr.flavor = FL_PROCEDURE;
11941           if (sym->attr.dimension)
11942             sym->attr.function = 1;
11943         }
11944     }
11945
11946   if (sym->attr.external && sym->ts.type != BT_UNKNOWN && !sym->attr.function)
11947     gfc_add_function (&sym->attr, sym->name, &sym->declared_at);
11948
11949   if (sym->attr.procedure && sym->ts.interface
11950       && sym->attr.if_source != IFSRC_DECL
11951       && resolve_procedure_interface (sym) == FAILURE)
11952     return;
11953
11954   if (sym->attr.is_protected && !sym->attr.proc_pointer
11955       && (sym->attr.procedure || sym->attr.external))
11956     {
11957       if (sym->attr.external)
11958         gfc_error ("PROTECTED attribute conflicts with EXTERNAL attribute "
11959                    "at %L", &sym->declared_at);
11960       else
11961         gfc_error ("PROCEDURE attribute conflicts with PROTECTED attribute "
11962                    "at %L", &sym->declared_at);
11963
11964       return;
11965     }
11966
11967
11968   /* F2008, C530. */
11969   if (sym->attr.contiguous
11970       && (!sym->attr.dimension || (sym->as->type != AS_ASSUMED_SHAPE
11971                                    && !sym->attr.pointer)))
11972     {
11973       gfc_error ("'%s' at %L has the CONTIGUOUS attribute but is not an "
11974                   "array pointer or an assumed-shape array", sym->name,
11975                   &sym->declared_at);
11976       return;
11977     }
11978
11979   if (sym->attr.flavor == FL_DERIVED && resolve_fl_derived (sym) == FAILURE)
11980     return;
11981
11982   /* Symbols that are module procedures with results (functions) have
11983      the types and array specification copied for type checking in
11984      procedures that call them, as well as for saving to a module
11985      file.  These symbols can't stand the scrutiny that their results
11986      can.  */
11987   mp_flag = (sym->result != NULL && sym->result != sym);
11988
11989   /* Make sure that the intrinsic is consistent with its internal 
11990      representation. This needs to be done before assigning a default 
11991      type to avoid spurious warnings.  */
11992   if (sym->attr.flavor != FL_MODULE && sym->attr.intrinsic
11993       && resolve_intrinsic (sym, &sym->declared_at) == FAILURE)
11994     return;
11995
11996   /* Resolve associate names.  */
11997   if (sym->assoc)
11998     resolve_assoc_var (sym, true);
11999
12000   /* Assign default type to symbols that need one and don't have one.  */
12001   if (sym->ts.type == BT_UNKNOWN)
12002     {
12003       if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER)
12004         gfc_set_default_type (sym, 1, NULL);
12005
12006       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.external
12007           && !sym->attr.function && !sym->attr.subroutine
12008           && gfc_get_default_type (sym->name, sym->ns)->type == BT_UNKNOWN)
12009         gfc_add_subroutine (&sym->attr, sym->name, &sym->declared_at);
12010
12011       if (sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12012         {
12013           /* The specific case of an external procedure should emit an error
12014              in the case that there is no implicit type.  */
12015           if (!mp_flag)
12016             gfc_set_default_type (sym, sym->attr.external, NULL);
12017           else
12018             {
12019               /* Result may be in another namespace.  */
12020               resolve_symbol (sym->result);
12021
12022               if (!sym->result->attr.proc_pointer)
12023                 {
12024                   sym->ts = sym->result->ts;
12025                   sym->as = gfc_copy_array_spec (sym->result->as);
12026                   sym->attr.dimension = sym->result->attr.dimension;
12027                   sym->attr.pointer = sym->result->attr.pointer;
12028                   sym->attr.allocatable = sym->result->attr.allocatable;
12029                   sym->attr.contiguous = sym->result->attr.contiguous;
12030                 }
12031             }
12032         }
12033     }
12034   else if (mp_flag && sym->attr.flavor == FL_PROCEDURE && sym->attr.function)
12035     gfc_resolve_array_spec (sym->result->as, false);
12036
12037   /* Assumed size arrays and assumed shape arrays must be dummy
12038      arguments.  Array-spec's of implied-shape should have been resolved to
12039      AS_EXPLICIT already.  */
12040
12041   if (sym->as)
12042     {
12043       gcc_assert (sym->as->type != AS_IMPLIED_SHAPE);
12044       if (((sym->as->type == AS_ASSUMED_SIZE && !sym->as->cp_was_assumed)
12045            || sym->as->type == AS_ASSUMED_SHAPE)
12046           && sym->attr.dummy == 0)
12047         {
12048           if (sym->as->type == AS_ASSUMED_SIZE)
12049             gfc_error ("Assumed size array at %L must be a dummy argument",
12050                        &sym->declared_at);
12051           else
12052             gfc_error ("Assumed shape array at %L must be a dummy argument",
12053                        &sym->declared_at);
12054           return;
12055         }
12056     }
12057
12058   /* Make sure symbols with known intent or optional are really dummy
12059      variable.  Because of ENTRY statement, this has to be deferred
12060      until resolution time.  */
12061
12062   if (!sym->attr.dummy
12063       && (sym->attr.optional || sym->attr.intent != INTENT_UNKNOWN))
12064     {
12065       gfc_error ("Symbol at %L is not a DUMMY variable", &sym->declared_at);
12066       return;
12067     }
12068
12069   if (sym->attr.value && !sym->attr.dummy)
12070     {
12071       gfc_error ("'%s' at %L cannot have the VALUE attribute because "
12072                  "it is not a dummy argument", sym->name, &sym->declared_at);
12073       return;
12074     }
12075
12076   if (sym->attr.value && sym->ts.type == BT_CHARACTER)
12077     {
12078       gfc_charlen *cl = sym->ts.u.cl;
12079       if (!cl || !cl->length || cl->length->expr_type != EXPR_CONSTANT)
12080         {
12081           gfc_error ("Character dummy variable '%s' at %L with VALUE "
12082                      "attribute must have constant length",
12083                      sym->name, &sym->declared_at);
12084           return;
12085         }
12086
12087       if (sym->ts.is_c_interop
12088           && mpz_cmp_si (cl->length->value.integer, 1) != 0)
12089         {
12090           gfc_error ("C interoperable character dummy variable '%s' at %L "
12091                      "with VALUE attribute must have length one",
12092                      sym->name, &sym->declared_at);
12093           return;
12094         }
12095     }
12096
12097   /* If the symbol is marked as bind(c), verify it's type and kind.  Do not
12098      do this for something that was implicitly typed because that is handled
12099      in gfc_set_default_type.  Handle dummy arguments and procedure
12100      definitions separately.  Also, anything that is use associated is not
12101      handled here but instead is handled in the module it is declared in.
12102      Finally, derived type definitions are allowed to be BIND(C) since that
12103      only implies that they're interoperable, and they are checked fully for
12104      interoperability when a variable is declared of that type.  */
12105   if (sym->attr.is_bind_c && sym->attr.implicit_type == 0 &&
12106       sym->attr.use_assoc == 0 && sym->attr.dummy == 0 &&
12107       sym->attr.flavor != FL_PROCEDURE && sym->attr.flavor != FL_DERIVED)
12108     {
12109       gfc_try t = SUCCESS;
12110       
12111       /* First, make sure the variable is declared at the
12112          module-level scope (J3/04-007, Section 15.3).  */
12113       if (sym->ns->proc_name->attr.flavor != FL_MODULE &&
12114           sym->attr.in_common == 0)
12115         {
12116           gfc_error ("Variable '%s' at %L cannot be BIND(C) because it "
12117                      "is neither a COMMON block nor declared at the "
12118                      "module level scope", sym->name, &(sym->declared_at));
12119           t = FAILURE;
12120         }
12121       else if (sym->common_head != NULL)
12122         {
12123           t = verify_com_block_vars_c_interop (sym->common_head);
12124         }
12125       else
12126         {
12127           /* If type() declaration, we need to verify that the components
12128              of the given type are all C interoperable, etc.  */
12129           if (sym->ts.type == BT_DERIVED &&
12130               sym->ts.u.derived->attr.is_c_interop != 1)
12131             {
12132               /* Make sure the user marked the derived type as BIND(C).  If
12133                  not, call the verify routine.  This could print an error
12134                  for the derived type more than once if multiple variables
12135                  of that type are declared.  */
12136               if (sym->ts.u.derived->attr.is_bind_c != 1)
12137                 verify_bind_c_derived_type (sym->ts.u.derived);
12138               t = FAILURE;
12139             }
12140           
12141           /* Verify the variable itself as C interoperable if it
12142              is BIND(C).  It is not possible for this to succeed if
12143              the verify_bind_c_derived_type failed, so don't have to handle
12144              any error returned by verify_bind_c_derived_type.  */
12145           t = verify_bind_c_sym (sym, &(sym->ts), sym->attr.in_common,
12146                                  sym->common_block);
12147         }
12148
12149       if (t == FAILURE)
12150         {
12151           /* clear the is_bind_c flag to prevent reporting errors more than
12152              once if something failed.  */
12153           sym->attr.is_bind_c = 0;
12154           return;
12155         }
12156     }
12157
12158   /* If a derived type symbol has reached this point, without its
12159      type being declared, we have an error.  Notice that most
12160      conditions that produce undefined derived types have already
12161      been dealt with.  However, the likes of:
12162      implicit type(t) (t) ..... call foo (t) will get us here if
12163      the type is not declared in the scope of the implicit
12164      statement. Change the type to BT_UNKNOWN, both because it is so
12165      and to prevent an ICE.  */
12166   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->components == NULL
12167       && !sym->ts.u.derived->attr.zero_comp)
12168     {
12169       gfc_error ("The derived type '%s' at %L is of type '%s', "
12170                  "which has not been defined", sym->name,
12171                   &sym->declared_at, sym->ts.u.derived->name);
12172       sym->ts.type = BT_UNKNOWN;
12173       return;
12174     }
12175
12176   /* Make sure that the derived type has been resolved and that the
12177      derived type is visible in the symbol's namespace, if it is a
12178      module function and is not PRIVATE.  */
12179   if (sym->ts.type == BT_DERIVED
12180         && sym->ts.u.derived->attr.use_assoc
12181         && sym->ns->proc_name
12182         && sym->ns->proc_name->attr.flavor == FL_MODULE)
12183     {
12184       gfc_symbol *ds;
12185
12186       if (resolve_fl_derived (sym->ts.u.derived) == FAILURE)
12187         return;
12188
12189       gfc_find_symbol (sym->ts.u.derived->name, sym->ns, 1, &ds);
12190       if (!ds && sym->attr.function && gfc_check_symbol_access (sym))
12191         {
12192           symtree = gfc_new_symtree (&sym->ns->sym_root,
12193                                      sym->ts.u.derived->name);
12194           symtree->n.sym = sym->ts.u.derived;
12195           sym->ts.u.derived->refs++;
12196         }
12197     }
12198
12199   /* Unless the derived-type declaration is use associated, Fortran 95
12200      does not allow public entries of private derived types.
12201      See 4.4.1 (F95) and 4.5.1.1 (F2003); and related interpretation
12202      161 in 95-006r3.  */
12203   if (sym->ts.type == BT_DERIVED
12204       && sym->ns->proc_name && sym->ns->proc_name->attr.flavor == FL_MODULE
12205       && !sym->ts.u.derived->attr.use_assoc
12206       && gfc_check_symbol_access (sym)
12207       && !gfc_check_symbol_access (sym->ts.u.derived)
12208       && gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC %s '%s' at %L "
12209                          "of PRIVATE derived type '%s'",
12210                          (sym->attr.flavor == FL_PARAMETER) ? "parameter"
12211                          : "variable", sym->name, &sym->declared_at,
12212                          sym->ts.u.derived->name) == FAILURE)
12213     return;
12214
12215   /* F2008, C1302.  */
12216   if (sym->ts.type == BT_DERIVED
12217       && sym->ts.u.derived->from_intmod == INTMOD_ISO_FORTRAN_ENV
12218       && sym->ts.u.derived->intmod_sym_id == ISOFORTRAN_LOCK_TYPE
12219       && !sym->attr.codimension)
12220     {
12221       gfc_error ("Variable '%s' at %L of type LOCK_TYPE must be a coarray",
12222                  sym->name, &sym->declared_at);
12223       return;
12224     }
12225
12226   /* An assumed-size array with INTENT(OUT) shall not be of a type for which
12227      default initialization is defined (5.1.2.4.4).  */
12228   if (sym->ts.type == BT_DERIVED
12229       && sym->attr.dummy
12230       && sym->attr.intent == INTENT_OUT
12231       && sym->as
12232       && sym->as->type == AS_ASSUMED_SIZE)
12233     {
12234       for (c = sym->ts.u.derived->components; c; c = c->next)
12235         {
12236           if (c->initializer)
12237             {
12238               gfc_error ("The INTENT(OUT) dummy argument '%s' at %L is "
12239                          "ASSUMED SIZE and so cannot have a default initializer",
12240                          sym->name, &sym->declared_at);
12241               return;
12242             }
12243         }
12244     }
12245
12246   /* F2008, C542.  */
12247   if (sym->ts.type == BT_DERIVED && sym->attr.dummy
12248       && sym->attr.intent == INTENT_OUT && sym->attr.lock_comp)
12249     {
12250       gfc_error ("Dummy argument '%s' at %L of LOCK_TYPE shall not be "
12251                  "INTENT(OUT)", sym->name, &sym->declared_at);
12252       return;
12253     }
12254
12255   /* F2008, C525.  */
12256   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12257        || sym->attr.codimension)
12258       && (sym->attr.result || sym->result == sym))
12259     {
12260       gfc_error ("Function result '%s' at %L shall not be a coarray or have "
12261                  "a coarray component", sym->name, &sym->declared_at);
12262       return;
12263     }
12264
12265   /* F2008, C524.  */
12266   if (sym->attr.codimension && sym->ts.type == BT_DERIVED
12267       && sym->ts.u.derived->ts.is_iso_c)
12268     {
12269       gfc_error ("Variable '%s' at %L of TYPE(C_PTR) or TYPE(C_FUNPTR) "
12270                  "shall not be a coarray", sym->name, &sym->declared_at);
12271       return;
12272     }
12273
12274   /* F2008, C525.  */
12275   if (sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp
12276       && (sym->attr.codimension || sym->attr.pointer || sym->attr.dimension
12277           || sym->attr.allocatable))
12278     {
12279       gfc_error ("Variable '%s' at %L with coarray component "
12280                  "shall be a nonpointer, nonallocatable scalar",
12281                  sym->name, &sym->declared_at);
12282       return;
12283     }
12284
12285   /* F2008, C526.  The function-result case was handled above.  */
12286   if (sym->attr.codimension
12287       && !(sym->attr.allocatable || sym->attr.dummy || sym->attr.save
12288            || sym->ns->save_all
12289            || sym->ns->proc_name->attr.flavor == FL_MODULE
12290            || sym->ns->proc_name->attr.is_main_program
12291            || sym->attr.function || sym->attr.result || sym->attr.use_assoc))
12292     {
12293       gfc_error ("Variable '%s' at %L is a coarray and is not ALLOCATABLE, SAVE "
12294                  "nor a dummy argument", sym->name, &sym->declared_at);
12295       return;
12296     }
12297   /* F2008, C528.  */  /* FIXME: sym->as check due to PR 43412.  */
12298   else if (sym->attr.codimension && !sym->attr.allocatable
12299       && sym->as && sym->as->cotype == AS_DEFERRED)
12300     {
12301       gfc_error ("Coarray variable '%s' at %L shall not have codimensions with "
12302                  "deferred shape", sym->name, &sym->declared_at);
12303       return;
12304     }
12305   else if (sym->attr.codimension && sym->attr.allocatable
12306       && (sym->as->type != AS_DEFERRED || sym->as->cotype != AS_DEFERRED))
12307     {
12308       gfc_error ("Allocatable coarray variable '%s' at %L must have "
12309                  "deferred shape", sym->name, &sym->declared_at);
12310       return;
12311     }
12312
12313   /* F2008, C541.  */
12314   if (((sym->ts.type == BT_DERIVED && sym->ts.u.derived->attr.coarray_comp)
12315        || (sym->attr.codimension && sym->attr.allocatable))
12316       && sym->attr.dummy && sym->attr.intent == INTENT_OUT)
12317     {
12318       gfc_error ("Variable '%s' at %L is INTENT(OUT) and can thus not be an "
12319                  "allocatable coarray or have coarray components",
12320                  sym->name, &sym->declared_at);
12321       return;
12322     }
12323
12324   if (sym->attr.codimension && sym->attr.dummy
12325       && sym->ns->proc_name && sym->ns->proc_name->attr.is_bind_c)
12326     {
12327       gfc_error ("Coarray dummy variable '%s' at %L not allowed in BIND(C) "
12328                  "procedure '%s'", sym->name, &sym->declared_at,
12329                  sym->ns->proc_name->name);
12330       return;
12331     }
12332
12333   switch (sym->attr.flavor)
12334     {
12335     case FL_VARIABLE:
12336       if (resolve_fl_variable (sym, mp_flag) == FAILURE)
12337         return;
12338       break;
12339
12340     case FL_PROCEDURE:
12341       if (resolve_fl_procedure (sym, mp_flag) == FAILURE)
12342         return;
12343       break;
12344
12345     case FL_NAMELIST:
12346       if (resolve_fl_namelist (sym) == FAILURE)
12347         return;
12348       break;
12349
12350     case FL_PARAMETER:
12351       if (resolve_fl_parameter (sym) == FAILURE)
12352         return;
12353       break;
12354
12355     default:
12356       break;
12357     }
12358
12359   /* Resolve array specifier. Check as well some constraints
12360      on COMMON blocks.  */
12361
12362   check_constant = sym->attr.in_common && !sym->attr.pointer;
12363
12364   /* Set the formal_arg_flag so that check_conflict will not throw
12365      an error for host associated variables in the specification
12366      expression for an array_valued function.  */
12367   if (sym->attr.function && sym->as)
12368     formal_arg_flag = 1;
12369
12370   gfc_resolve_array_spec (sym->as, check_constant);
12371
12372   formal_arg_flag = 0;
12373
12374   /* Resolve formal namespaces.  */
12375   if (sym->formal_ns && sym->formal_ns != gfc_current_ns
12376       && !sym->attr.contained && !sym->attr.intrinsic)
12377     gfc_resolve (sym->formal_ns);
12378
12379   /* Make sure the formal namespace is present.  */
12380   if (sym->formal && !sym->formal_ns)
12381     {
12382       gfc_formal_arglist *formal = sym->formal;
12383       while (formal && !formal->sym)
12384         formal = formal->next;
12385
12386       if (formal)
12387         {
12388           sym->formal_ns = formal->sym->ns;
12389           sym->formal_ns->refs++;
12390         }
12391     }
12392
12393   /* Check threadprivate restrictions.  */
12394   if (sym->attr.threadprivate && !sym->attr.save && !sym->ns->save_all
12395       && (!sym->attr.in_common
12396           && sym->module == NULL
12397           && (sym->ns->proc_name == NULL
12398               || sym->ns->proc_name->attr.flavor != FL_MODULE)))
12399     gfc_error ("Threadprivate at %L isn't SAVEd", &sym->declared_at);
12400
12401   /* If we have come this far we can apply default-initializers, as
12402      described in 14.7.5, to those variables that have not already
12403      been assigned one.  */
12404   if (sym->ts.type == BT_DERIVED
12405       && sym->ns == gfc_current_ns
12406       && !sym->value
12407       && !sym->attr.allocatable
12408       && !sym->attr.alloc_comp)
12409     {
12410       symbol_attribute *a = &sym->attr;
12411
12412       if ((!a->save && !a->dummy && !a->pointer
12413            && !a->in_common && !a->use_assoc
12414            && (a->referenced || a->result)
12415            && !(a->function && sym != sym->result))
12416           || (a->dummy && a->intent == INTENT_OUT && !a->pointer))
12417         apply_default_init (sym);
12418     }
12419
12420   if (sym->ts.type == BT_CLASS && sym->ns == gfc_current_ns
12421       && sym->attr.dummy && sym->attr.intent == INTENT_OUT
12422       && !CLASS_DATA (sym)->attr.class_pointer
12423       && !CLASS_DATA (sym)->attr.allocatable)
12424     apply_default_init (sym);
12425
12426   /* If this symbol has a type-spec, check it.  */
12427   if (sym->attr.flavor == FL_VARIABLE || sym->attr.flavor == FL_PARAMETER
12428       || (sym->attr.flavor == FL_PROCEDURE && sym->attr.function))
12429     if (resolve_typespec_used (&sym->ts, &sym->declared_at, sym->name)
12430           == FAILURE)
12431       return;
12432 }
12433
12434
12435 /************* Resolve DATA statements *************/
12436
12437 static struct
12438 {
12439   gfc_data_value *vnode;
12440   mpz_t left;
12441 }
12442 values;
12443
12444
12445 /* Advance the values structure to point to the next value in the data list.  */
12446
12447 static gfc_try
12448 next_data_value (void)
12449 {
12450   while (mpz_cmp_ui (values.left, 0) == 0)
12451     {
12452
12453       if (values.vnode->next == NULL)
12454         return FAILURE;
12455
12456       values.vnode = values.vnode->next;
12457       mpz_set (values.left, values.vnode->repeat);
12458     }
12459
12460   return SUCCESS;
12461 }
12462
12463
12464 static gfc_try
12465 check_data_variable (gfc_data_variable *var, locus *where)
12466 {
12467   gfc_expr *e;
12468   mpz_t size;
12469   mpz_t offset;
12470   gfc_try t;
12471   ar_type mark = AR_UNKNOWN;
12472   int i;
12473   mpz_t section_index[GFC_MAX_DIMENSIONS];
12474   gfc_ref *ref;
12475   gfc_array_ref *ar;
12476   gfc_symbol *sym;
12477   int has_pointer;
12478
12479   if (gfc_resolve_expr (var->expr) == FAILURE)
12480     return FAILURE;
12481
12482   ar = NULL;
12483   mpz_init_set_si (offset, 0);
12484   e = var->expr;
12485
12486   if (e->expr_type != EXPR_VARIABLE)
12487     gfc_internal_error ("check_data_variable(): Bad expression");
12488
12489   sym = e->symtree->n.sym;
12490
12491   if (sym->ns->is_block_data && !sym->attr.in_common)
12492     {
12493       gfc_error ("BLOCK DATA element '%s' at %L must be in COMMON",
12494                  sym->name, &sym->declared_at);
12495     }
12496
12497   if (e->ref == NULL && sym->as)
12498     {
12499       gfc_error ("DATA array '%s' at %L must be specified in a previous"
12500                  " declaration", sym->name, where);
12501       return FAILURE;
12502     }
12503
12504   has_pointer = sym->attr.pointer;
12505
12506   if (gfc_is_coindexed (e))
12507     {
12508       gfc_error ("DATA element '%s' at %L cannot have a coindex", sym->name,
12509                  where);
12510       return FAILURE;
12511     }
12512
12513   for (ref = e->ref; ref; ref = ref->next)
12514     {
12515       if (ref->type == REF_COMPONENT && ref->u.c.component->attr.pointer)
12516         has_pointer = 1;
12517
12518       if (has_pointer
12519             && ref->type == REF_ARRAY
12520             && ref->u.ar.type != AR_FULL)
12521           {
12522             gfc_error ("DATA element '%s' at %L is a pointer and so must "
12523                         "be a full array", sym->name, where);
12524             return FAILURE;
12525           }
12526     }
12527
12528   if (e->rank == 0 || has_pointer)
12529     {
12530       mpz_init_set_ui (size, 1);
12531       ref = NULL;
12532     }
12533   else
12534     {
12535       ref = e->ref;
12536
12537       /* Find the array section reference.  */
12538       for (ref = e->ref; ref; ref = ref->next)
12539         {
12540           if (ref->type != REF_ARRAY)
12541             continue;
12542           if (ref->u.ar.type == AR_ELEMENT)
12543             continue;
12544           break;
12545         }
12546       gcc_assert (ref);
12547
12548       /* Set marks according to the reference pattern.  */
12549       switch (ref->u.ar.type)
12550         {
12551         case AR_FULL:
12552           mark = AR_FULL;
12553           break;
12554
12555         case AR_SECTION:
12556           ar = &ref->u.ar;
12557           /* Get the start position of array section.  */
12558           gfc_get_section_index (ar, section_index, &offset);
12559           mark = AR_SECTION;
12560           break;
12561
12562         default:
12563           gcc_unreachable ();
12564         }
12565
12566       if (gfc_array_size (e, &size) == FAILURE)
12567         {
12568           gfc_error ("Nonconstant array section at %L in DATA statement",
12569                      &e->where);
12570           mpz_clear (offset);
12571           return FAILURE;
12572         }
12573     }
12574
12575   t = SUCCESS;
12576
12577   while (mpz_cmp_ui (size, 0) > 0)
12578     {
12579       if (next_data_value () == FAILURE)
12580         {
12581           gfc_error ("DATA statement at %L has more variables than values",
12582                      where);
12583           t = FAILURE;
12584           break;
12585         }
12586
12587       t = gfc_check_assign (var->expr, values.vnode->expr, 0);
12588       if (t == FAILURE)
12589         break;
12590
12591       /* If we have more than one element left in the repeat count,
12592          and we have more than one element left in the target variable,
12593          then create a range assignment.  */
12594       /* FIXME: Only done for full arrays for now, since array sections
12595          seem tricky.  */
12596       if (mark == AR_FULL && ref && ref->next == NULL
12597           && mpz_cmp_ui (values.left, 1) > 0 && mpz_cmp_ui (size, 1) > 0)
12598         {
12599           mpz_t range;
12600
12601           if (mpz_cmp (size, values.left) >= 0)
12602             {
12603               mpz_init_set (range, values.left);
12604               mpz_sub (size, size, values.left);
12605               mpz_set_ui (values.left, 0);
12606             }
12607           else
12608             {
12609               mpz_init_set (range, size);
12610               mpz_sub (values.left, values.left, size);
12611               mpz_set_ui (size, 0);
12612             }
12613
12614           t = gfc_assign_data_value (var->expr, values.vnode->expr,
12615                                      offset, &range);
12616
12617           mpz_add (offset, offset, range);
12618           mpz_clear (range);
12619
12620           if (t == FAILURE)
12621             break;
12622         }
12623
12624       /* Assign initial value to symbol.  */
12625       else
12626         {
12627           mpz_sub_ui (values.left, values.left, 1);
12628           mpz_sub_ui (size, size, 1);
12629
12630           t = gfc_assign_data_value (var->expr, values.vnode->expr,
12631                                      offset, NULL);
12632           if (t == FAILURE)
12633             break;
12634
12635           if (mark == AR_FULL)
12636             mpz_add_ui (offset, offset, 1);
12637
12638           /* Modify the array section indexes and recalculate the offset
12639              for next element.  */
12640           else if (mark == AR_SECTION)
12641             gfc_advance_section (section_index, ar, &offset);
12642         }
12643     }
12644
12645   if (mark == AR_SECTION)
12646     {
12647       for (i = 0; i < ar->dimen; i++)
12648         mpz_clear (section_index[i]);
12649     }
12650
12651   mpz_clear (size);
12652   mpz_clear (offset);
12653
12654   return t;
12655 }
12656
12657
12658 static gfc_try traverse_data_var (gfc_data_variable *, locus *);
12659
12660 /* Iterate over a list of elements in a DATA statement.  */
12661
12662 static gfc_try
12663 traverse_data_list (gfc_data_variable *var, locus *where)
12664 {
12665   mpz_t trip;
12666   iterator_stack frame;
12667   gfc_expr *e, *start, *end, *step;
12668   gfc_try retval = SUCCESS;
12669
12670   mpz_init (frame.value);
12671   mpz_init (trip);
12672
12673   start = gfc_copy_expr (var->iter.start);
12674   end = gfc_copy_expr (var->iter.end);
12675   step = gfc_copy_expr (var->iter.step);
12676
12677   if (gfc_simplify_expr (start, 1) == FAILURE
12678       || start->expr_type != EXPR_CONSTANT)
12679     {
12680       gfc_error ("start of implied-do loop at %L could not be "
12681                  "simplified to a constant value", &start->where);
12682       retval = FAILURE;
12683       goto cleanup;
12684     }
12685   if (gfc_simplify_expr (end, 1) == FAILURE
12686       || end->expr_type != EXPR_CONSTANT)
12687     {
12688       gfc_error ("end of implied-do loop at %L could not be "
12689                  "simplified to a constant value", &start->where);
12690       retval = FAILURE;
12691       goto cleanup;
12692     }
12693   if (gfc_simplify_expr (step, 1) == FAILURE
12694       || step->expr_type != EXPR_CONSTANT)
12695     {
12696       gfc_error ("step of implied-do loop at %L could not be "
12697                  "simplified to a constant value", &start->where);
12698       retval = FAILURE;
12699       goto cleanup;
12700     }
12701
12702   mpz_set (trip, end->value.integer);
12703   mpz_sub (trip, trip, start->value.integer);
12704   mpz_add (trip, trip, step->value.integer);
12705
12706   mpz_div (trip, trip, step->value.integer);
12707
12708   mpz_set (frame.value, start->value.integer);
12709
12710   frame.prev = iter_stack;
12711   frame.variable = var->iter.var->symtree;
12712   iter_stack = &frame;
12713
12714   while (mpz_cmp_ui (trip, 0) > 0)
12715     {
12716       if (traverse_data_var (var->list, where) == FAILURE)
12717         {
12718           retval = FAILURE;
12719           goto cleanup;
12720         }
12721
12722       e = gfc_copy_expr (var->expr);
12723       if (gfc_simplify_expr (e, 1) == FAILURE)
12724         {
12725           gfc_free_expr (e);
12726           retval = FAILURE;
12727           goto cleanup;
12728         }
12729
12730       mpz_add (frame.value, frame.value, step->value.integer);
12731
12732       mpz_sub_ui (trip, trip, 1);
12733     }
12734
12735 cleanup:
12736   mpz_clear (frame.value);
12737   mpz_clear (trip);
12738
12739   gfc_free_expr (start);
12740   gfc_free_expr (end);
12741   gfc_free_expr (step);
12742
12743   iter_stack = frame.prev;
12744   return retval;
12745 }
12746
12747
12748 /* Type resolve variables in the variable list of a DATA statement.  */
12749
12750 static gfc_try
12751 traverse_data_var (gfc_data_variable *var, locus *where)
12752 {
12753   gfc_try t;
12754
12755   for (; var; var = var->next)
12756     {
12757       if (var->expr == NULL)
12758         t = traverse_data_list (var, where);
12759       else
12760         t = check_data_variable (var, where);
12761
12762       if (t == FAILURE)
12763         return FAILURE;
12764     }
12765
12766   return SUCCESS;
12767 }
12768
12769
12770 /* Resolve the expressions and iterators associated with a data statement.
12771    This is separate from the assignment checking because data lists should
12772    only be resolved once.  */
12773
12774 static gfc_try
12775 resolve_data_variables (gfc_data_variable *d)
12776 {
12777   for (; d; d = d->next)
12778     {
12779       if (d->list == NULL)
12780         {
12781           if (gfc_resolve_expr (d->expr) == FAILURE)
12782             return FAILURE;
12783         }
12784       else
12785         {
12786           if (gfc_resolve_iterator (&d->iter, false) == FAILURE)
12787             return FAILURE;
12788
12789           if (resolve_data_variables (d->list) == FAILURE)
12790             return FAILURE;
12791         }
12792     }
12793
12794   return SUCCESS;
12795 }
12796
12797
12798 /* Resolve a single DATA statement.  We implement this by storing a pointer to
12799    the value list into static variables, and then recursively traversing the
12800    variables list, expanding iterators and such.  */
12801
12802 static void
12803 resolve_data (gfc_data *d)
12804 {
12805
12806   if (resolve_data_variables (d->var) == FAILURE)
12807     return;
12808
12809   values.vnode = d->value;
12810   if (d->value == NULL)
12811     mpz_set_ui (values.left, 0);
12812   else
12813     mpz_set (values.left, d->value->repeat);
12814
12815   if (traverse_data_var (d->var, &d->where) == FAILURE)
12816     return;
12817
12818   /* At this point, we better not have any values left.  */
12819
12820   if (next_data_value () == SUCCESS)
12821     gfc_error ("DATA statement at %L has more values than variables",
12822                &d->where);
12823 }
12824
12825
12826 /* 12.6 Constraint: In a pure subprogram any variable which is in common or
12827    accessed by host or use association, is a dummy argument to a pure function,
12828    is a dummy argument with INTENT (IN) to a pure subroutine, or an object that
12829    is storage associated with any such variable, shall not be used in the
12830    following contexts: (clients of this function).  */
12831
12832 /* Determines if a variable is not 'pure', i.e., not assignable within a pure
12833    procedure.  Returns zero if assignment is OK, nonzero if there is a
12834    problem.  */
12835 int
12836 gfc_impure_variable (gfc_symbol *sym)
12837 {
12838   gfc_symbol *proc;
12839   gfc_namespace *ns;
12840
12841   if (sym->attr.use_assoc || sym->attr.in_common)
12842     return 1;
12843
12844   /* Check if the symbol's ns is inside the pure procedure.  */
12845   for (ns = gfc_current_ns; ns; ns = ns->parent)
12846     {
12847       if (ns == sym->ns)
12848         break;
12849       if (ns->proc_name->attr.flavor == FL_PROCEDURE && !sym->attr.function)
12850         return 1;
12851     }
12852
12853   proc = sym->ns->proc_name;
12854   if (sym->attr.dummy && gfc_pure (proc)
12855         && ((proc->attr.subroutine && sym->attr.intent == INTENT_IN)
12856                 ||
12857              proc->attr.function))
12858     return 1;
12859
12860   /* TODO: Sort out what can be storage associated, if anything, and include
12861      it here.  In principle equivalences should be scanned but it does not
12862      seem to be possible to storage associate an impure variable this way.  */
12863   return 0;
12864 }
12865
12866
12867 /* Test whether a symbol is pure or not.  For a NULL pointer, checks if the
12868    current namespace is inside a pure procedure.  */
12869
12870 int
12871 gfc_pure (gfc_symbol *sym)
12872 {
12873   symbol_attribute attr;
12874   gfc_namespace *ns;
12875
12876   if (sym == NULL)
12877     {
12878       /* Check if the current namespace or one of its parents
12879         belongs to a pure procedure.  */
12880       for (ns = gfc_current_ns; ns; ns = ns->parent)
12881         {
12882           sym = ns->proc_name;
12883           if (sym == NULL)
12884             return 0;
12885           attr = sym->attr;
12886           if (attr.flavor == FL_PROCEDURE && attr.pure)
12887             return 1;
12888         }
12889       return 0;
12890     }
12891
12892   attr = sym->attr;
12893
12894   return attr.flavor == FL_PROCEDURE && attr.pure;
12895 }
12896
12897
12898 /* Test whether a symbol is implicitly pure or not.  For a NULL pointer,
12899    checks if the current namespace is implicitly pure.  Note that this
12900    function returns false for a PURE procedure.  */
12901
12902 int
12903 gfc_implicit_pure (gfc_symbol *sym)
12904 {
12905   symbol_attribute attr;
12906
12907   if (sym == NULL)
12908     {
12909       /* Check if the current namespace is implicit_pure.  */
12910       sym = gfc_current_ns->proc_name;
12911       if (sym == NULL)
12912         return 0;
12913       attr = sym->attr;
12914       if (attr.flavor == FL_PROCEDURE
12915             && attr.implicit_pure && !attr.pure)
12916         return 1;
12917       return 0;
12918     }
12919
12920   attr = sym->attr;
12921
12922   return attr.flavor == FL_PROCEDURE && attr.implicit_pure && !attr.pure;
12923 }
12924
12925
12926 /* Test whether the current procedure is elemental or not.  */
12927
12928 int
12929 gfc_elemental (gfc_symbol *sym)
12930 {
12931   symbol_attribute attr;
12932
12933   if (sym == NULL)
12934     sym = gfc_current_ns->proc_name;
12935   if (sym == NULL)
12936     return 0;
12937   attr = sym->attr;
12938
12939   return attr.flavor == FL_PROCEDURE && attr.elemental;
12940 }
12941
12942
12943 /* Warn about unused labels.  */
12944
12945 static void
12946 warn_unused_fortran_label (gfc_st_label *label)
12947 {
12948   if (label == NULL)
12949     return;
12950
12951   warn_unused_fortran_label (label->left);
12952
12953   if (label->defined == ST_LABEL_UNKNOWN)
12954     return;
12955
12956   switch (label->referenced)
12957     {
12958     case ST_LABEL_UNKNOWN:
12959       gfc_warning ("Label %d at %L defined but not used", label->value,
12960                    &label->where);
12961       break;
12962
12963     case ST_LABEL_BAD_TARGET:
12964       gfc_warning ("Label %d at %L defined but cannot be used",
12965                    label->value, &label->where);
12966       break;
12967
12968     default:
12969       break;
12970     }
12971
12972   warn_unused_fortran_label (label->right);
12973 }
12974
12975
12976 /* Returns the sequence type of a symbol or sequence.  */
12977
12978 static seq_type
12979 sequence_type (gfc_typespec ts)
12980 {
12981   seq_type result;
12982   gfc_component *c;
12983
12984   switch (ts.type)
12985   {
12986     case BT_DERIVED:
12987
12988       if (ts.u.derived->components == NULL)
12989         return SEQ_NONDEFAULT;
12990
12991       result = sequence_type (ts.u.derived->components->ts);
12992       for (c = ts.u.derived->components->next; c; c = c->next)
12993         if (sequence_type (c->ts) != result)
12994           return SEQ_MIXED;
12995
12996       return result;
12997
12998     case BT_CHARACTER:
12999       if (ts.kind != gfc_default_character_kind)
13000           return SEQ_NONDEFAULT;
13001
13002       return SEQ_CHARACTER;
13003
13004     case BT_INTEGER:
13005       if (ts.kind != gfc_default_integer_kind)
13006           return SEQ_NONDEFAULT;
13007
13008       return SEQ_NUMERIC;
13009
13010     case BT_REAL:
13011       if (!(ts.kind == gfc_default_real_kind
13012             || ts.kind == gfc_default_double_kind))
13013           return SEQ_NONDEFAULT;
13014
13015       return SEQ_NUMERIC;
13016
13017     case BT_COMPLEX:
13018       if (ts.kind != gfc_default_complex_kind)
13019           return SEQ_NONDEFAULT;
13020
13021       return SEQ_NUMERIC;
13022
13023     case BT_LOGICAL:
13024       if (ts.kind != gfc_default_logical_kind)
13025           return SEQ_NONDEFAULT;
13026
13027       return SEQ_NUMERIC;
13028
13029     default:
13030       return SEQ_NONDEFAULT;
13031   }
13032 }
13033
13034
13035 /* Resolve derived type EQUIVALENCE object.  */
13036
13037 static gfc_try
13038 resolve_equivalence_derived (gfc_symbol *derived, gfc_symbol *sym, gfc_expr *e)
13039 {
13040   gfc_component *c = derived->components;
13041
13042   if (!derived)
13043     return SUCCESS;
13044
13045   /* Shall not be an object of nonsequence derived type.  */
13046   if (!derived->attr.sequence)
13047     {
13048       gfc_error ("Derived type variable '%s' at %L must have SEQUENCE "
13049                  "attribute to be an EQUIVALENCE object", sym->name,
13050                  &e->where);
13051       return FAILURE;
13052     }
13053
13054   /* Shall not have allocatable components.  */
13055   if (derived->attr.alloc_comp)
13056     {
13057       gfc_error ("Derived type variable '%s' at %L cannot have ALLOCATABLE "
13058                  "components to be an EQUIVALENCE object",sym->name,
13059                  &e->where);
13060       return FAILURE;
13061     }
13062
13063   if (sym->attr.in_common && gfc_has_default_initializer (sym->ts.u.derived))
13064     {
13065       gfc_error ("Derived type variable '%s' at %L with default "
13066                  "initialization cannot be in EQUIVALENCE with a variable "
13067                  "in COMMON", sym->name, &e->where);
13068       return FAILURE;
13069     }
13070
13071   for (; c ; c = c->next)
13072     {
13073       if (c->ts.type == BT_DERIVED
13074           && (resolve_equivalence_derived (c->ts.u.derived, sym, e) == FAILURE))
13075         return FAILURE;
13076
13077       /* Shall not be an object of sequence derived type containing a pointer
13078          in the structure.  */
13079       if (c->attr.pointer)
13080         {
13081           gfc_error ("Derived type variable '%s' at %L with pointer "
13082                      "component(s) cannot be an EQUIVALENCE object",
13083                      sym->name, &e->where);
13084           return FAILURE;
13085         }
13086     }
13087   return SUCCESS;
13088 }
13089
13090
13091 /* Resolve equivalence object. 
13092    An EQUIVALENCE object shall not be a dummy argument, a pointer, a target,
13093    an allocatable array, an object of nonsequence derived type, an object of
13094    sequence derived type containing a pointer at any level of component
13095    selection, an automatic object, a function name, an entry name, a result
13096    name, a named constant, a structure component, or a subobject of any of
13097    the preceding objects.  A substring shall not have length zero.  A
13098    derived type shall not have components with default initialization nor
13099    shall two objects of an equivalence group be initialized.
13100    Either all or none of the objects shall have an protected attribute.
13101    The simple constraints are done in symbol.c(check_conflict) and the rest
13102    are implemented here.  */
13103
13104 static void
13105 resolve_equivalence (gfc_equiv *eq)
13106 {
13107   gfc_symbol *sym;
13108   gfc_symbol *first_sym;
13109   gfc_expr *e;
13110   gfc_ref *r;
13111   locus *last_where = NULL;
13112   seq_type eq_type, last_eq_type;
13113   gfc_typespec *last_ts;
13114   int object, cnt_protected;
13115   const char *msg;
13116
13117   last_ts = &eq->expr->symtree->n.sym->ts;
13118
13119   first_sym = eq->expr->symtree->n.sym;
13120
13121   cnt_protected = 0;
13122
13123   for (object = 1; eq; eq = eq->eq, object++)
13124     {
13125       e = eq->expr;
13126
13127       e->ts = e->symtree->n.sym->ts;
13128       /* match_varspec might not know yet if it is seeing
13129          array reference or substring reference, as it doesn't
13130          know the types.  */
13131       if (e->ref && e->ref->type == REF_ARRAY)
13132         {
13133           gfc_ref *ref = e->ref;
13134           sym = e->symtree->n.sym;
13135
13136           if (sym->attr.dimension)
13137             {
13138               ref->u.ar.as = sym->as;
13139               ref = ref->next;
13140             }
13141
13142           /* For substrings, convert REF_ARRAY into REF_SUBSTRING.  */
13143           if (e->ts.type == BT_CHARACTER
13144               && ref
13145               && ref->type == REF_ARRAY
13146               && ref->u.ar.dimen == 1
13147               && ref->u.ar.dimen_type[0] == DIMEN_RANGE
13148               && ref->u.ar.stride[0] == NULL)
13149             {
13150               gfc_expr *start = ref->u.ar.start[0];
13151               gfc_expr *end = ref->u.ar.end[0];
13152               void *mem = NULL;
13153
13154               /* Optimize away the (:) reference.  */
13155               if (start == NULL && end == NULL)
13156                 {
13157                   if (e->ref == ref)
13158                     e->ref = ref->next;
13159                   else
13160                     e->ref->next = ref->next;
13161                   mem = ref;
13162                 }
13163               else
13164                 {
13165                   ref->type = REF_SUBSTRING;
13166                   if (start == NULL)
13167                     start = gfc_get_int_expr (gfc_default_integer_kind,
13168                                               NULL, 1);
13169                   ref->u.ss.start = start;
13170                   if (end == NULL && e->ts.u.cl)
13171                     end = gfc_copy_expr (e->ts.u.cl->length);
13172                   ref->u.ss.end = end;
13173                   ref->u.ss.length = e->ts.u.cl;
13174                   e->ts.u.cl = NULL;
13175                 }
13176               ref = ref->next;
13177               free (mem);
13178             }
13179
13180           /* Any further ref is an error.  */
13181           if (ref)
13182             {
13183               gcc_assert (ref->type == REF_ARRAY);
13184               gfc_error ("Syntax error in EQUIVALENCE statement at %L",
13185                          &ref->u.ar.where);
13186               continue;
13187             }
13188         }
13189
13190       if (gfc_resolve_expr (e) == FAILURE)
13191         continue;
13192
13193       sym = e->symtree->n.sym;
13194
13195       if (sym->attr.is_protected)
13196         cnt_protected++;
13197       if (cnt_protected > 0 && cnt_protected != object)
13198         {
13199               gfc_error ("Either all or none of the objects in the "
13200                          "EQUIVALENCE set at %L shall have the "
13201                          "PROTECTED attribute",
13202                          &e->where);
13203               break;
13204         }
13205
13206       /* Shall not equivalence common block variables in a PURE procedure.  */
13207       if (sym->ns->proc_name
13208           && sym->ns->proc_name->attr.pure
13209           && sym->attr.in_common)
13210         {
13211           gfc_error ("Common block member '%s' at %L cannot be an EQUIVALENCE "
13212                      "object in the pure procedure '%s'",
13213                      sym->name, &e->where, sym->ns->proc_name->name);
13214           break;
13215         }
13216
13217       /* Shall not be a named constant.  */
13218       if (e->expr_type == EXPR_CONSTANT)
13219         {
13220           gfc_error ("Named constant '%s' at %L cannot be an EQUIVALENCE "
13221                      "object", sym->name, &e->where);
13222           continue;
13223         }
13224
13225       if (e->ts.type == BT_DERIVED
13226           && resolve_equivalence_derived (e->ts.u.derived, sym, e) == FAILURE)
13227         continue;
13228
13229       /* Check that the types correspond correctly:
13230          Note 5.28:
13231          A numeric sequence structure may be equivalenced to another sequence
13232          structure, an object of default integer type, default real type, double
13233          precision real type, default logical type such that components of the
13234          structure ultimately only become associated to objects of the same
13235          kind. A character sequence structure may be equivalenced to an object
13236          of default character kind or another character sequence structure.
13237          Other objects may be equivalenced only to objects of the same type and
13238          kind parameters.  */
13239
13240       /* Identical types are unconditionally OK.  */
13241       if (object == 1 || gfc_compare_types (last_ts, &sym->ts))
13242         goto identical_types;
13243
13244       last_eq_type = sequence_type (*last_ts);
13245       eq_type = sequence_type (sym->ts);
13246
13247       /* Since the pair of objects is not of the same type, mixed or
13248          non-default sequences can be rejected.  */
13249
13250       msg = "Sequence %s with mixed components in EQUIVALENCE "
13251             "statement at %L with different type objects";
13252       if ((object ==2
13253            && last_eq_type == SEQ_MIXED
13254            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name, last_where)
13255               == FAILURE)
13256           || (eq_type == SEQ_MIXED
13257               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13258                                  &e->where) == FAILURE))
13259         continue;
13260
13261       msg = "Non-default type object or sequence %s in EQUIVALENCE "
13262             "statement at %L with objects of different type";
13263       if ((object ==2
13264            && last_eq_type == SEQ_NONDEFAULT
13265            && gfc_notify_std (GFC_STD_GNU, msg, first_sym->name,
13266                               last_where) == FAILURE)
13267           || (eq_type == SEQ_NONDEFAULT
13268               && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13269                                  &e->where) == FAILURE))
13270         continue;
13271
13272       msg ="Non-CHARACTER object '%s' in default CHARACTER "
13273            "EQUIVALENCE statement at %L";
13274       if (last_eq_type == SEQ_CHARACTER
13275           && eq_type != SEQ_CHARACTER
13276           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13277                              &e->where) == FAILURE)
13278                 continue;
13279
13280       msg ="Non-NUMERIC object '%s' in default NUMERIC "
13281            "EQUIVALENCE statement at %L";
13282       if (last_eq_type == SEQ_NUMERIC
13283           && eq_type != SEQ_NUMERIC
13284           && gfc_notify_std (GFC_STD_GNU, msg, sym->name,
13285                              &e->where) == FAILURE)
13286                 continue;
13287
13288   identical_types:
13289       last_ts =&sym->ts;
13290       last_where = &e->where;
13291
13292       if (!e->ref)
13293         continue;
13294
13295       /* Shall not be an automatic array.  */
13296       if (e->ref->type == REF_ARRAY
13297           && gfc_resolve_array_spec (e->ref->u.ar.as, 1) == FAILURE)
13298         {
13299           gfc_error ("Array '%s' at %L with non-constant bounds cannot be "
13300                      "an EQUIVALENCE object", sym->name, &e->where);
13301           continue;
13302         }
13303
13304       r = e->ref;
13305       while (r)
13306         {
13307           /* Shall not be a structure component.  */
13308           if (r->type == REF_COMPONENT)
13309             {
13310               gfc_error ("Structure component '%s' at %L cannot be an "
13311                          "EQUIVALENCE object",
13312                          r->u.c.component->name, &e->where);
13313               break;
13314             }
13315
13316           /* A substring shall not have length zero.  */
13317           if (r->type == REF_SUBSTRING)
13318             {
13319               if (compare_bound (r->u.ss.start, r->u.ss.end) == CMP_GT)
13320                 {
13321                   gfc_error ("Substring at %L has length zero",
13322                              &r->u.ss.start->where);
13323                   break;
13324                 }
13325             }
13326           r = r->next;
13327         }
13328     }
13329 }
13330
13331
13332 /* Resolve function and ENTRY types, issue diagnostics if needed.  */
13333
13334 static void
13335 resolve_fntype (gfc_namespace *ns)
13336 {
13337   gfc_entry_list *el;
13338   gfc_symbol *sym;
13339
13340   if (ns->proc_name == NULL || !ns->proc_name->attr.function)
13341     return;
13342
13343   /* If there are any entries, ns->proc_name is the entry master
13344      synthetic symbol and ns->entries->sym actual FUNCTION symbol.  */
13345   if (ns->entries)
13346     sym = ns->entries->sym;
13347   else
13348     sym = ns->proc_name;
13349   if (sym->result == sym
13350       && sym->ts.type == BT_UNKNOWN
13351       && gfc_set_default_type (sym, 0, NULL) == FAILURE
13352       && !sym->attr.untyped)
13353     {
13354       gfc_error ("Function '%s' at %L has no IMPLICIT type",
13355                  sym->name, &sym->declared_at);
13356       sym->attr.untyped = 1;
13357     }
13358
13359   if (sym->ts.type == BT_DERIVED && !sym->ts.u.derived->attr.use_assoc
13360       && !sym->attr.contained
13361       && !gfc_check_symbol_access (sym->ts.u.derived)
13362       && gfc_check_symbol_access (sym))
13363     {
13364       gfc_notify_std (GFC_STD_F2003, "Fortran 2003: PUBLIC function '%s' at "
13365                       "%L of PRIVATE type '%s'", sym->name,
13366                       &sym->declared_at, sym->ts.u.derived->name);
13367     }
13368
13369     if (ns->entries)
13370     for (el = ns->entries->next; el; el = el->next)
13371       {
13372         if (el->sym->result == el->sym
13373             && el->sym->ts.type == BT_UNKNOWN
13374             && gfc_set_default_type (el->sym, 0, NULL) == FAILURE
13375             && !el->sym->attr.untyped)
13376           {
13377             gfc_error ("ENTRY '%s' at %L has no IMPLICIT type",
13378                        el->sym->name, &el->sym->declared_at);
13379             el->sym->attr.untyped = 1;
13380           }
13381       }
13382 }
13383
13384
13385 /* 12.3.2.1.1 Defined operators.  */
13386
13387 static gfc_try
13388 check_uop_procedure (gfc_symbol *sym, locus where)
13389 {
13390   gfc_formal_arglist *formal;
13391
13392   if (!sym->attr.function)
13393     {
13394       gfc_error ("User operator procedure '%s' at %L must be a FUNCTION",
13395                  sym->name, &where);
13396       return FAILURE;
13397     }
13398
13399   if (sym->ts.type == BT_CHARACTER
13400       && !(sym->ts.u.cl && sym->ts.u.cl->length)
13401       && !(sym->result && sym->result->ts.u.cl
13402            && sym->result->ts.u.cl->length))
13403     {
13404       gfc_error ("User operator procedure '%s' at %L cannot be assumed "
13405                  "character length", sym->name, &where);
13406       return FAILURE;
13407     }
13408
13409   formal = sym->formal;
13410   if (!formal || !formal->sym)
13411     {
13412       gfc_error ("User operator procedure '%s' at %L must have at least "
13413                  "one argument", sym->name, &where);
13414       return FAILURE;
13415     }
13416
13417   if (formal->sym->attr.intent != INTENT_IN)
13418     {
13419       gfc_error ("First argument of operator interface at %L must be "
13420                  "INTENT(IN)", &where);
13421       return FAILURE;
13422     }
13423
13424   if (formal->sym->attr.optional)
13425     {
13426       gfc_error ("First argument of operator interface at %L cannot be "
13427                  "optional", &where);
13428       return FAILURE;
13429     }
13430
13431   formal = formal->next;
13432   if (!formal || !formal->sym)
13433     return SUCCESS;
13434
13435   if (formal->sym->attr.intent != INTENT_IN)
13436     {
13437       gfc_error ("Second argument of operator interface at %L must be "
13438                  "INTENT(IN)", &where);
13439       return FAILURE;
13440     }
13441
13442   if (formal->sym->attr.optional)
13443     {
13444       gfc_error ("Second argument of operator interface at %L cannot be "
13445                  "optional", &where);
13446       return FAILURE;
13447     }
13448
13449   if (formal->next)
13450     {
13451       gfc_error ("Operator interface at %L must have, at most, two "
13452                  "arguments", &where);
13453       return FAILURE;
13454     }
13455
13456   return SUCCESS;
13457 }
13458
13459 static void
13460 gfc_resolve_uops (gfc_symtree *symtree)
13461 {
13462   gfc_interface *itr;
13463
13464   if (symtree == NULL)
13465     return;
13466
13467   gfc_resolve_uops (symtree->left);
13468   gfc_resolve_uops (symtree->right);
13469
13470   for (itr = symtree->n.uop->op; itr; itr = itr->next)
13471     check_uop_procedure (itr->sym, itr->sym->declared_at);
13472 }
13473
13474
13475 /* Examine all of the expressions associated with a program unit,
13476    assign types to all intermediate expressions, make sure that all
13477    assignments are to compatible types and figure out which names
13478    refer to which functions or subroutines.  It doesn't check code
13479    block, which is handled by resolve_code.  */
13480
13481 static void
13482 resolve_types (gfc_namespace *ns)
13483 {
13484   gfc_namespace *n;
13485   gfc_charlen *cl;
13486   gfc_data *d;
13487   gfc_equiv *eq;
13488   gfc_namespace* old_ns = gfc_current_ns;
13489
13490   /* Check that all IMPLICIT types are ok.  */
13491   if (!ns->seen_implicit_none)
13492     {
13493       unsigned letter;
13494       for (letter = 0; letter != GFC_LETTERS; ++letter)
13495         if (ns->set_flag[letter]
13496             && resolve_typespec_used (&ns->default_type[letter],
13497                                       &ns->implicit_loc[letter],
13498                                       NULL) == FAILURE)
13499           return;
13500     }
13501
13502   gfc_current_ns = ns;
13503
13504   resolve_entries (ns);
13505
13506   resolve_common_vars (ns->blank_common.head, false);
13507   resolve_common_blocks (ns->common_root);
13508
13509   resolve_contained_functions (ns);
13510
13511   if (ns->proc_name && ns->proc_name->attr.flavor == FL_PROCEDURE
13512       && ns->proc_name->attr.if_source == IFSRC_IFBODY)
13513     resolve_formal_arglist (ns->proc_name);
13514
13515   gfc_traverse_ns (ns, resolve_bind_c_derived_types);
13516
13517   for (cl = ns->cl_list; cl; cl = cl->next)
13518     resolve_charlen (cl);
13519
13520   gfc_traverse_ns (ns, resolve_symbol);
13521
13522   resolve_fntype (ns);
13523
13524   for (n = ns->contained; n; n = n->sibling)
13525     {
13526       if (gfc_pure (ns->proc_name) && !gfc_pure (n->proc_name))
13527         gfc_error ("Contained procedure '%s' at %L of a PURE procedure must "
13528                    "also be PURE", n->proc_name->name,
13529                    &n->proc_name->declared_at);
13530
13531       resolve_types (n);
13532     }
13533
13534   forall_flag = 0;
13535   gfc_check_interfaces (ns);
13536
13537   gfc_traverse_ns (ns, resolve_values);
13538
13539   if (ns->save_all)
13540     gfc_save_all (ns);
13541
13542   iter_stack = NULL;
13543   for (d = ns->data; d; d = d->next)
13544     resolve_data (d);
13545
13546   iter_stack = NULL;
13547   gfc_traverse_ns (ns, gfc_formalize_init_value);
13548
13549   gfc_traverse_ns (ns, gfc_verify_binding_labels);
13550
13551   if (ns->common_root != NULL)
13552     gfc_traverse_symtree (ns->common_root, resolve_bind_c_comms);
13553
13554   for (eq = ns->equiv; eq; eq = eq->next)
13555     resolve_equivalence (eq);
13556
13557   /* Warn about unused labels.  */
13558   if (warn_unused_label)
13559     warn_unused_fortran_label (ns->st_labels);
13560
13561   gfc_resolve_uops (ns->uop_root);
13562
13563   gfc_current_ns = old_ns;
13564 }
13565
13566
13567 /* Call resolve_code recursively.  */
13568
13569 static void
13570 resolve_codes (gfc_namespace *ns)
13571 {
13572   gfc_namespace *n;
13573   bitmap_obstack old_obstack;
13574
13575   if (ns->resolved == 1)
13576     return;
13577
13578   for (n = ns->contained; n; n = n->sibling)
13579     resolve_codes (n);
13580
13581   gfc_current_ns = ns;
13582
13583   /* Don't clear 'cs_base' if this is the namespace of a BLOCK construct.  */
13584   if (!(ns->proc_name && ns->proc_name->attr.flavor == FL_LABEL))
13585     cs_base = NULL;
13586
13587   /* Set to an out of range value.  */
13588   current_entry_id = -1;
13589
13590   old_obstack = labels_obstack;
13591   bitmap_obstack_initialize (&labels_obstack);
13592
13593   resolve_code (ns->code, ns);
13594
13595   bitmap_obstack_release (&labels_obstack);
13596   labels_obstack = old_obstack;
13597 }
13598
13599
13600 /* This function is called after a complete program unit has been compiled.
13601    Its purpose is to examine all of the expressions associated with a program
13602    unit, assign types to all intermediate expressions, make sure that all
13603    assignments are to compatible types and figure out which names refer to
13604    which functions or subroutines.  */
13605
13606 void
13607 gfc_resolve (gfc_namespace *ns)
13608 {
13609   gfc_namespace *old_ns;
13610   code_stack *old_cs_base;
13611
13612   if (ns->resolved)
13613     return;
13614
13615   ns->resolved = -1;
13616   old_ns = gfc_current_ns;
13617   old_cs_base = cs_base;
13618
13619   resolve_types (ns);
13620   resolve_codes (ns);
13621
13622   gfc_current_ns = old_ns;
13623   cs_base = old_cs_base;
13624   ns->resolved = 1;
13625
13626   gfc_run_passes (ns);
13627 }